Derived type with some components private

Suppose you have a derived type that stores the results of a simple linear regression:

type reg
   real              :: slope,intercept
   real, allocatable :: residuals(:)
end type reg

You always want to store the slope and intercept of the regression, but you may not want to store the residuals. It would be nice if slope and intercept were PUBLIC while residuals were PRIVATE. That way you would prevented from accessing the residuals component when it has not been ALLOCATEd. It would be accessed through a function that makes appropriate checks. How can this functionality be achieved?

@Beliavsky,

This is yet another instance that should inform you to advance well beyond Fortran 95 and consider current Fortran standard and compilers which support it fully such as IFORT in Intel oneAPI.

Starting with Fortran 2003 way back in 2004, it has been possible to do the following:

type :: reg
    real, public :: slope, intercept
    real, allocatable, private :: residuals(:)
end type

There are variants possible such as marking derived-type components as all PRIVATE by default and only marking certain components as PUBLIC and some other constraints such as the derived type definition has be to in a MODULE for the PRIVATE/{PUBLIC accessibility is with respect to the MODULE scope and so forth.

The proxy document for the Fortran standard and/or books such as Modern Fortran Explained are the best sources to grasp all the details.

1 Like

Thanks. I see section 8.15 Derived-type definitions of “Modern Fortran Explained: Incorporating Fortran 2018”. (I own several editions of MFE, but it is terse and “quite dry”, as a recent book described it.) In the “Modern Fortran” book of Curcic, the relevant section is 8.3.3 Controlling access to type components and methods, and reading that caused me to experiment. Curcic writes,

An interesting caveat to private type components is that they make it impossible to use a default type constructor.

On Stack Overflow, someone elaborated that this does not apply to allocatable and pointer components. Thus, the following program compiles and runs with gfortran and Intel Fortran:

module dt_mod
implicit none
type reg
   real, public               :: slope,intercept
   real, private, allocatable :: residuals(:)
end type reg
contains
function allocated_residuals(x) result(tf)
type(reg), intent(in) :: x
logical               :: tf
tf = allocated(x%residuals)
end function allocated_residuals
end module dt_mod
!
program main
use dt_mod, only: reg,allocated_residuals
implicit none
type(reg) :: foo
foo = reg(2.1,3.4)
print*,foo%slope,foo%intercept
print*,allocated_residuals(foo)
end program main

giving

   2.09999990       3.40000010    
 F
1 Like

Nice! I didn’t know about this feature, and it seems quite useful.

I agree completely with your assessment on the “MFE” book in terms of its style. Moreover, the latest the 5th Edition incorporating Fortran 2018 is a further deterioration on the style in several ways and even the organization of the whole content leaves much to be desired. But it is the “best” Fortran has got in terms of covering the whole standard and thus it’s the go-to reference for what the standard has to offer.

Now, note with the following 3 crucial aspects

  1. standard semantics with pointer and allocatable components regardless of its accessibility attributes i.e., private/public,
  2. default initialization of components,
  3. the option to write generic interfaces to module subprograms (functions) with the same name as the derived type,

you’ve a fair bit of facility to work with derived types. Not just that, you’re now “inches away” from adopting the object-oriented (OO) approach also in your code design.

So you can do if you so wish:

module linear_reg_m
   private
   type, public :: linear_reg_t
      private
      real :: R_squared = 0.0  ! note default initialized to zero
      real, allocatable :: residuals(:)
      real, public :: slope = 0.0 ! note default initialized to zero
      real, public :: intercept = 0.0 ! note default initialized to zero
   contains
      private
      procedure, pass(this), public :: allocated_residuals !<-- a subprogram that operates on data of the derived type
   end type
contains
   function allocated_residuals(this) result(tf)
      class(linear_reg_t), intent(in) :: this
      logical :: tf
      tf = allocated( this%residuals )
   end function
end module
   use linear_reg_m, only : linear_reg_t
   type(linear_reg_t) :: foo
   foo = linear_reg_t( slope=2.1, intercept=3.4 )
   print *, foo%slope,foo%intercept
   print *, foo%allocated_residuals()
end

For anyone interested in learning more about user-defined “constructors” via a generic interface that has the same name as the derived type, see below a simple example to experiment with using gfortran , Intel oneAPI IFORT, etc.

The example uses the topic at hand of linear regression. Note also with the question in the original post with derived type components being PRIVATE, that notion has been extended to the basic OO concept of information hiding and data encapsulation in this example.

I’ll leave it to critics of OO to give commentary on how such a style can be unwieldy in some circumstances!

module linear_reg_m

   private

   type, public :: linear_reg_t
      private ! All components private by default
      real :: m_n = 0.0
      real :: m_R_squared = 0.0  ! note default initialized to zero
      real :: m_slope = 0.0
      real :: m_intercept = 0.0
      real :: m_Sx = 0.0
      real :: m_Sy = 0.0
      real :: m_Sxx = 0.0
      real :: m_Syy = 0.0
      real :: m_Sxy = 0.0
      real, allocatable :: m_residuals(:)
   contains
      private
      procedure, pass(this), public :: intercept => get_intercept
      procedure, pass(this), public :: residuals => get_residuals
      procedure, pass(this), public :: slope => get_slope
      procedure, pass(this), public :: y => calc_y
   end type

   interface linear_reg_t ! Generic interface
      module procedure construct_linear_reg_basic
      module procedure construct_linear_reg_data
   end interface

contains

   function construct_linear_reg_basic( slope, intercept ) result(r)

      real, intent(in) :: slope
      real, intent(in) :: intercept
      ! Function result
      type(linear_reg_t) :: r

      r%m_slope = slope
      r%m_intercept = intercept

   end function

   function construct_linear_reg_data( x, y ) result(r)

      real, intent(in) :: x(:)
      real, intent(in) :: y(:)
      ! Function result
      type(linear_reg_t) :: r

      ! Elided are checks on data
      r%m_n = real( size(x) )
      r%m_Sx = sum( x )
      r%m_Sy = sum( y )
      r%m_Sxx = dot_product( x, x )
      r%m_Syy = dot_product( y, y )
      r%m_Sxy = dot_product( x, y )

      r%m_slope = ( r%m_n*r%m_Sxy - r%m_Sx*r%m_Sy) / (r%m_n*r%m_Sxx - r%m_Sx**2)
      r%m_intercept = ( r%m_Sy - r%m_slope*r%m_Sx ) / r%m_n

      allocate( r%m_residuals(size(x)) )
      r%m_residuals = calc_y( r, x ) - y

    end function

   elemental function get_intercept( this ) result(intercept)

      class(linear_reg_t), intent(in) :: this
      ! Function result
      real :: intercept

      intercept = this%m_intercept

   end function

   elemental function get_slope( this ) result(slope)

      class(linear_reg_t), intent(in) :: this
      ! Function result
      real :: slope

      slope = this%m_slope

   end function

   elemental function calc_y( this, x ) result(y)

      class(linear_reg_t), intent(in) :: this
      real, intent(in) :: x
      ! Function result
      real :: y

      y = this%m_slope*x + this%m_intercept

   end function

   function get_residuals(this) result(residuals)

      class(linear_reg_t), intent(in) :: this
      ! Function result
      real, allocatable :: residuals(:)

      ! Elided are checks on state
      if ( allocated(this%m_residuals) ) then
         residuals = this%m_residuals
      else
         ! Return a zero-sized vector?
         residuals = [ real :: ]
      end if

   end function

end module

   use linear_reg_m, only : linear_reg_t

   blk1: block

      real, allocatable :: height(:)
      real, allocatable :: weight(:)
      type(linear_reg_t) :: model

      print *, "Block 1: Linear Regression of some data"
      ! Arbitrary data
      height = [ 1.47, 1.50, 1.52, 1.55, 1.57, 1.60 ]
      weight = [ 52.21, 53.12, 54.48, 55.84, 57.20, 58.57 ]

      model = linear_reg_t( x=height, y=weight )  !<< Construct model using raw data
      print *, "Slope: ", model%slope()
      print *, "Intercept: ", model%intercept()
      print *, "Residuals: ", new_line(""), model%residuals()

   end block blk1

   print *

   blk2: block

      type(linear_reg_t) :: model

      print *, "Block 2: Calculation using an arbitrary model"

      model = linear_reg_t( slope=61.272, intercept=-39.062 ) !<< Construct model using reduced data
      print *, "y(x) at x=1.5: ", model%y( x=1.5 )

   end block blk2

end

Upon execution with gfortran, the output is as I expect:

Block 1: Linear Regression of some data
Slope: 50.7999115
Intercept: -22.7411957
Residuals:
-0.275321960 0.338672638 -5.32913208E-03 0.158664703 -0.185329437 -3.13339233E-02

Block 2: Calculation using an arbitrary model
y(x) at x=1.5: 52.8459969

1 Like

Well, I did not really touch the private aspect, but it is sort of implied.

BTW, I always liked MFE the most. It works great as a handbook and a complete course text book unlike other books like the Fortran for Scientists and Engineers series with many discussions and examples that make finding the actual restrictions and rules difficult with so many long worked examples and intros. I bought it to my library but mostly only work with MFE in my course. Other books may be good for beginner’s self-study but once one learns the basic, MFE is the best book to return to for reference.

2 Likes