A question about the OO style

Hi, guys. I need some help here!
Suppose I have a module like this,

Should I use the style I commented or should I use the original version, and which one is better?

While I am no specialist for Fortran OO programming, I believe the compiler will produce the same code in both cases.

Personally, I prefer the first one because it is shorter. But since average_func does not actually use any internals from this (unused dummy argument) the question arises why make it available through the derived type.

In cases where you need to access many members of your derived type (and reuse them) you can also use an associate construct:

  function covariance_func(self,x,y) result(ret)
    class(test_t), intent(in) :: self
    real, intent(in) :: x(:), y(:)
    real :: ret

    associate(ax => self%avg(x), ay => self%avg(y))
      ret = self%avg((x - ax)*(y - ay))
    end associate
  end function

In this short example however, it is not that useful.

In the case of this example, the OO style here is overkill. Unless you expect someone to extend your type and provide a different implementation for average_func (which I think can’t actually be done since you’ve marked it private), then there’s no reason reason to call the function through the object. In fact, this implementation will (likely) be slower, because it needs to do a VTable lookup to find the function implementation at runtime, because as far as the compiler knows, you may have passed in a child type with a different implementation.

1 Like

@han190,

For what you show, please note for the typical applications of Fortran in scientific and technical computing, you’d use neither of your options nor an OO-style at all, though one of the key aspects of OO with information hiding can still be employed with MODULE-based programming. Rather, Fortranners will expect a functional programming style along with the powerful option in Fortran with PURE keyword that can also help consumers of your code.

Another consideration will be to bring in as much as generic programming as reasonably possible considering the limitations of Fortran. So in this instance, you can think of bringing in KIND genericity.

Also, @ivanpribec’s suggestion of the ASSOCIATE construct can come in really handy with performance for medium to large datasets up to a certain size depending on the processor. Here’s an example:

module kinds_m
   use, intrinsic :: iso_fortran_env, only : real_kinds
   ! A processor can be expected to support at least 2 kinds of REAL, perhaps more
   integer, parameter :: RK1 = real_kinds(1), RK2 = real_kinds(2)
end module

module stats_m

   use kinds_m, only : RK1, RK2 ! elided is support for more kinds

   private

   generic, public :: avg => avg_rk1, avg_rk2
   generic, public :: cov => cov_rk1, cov_rk2

contains

   pure function avg_rk1( x ) result( r )
      ! Argument list
      real(rk1), intent(in) :: x(:)
      ! Function result
      real(rk1) :: r
      r = sum(x)/size(x)
      return
   end function
   pure function avg_rk2( x ) result( r )
      ! Argument list
      real(rk2), intent(in) :: x(:)
      ! Function result
      real(rk2) :: r
      r = sum(x)/size(x)
      return
   end function

   pure function cov_rk1( x, y ) result( r )
      ! Argument list
      real(rk1), intent(in) :: x(:)
      real(rk1), intent(in) :: y(:)
      ! Function result
      real(rk1) :: r
      associate ( avg_x => avg(x), avg_y => avg(y) )
         r = avg( (x - avg_x)*(y - avg_y) )
      end associate
      return
   end function
   pure function cov_rk2( x, y ) result( r )
      ! Argument list
      real(rk2), intent(in) :: x(:)
      real(rk2), intent(in) :: y(:)
      ! Function result
      real(rk2) :: r
      associate ( avg_x => avg(x), avg_y => avg(y) )
         r = avg( (x - avg_x)*(y - avg_y) )
      end associate
      return
   end function

end module

program p
   use stats_m, only : avg, cov
   blk1: block
      real :: x(3), y(3) !<- default real; likely will map to RK1
      x = [ 0.45, 0.5, 0.55 ]
      y = [ 0.95, 1.0, 1.05 ]
      print *, "Block 1: working with precision of ", precision( x(1) )
      print *, "avg(x) = ", avg(x)
      print *, "cov(x,y) = ", cov(x,y)
   end block blk1
   print *
   blk2: block
      integer, parameter :: RK = selected_real_kind( p=12 )
      real(RK) :: x(3), y(3) !<- likely will map to RK2
      x = [ 0.45_rk, 0.5_rk, 0.55_rk ]
      y = [ 0.95_rk, 1.0_rk, 1.05_rk ]
      print *, "Block 2: working with precision of ", precision( x(1) )
      print *, "avg(x) = ", avg(x)
      print *, "cov(x,y) = ", cov(x,y)
   end block blk2
   stop
end program

Upon execution with a commercial compiler, the output is as expected:

C:\Temp>ifort /standard-semantics /warn:all /stand:f18 p.f90
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, Version 19.1.2.254 Build 20200623
Copyright (C) 1985-2020 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.26.28806.0
Copyright (C) Microsoft Corporation. All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\Temp>p.exe
Block 1: working with precision of 6
avg(x) = 0.5000000
cov(x,y) = 1.6666665E-03

Block 2: working with precision of 15
avg(x) = 0.500000000000000
cov(x,y) = 1.666666666666669E-003

C:\Temp>

1 Like

@everythingfunctional, @FortranFan

Hi, thanks for the reply! I am aware this is an overkill. I guess I didn’t make my question clear. I am wondering should I use the style self%func(a, b) or func(this, a, b) if I want to call a type-bound procedure in a type-bound procedure? I am definitely not going to use this implementation in my code nor will I frequently use OO style in scientific computing. I am just curious if the compiler will treat these two styles differently?

This Dr Fortran blog may be of more help to you as well as other readers here. Especially the “under the hood” section:

if you pass a non-polymorphic variable to a polymorphic dummy argument ( class() ), the compiler has to construct a class descriptor at the point of the call. Yes, there are optimizations that can be done, but this is still a complex operation that can generate hundreds of instructions. Try not to do this a lot if performance is a goal.

Check and verify with your compiler always, but if you can avoid situations such as above, you should be alright.

1 Like

I am wondering should I use the style self%func(a, b) or func(this, a, b) if I want to call a type-bound procedure in a type-bound procedure?

If you’re calling a type-bound procedure, use the OO syntax. If you don’t, it obfuscates the fact that it is a type-bound procedure and that the overhead of polymorphism is involved.

2 Likes

Though not very sure, apart from performance, isn’t it related to “dynamic vs static” dispatch things? For example, the following code gives different results when using “self % func()” vs “func( self )”.

module test_m
    implicit none

    type Parent_t
    contains
        procedure :: sub
        procedure :: func
    endtype

    type, extends(Parent_t) :: Child_t
    contains
        procedure :: func => Child_func   !! overrides Parent's "func"
    endtype
        
contains
    subroutine sub( self )
        class(Parent_t) :: self

        print *, self% func()    !! --> 200 (via dynamic dispatch)
        ! print *, func( self )    !! --> 100 (via static dispatch)
    end
    function func( self ) result( ret )
        class(Parent_t) :: self
        integer :: ret
        ret = 100
    end
    function Child_func( self ) result( ret )
        class(Child_t) :: self
        integer :: ret
        ret = 200
    end
end

program main
    use test_m
    implicit none
    class(Parent_t), allocatable :: p

    allocate( Child_t :: p )

    call p % sub()
end

(Apart from OO, I use a similar thing to create a “module type” that contains various module procedures and used to allow module_name % module_proc().)

2 Likes

Note this can be a gotcha with the OO paradigm generally but also with Fortran.

In the case of Fortran, coders - if they wish to be careful - can provide the binding-name along the lines of a generic name and employ distinct procedure-names which will help prevent such ambiguities e.g.,

..
   type Parent_t
   contains
      procedure :: sub
      procedure :: func => Parent_func
   end type
..

in which case the following will not work and the processor will issue a diagnostic:

   subroutine sub( self )
      class(Parent_t) :: self
      ..
      print *, func( self )  !  will not compile

whereas self%func() or Parent_func( self ) will be alright and the result will be consistent with how the program was authored whether the writer’s intent was subconscious or conscious!

3 Likes