Traits/interfaces in Fortran?

@gronki,

Here’s some narrow input in the sense of how to circumvent the current limitations using verbose solutions that employ facilities possibly not best intended for the task at hand i.e., the use unlimited polymorphism and other OO patterns as a poor Fortranner’s substitute for generic programming, something that I ordinarily do not recommend.

Here’s an illustration of which the underlying simple and silly idea will be well known to you but which may be more beneficial to other readers of this forum. It’s mostly based on the same notion as I communicated earlier with a “super” base class and a lot of boilerplate type of code including setting up a “library” of “utility” procedures, as needed.

Note here the “utility” is based on the specific case you bring up in the original post i.e., a “generic” procedure to stringify an object in Fortran, shown here for two intrinsic types (default integer and real) and all those that extend from the base type.

Click here for code
module base_m
   type, abstract :: base_t
   contains
      procedure(Istringfy), deferred :: ToString
   end type
   abstract interface
      function Istringfy( this ) result(s)
         import :: base_t
         ! Argument list
         class(base_t), intent(in) :: this
         ! Function result
         character(len=:), allocatable :: s
      end function 
   end interface
end module
module utils_m
   use base_m, only : base_t
contains
   function ToString( this ) result(s)
      ! Argument list
      class(*), intent(in) :: this
      ! Function result
      character(len=:), allocatable :: s
      allocate( character(len=256) :: s )
      select type ( this )
         type is ( integer )
            write( unit=s, fmt=* ) this
         type is ( real )
            write( unit=s, fmt=* ) this
         class is ( base_t )
            s = this%ToString()
         class default 
      end select
      s = trim( s )
   end function 
end module
module circle_m
   use base_m, only : base_t
   use utils_m, only : ToString
   type, extends(base_t) :: circle_t
      real :: r
   contains
      procedure :: ToString => CircleToString
   end type
   real, parameter :: PI=3.14159265359
contains
   function CircleToString( this ) result(s)
      ! Argument list
      class(circle_t), intent(in) :: this
      ! Function result
      character(len=:), allocatable :: s
      s = "I am a circle with an area of " // ToString( PI*this%r**2 ) 
   end function 
end module
   use circle_m, only : circle_t
   type(circle_t) :: c
   c%r = 1.0
   call print_anything( 42 )
   call print_anything( c )
contains
   subroutine print_anything( a )
      use utils_m, only : ToString
      class(*), intent(in) :: a
      print *, ToString( a )
   end subroutine
end    
Click here for compiler response
C:\temp>gfortran -ffree-form p.f -o p.exe

C:\temp>p.exe
           42
 I am a circle with an area of    3.14159274

P.S.> With respect to Fortran 2023 (the upcoming standard revision), note the ALLOCATE statement in the silly illustration above will be unnecessary c.f. WG5 N2212 document:

When a deferred-length allocatable variable is defined by intrinsic assignment, as in the example
character(:), allocatable :: quotation
:
quotation = ‘Now is the winter of our discontent.’
it is allocated by the processor to the correct length. This behaviour is extended to … writing to a scalar character variable as an internal file …