Traits/interfaces in Fortran?

So I was wondering, if there is any way to implement a behavior that would be similar to Rust traits or Java interfaces. As we know, Fortran OOP is single-inheritance only, which is good, since any kind of inheritance seems to be considered an anti-pattern recently. Interfaces/traits, however, do not permit any data to be added to the type – only methods. This allows for flexible polymorphism without all the constructor/destructor hell.For instance, consider the following pseudocode:

trait StrConvertible
   procedure(asstr_proto) :: asStr()
end trait

abstract interface
  function :: asstr_proto(self) result(strrepr)
    import StrConvertible
    class(StrConvertible) :: self
    character(len=:), allocatable :: strrepr
  end subroutine
end interface

type, extends(Shape), facilitates(StrConvertible) :: Circle
contains
   generic :: asStr => circle_asstr
end type

Then one could use it the following way:

subroutine print_anything(s)
   class(StrConvertible) :: s
   print *, s % asStr()
end subroutine

! ...

type(Circle) :: c
call print_anything(c)

Of course, this is only dream matter. But is it possible to currently perform such pattern, using Fortran 2023 revision? In other words, simulate multiple inheritance, assuming that we only inherit methods but not any actual class-data. The requirement is that it must be dynamically extensible (so when I make a new type that implements method toStr, it must work with the old code without changing it – a requirement that procedure interfaces in Fortran do not meet, as far as I understand). Perhaps some procedure pointers can be used, but I can’t fully wrap my head around how to do it, since function pointer is a data anyway.

Alternatively, do you guys have any idea how to circumvent these crazy restrictions and write an extensible and flexible code in Fotran? Perhaps some other patterns could be developed to achieve that. I am very curious about your narrow and broad input on the topic.

Have a nice day!
Dominik

2 Likes

Might this be of interest to what you want to do Dynamic user-procedure list initialization ?

I think something like Rust traits is a great idea. Being able to write code using interfaces as the common point connecting different pieces together should allow much more flexible programs without rigid inheritance structures.

Nothing like this is available in F2023. I can say that Rust traits and Java Interfaces did have some influence in the design of the F202Y Generics features. I expect the final product (even if the final pieces aren’t in til F203Z) will have some resemblance to these ideas.

That said, if you want to “approximate” the idea in current Fortran you can with some extra work.

type, extends(my_trait) :: my_type_wrapper
  type(my_type) :: obj
contains
  procedure :: trait_proc
end type

contains

subroutine trait_proc(self)
  class(my_type_wrapper) :: self

  call self%obj%trait_proc()
end subroutine

Then you can do something like

call needs_trait(my_type_wrapper(my_type_obj))

Not the prettiest, but not impossible.

1 Like

Brilliant, I was looking for something like this, just could not put two and two together! Now if obj is a pointer, this could be even done without copying I suppose, right? Thank you very much!

As for generics, indeed I have noticed some similarity. I hope this proposal gets passed! This will be the best day in Fortran since F90 :slight_smile:

Dominik

Yes, but the usage may not be quite so succinct.

Why is that?

For one, it’s not valid to have a pointer to something that isn’t a target. It ends up looking more like

type, extends(my_trait) :: my_type_wrapper
  type(my_type), pointer :: obj => null()
contains
  procedure :: take_reference
  procedure :: trait_proc
end type

contains

subroutine take_reference(self, ref)
  class(my_type_wrapper), intent(inout) :: self
  type(my_type), target, intent(in) :: ref

  self%obj => ref
end subroutine

subroutine trait_proc(self)
  class(my_type_wrapper) :: self

  if (associated(self%obj)) call self%obj%trait_proc()
end subroutine
type(my_type), target :: my_type_obj
type(my_type_wrapper) :: wrapper

call wrapper%take_reference(my_type_obj)
call needs_trait(wrapper)

Not too much worse. It all depends on your style and use case.

@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 …

If the readers focus on the use case provided OP, do note it reduces to that of a generic procedure.

Please see this thread.

So note Fortran has long-standing support for list-directed IO and it is already quite generic. Note all intrinsic types support list-directed IO and any derived type with defined IO can do as well. A processor can then verify this at compile-time instantiation.

Therefore, any work toward Generic features in Fortran 202Y thru’ Fortran 203Z must strive to build on the existing semantics from the days of FORTRAN I and keep it simple and not take so many years to standardize. Currently Fortranners may be looking at year 2048 and later they can avail themselves of any robust implementations, given the expected timeline indicated here!

For the specific case brought up by OP in the original post, Fortranners should simply be able to author a templated procedure like so - note any syntax employed here is for illustration purposes only.

Note here OP’s print_anything is deemed a templated subroutine that can be processed independently with strong concepts so that meaningful and compact diagnostics can be reported by the processor for any semantic or syntactical violations.

!  a templated subroutine as above
template subroutine print_anything<T>( s )
   template T
   supports write(formatted)  !<-- informs processor formatted IO is viable with T
   end template
   <T>, intent(in) :: s  !<-- <T> signifies all attributes except `INTENT` based on template T
   print *, s  !<-- listed-directed IO; write(formatted) stipulation above with T ensures this is kosher
end subroutine
..
   call print_anything<integer>( 42 )  !<-- *in situ* compile-time instantiation
..
   type(circle_t) :: c
..
   call print_anything<circle_t>( c )   !<-- *in situ* compile-time instantiation

Fortranners must all take close note:

  • Generics in Fortran is critically important
  • Simple, compact syntax and semantics for the two primary use cases in user code - generic subprograms and generic derived types - is paramount

Current effort with Fortran 202Y worries me immensely as deviating from this, this poses tremendous risk to long-term viability of Fortran, I am convinced, unless there is urgent course correction.

What if take_reference is here replaced with:

interface my_type_wrapper
   module procedure new_wrapper
end interface

! ... contains ...

function new_wrapper(ref)
  type(my_type), target, intent(in) :: ref
  type(my_type_wrapper) :: new_wrapper
  new_wrapper % obj => ref
end function

Then one could correctly call the same way?

call needs_trait(my_type_wrapper(my_type_obj))

I am still sometimes confused when target is needed.

One more question: what if my_type_obj is a temporary object (function result). How long does it life last? In the pointer scenario, should it cause segfault when referenced by needs_trait or does it last until the end of the statement?

I have been avoiding pointers at all cost in Fortran, but seems I need to make friends with them again. :slight_smile:

Dominik

Only if my_type_obj is declared with the target attribute, and note that the compiler will not warn you and things may even “work” with some compilers.

It is only required to live until the new_wrapper function returns, in which case the pointer will be invalid.

Unfortunately the pointer solution to this problem has a lot of footguns. If you really wanted to avoid copies, you might be better off with this solution:

type, extends(my_trait) :: my_type_wrapper
  type(my_type), allocatable :: obj
contains
  procedure :: give_reference
  procedure :: take_reference
  procedure :: trait_proc
end type

contains

subroutine give_reference(self, ref)
  class(my_type_wrapper), intent(inout) :: self
  type(my_type), allocatable, intent(inout) :: ref

  call move_alloc(from=ref, to=self%obj)
end subroutine

subroutine take_reference(self, ref)
  class(my_type_wrapper), intent(inout) :: self
  type(my_type), allocatable, intent(inout) :: ref

  call move_alloc(to=ref, from=self%obj)
end subroutine

subroutine trait_proc(self)
  class(my_type_wrapper) :: self

  call self%obj%trait_proc()
end subroutine
type(my_type), allocatable :: my_type_obj
type(my_type_wrapper) :: wrapper

call wrapper%give_reference(my_type_obj)
call needs_trait(wrapper)
call wrapper%take_reference(my_type_obj)

Sometimes, the dangling pointer “works” because the stack memory it references has not yet been overwritten. That memory is available for use by the compiler, but just by chance, it has not yet been overwritten, so all the pointer values and metadata might still be intact. But if you change the code slightly, in some way that it might appear should not matter, or if you change some apparently unrelated compiler option, then the compiler might decide to use that memory for some other purpose, and then the dangling pointer appears to no longer “work”. This is one kind of “Heisenbug” that can be difficult to track down.

1 Like

I do not understand the purpose of target then. What does it prevent? What if my_type_obj is not a target? I understand that it has to do with aliasing (which, by the way, I have never seen “no aliasing” help in any optimization, but I could be wrong). But why would it lead to incorrect results in this case? What would be the consequence of passing non-target my_type_obj as target dummy argument?

It feels like a bad design decision that resources are freed before end of a statement. It forces use of many copies of data, which is awful for a high-performance language, where you might be dealing with huge objects containing many records. Sometimes it feels like you can’t write any good code in Fortran, because whenever you try to do so, you hit a roadblock.

It does not prevent anything. It allows local pointers to associate with the dummy argument.

Any pointer associated with the dummy argument is not valid after completion of the procedure unless the actual argument is a pointer or has the target attribute. This covers the requirement that a pointer cannot be associated with anything that does not have the target attribute.

That’s the implication/consequence, but the design decisions were really there to ensure that (barring the use of pointers) there is never memory that is not explicitly associated with a single variable that, once that variable goes out of scope, can be freed. So, once an expression has been evaluated, any intermediate values can be freed. I.e. in exp(1+1) + 1 once the exponential has been calculated, the memory storing the result of 1+1 can be freed.

When both the actual argument and the dummy argument have the target attribute, then the compiler is not allowed to make a copy. If the actual argument does not have the target attribute, then the compiler is allowed to make a copy.

The potential error then is when the actual argument does not have the target attribute, the compiler makes a copy, and then the subroutine makes a pointer assignment to that copy. Inside the subroutine, that pointer may be used. But if that pointer is returned to the caller, then the temporary copy may be destroyed, overwritten, returned to the stack, and so on, so the pointer is dangling. The language does not allow that dangling pointer to reference its former target. As I said previously, a reference through that pointer might appear to “work”, simply because the former target has not yet been overwritten, leading to Heisenbugs in your code.

Yes, exactly. That is why the language provides a way to avoid that situation.

I would say it the other way. The target attribute for the actual argument prevents making a copy of the data, it doesn’t force it. On the other hand, if you do not have the target attribute, then the compiler is also not forced to make a copy, rather it is allowed, and generally it will only do so if it thinks there is some kind of optimization advantage or if there are other reasons (e.g. putting parentheses around the actual argument, or having the value attribute on the dummy argument, and so on). This is another way that the code might appear to “work”, even when it has the nontarget error.

I don’t really understand this sentence in this context. The language provides a way to avoid the copy, so the programmer can write efficient code. What exactly is preventing the programmer from doing this?

Re: “I don’t really understand this sentence in this context.” well, it is somewhat disingenuous to state “I don’t really understand this.” There have been way too many discussions on comp.lang.fortran earlier and now on this forum and elsewhere that this reader has been witness to the underlying issues to make such a comment here.

A larger context is readily noticeable in the original post in this very thread and in some other recent threads by the OP @gronki on this forum. Which is that the OP is in effect to seeking to author Fortran code to manage data, either leading toward (a lot of) number-crunching (CPU/GPU intensive compute instructions) and/or after or during the computations to engage/communicate with the humans. This data processing is extremely important, always has been and always will be. However the powers-that-be with the Fortran language development have, on many occasions, paid inadequate attention to this aspect with the refrain Fortran shall focus on performance (e.g., that helps vendors sell more/better hardware), this aspect is placed more in the “creature comfort” or “syntactic sugar”, etc. category and thus gets low or no priority.

The net result is threads like the original post here where OP seeks to author a generic procedure (the example by OP is print_anything) that can operate on data encapsulated in any object that has certain “traits” but the OP finds it quite confusing to write code that gives OP and the consumers of such code “confidence” and “comfort” that it will work reliably and securely in a variety of circumstances.

This is a legitimate concern, one which is shared by many Fortranners even if they arrive at it from different angles and express in different ways.

And re: OP’s comment, “it feels like you can’t write any good code in Fortran,” please note it is crystal clear even those work on the language evolution and the standard itself for decades and decades, such as the authors of the Modern Fortran Explained series, experience the same issue. A perfect illustration is what the authors set out as “object-oriented list example” in their book series, often included in Appendix C of any given edition.

See this link. It has taken nearly a couple of decades for a working example toward what should be a relatively simple endeavor. But even now the code (in a file named oo.f90 per the auhors) ain’t exactly a poster-child for “good code”! (A separate issue might be the ftp link provided to customers of the book is now broken :-()

An endeavor regarding which the authors themselves admit is “A recurring problem is computing is the need to manipulate a dynamic data structure. This might be a simple homogeneous linked list like the one encountered in section , but often a more complex structure is required.” (emphasis mine.).

The bottom-line is the Fortran language is inadequately advanced for its practitioners to easily and conveniently work with a “more complex structure”. Practitioners who feel confused or frustrated or have sentiments similar to OP are many, their voices are either not being heard or are being ignored or worse yet suppressed when it comes to language design. Note it all starts with views like in this paper, “All proposals should be considered to start with minus 100 points.”

By “in this context” I mean specifically the question of what the target attribute does and why it is necessary to ensure that a temporary copy of the actual argument is not created by the compiler.

Yes, in other contexts I do agree that it is sometimes difficult, due to language limitations, to write simple, clear, code that performs well. I am not being obtuse or disingenuous.

Thank you. Honestly, I had no idea about such behavior. This clears why it is “more verbose” to do the solution by @everythingfunctional by pointers. Then the middle ground seems to be:

  • for “light” objects, use allocatables – be okay with copies, let compiler handle memory management. even if a copy
  • for objects that need complex reference web, use pointers. you need to carefully manage the lifetime of an object by yourself, and prevent “aliasing prevention trap” that could lead to dangling pointers
  • for “heavy” objects, use pointers – do memory management yourself, but since this is rather large data, you will not do many allocations/deallocations – this way you can pass the pointers to down the line, without worrying about copy being made, since pointers are targets by default.

I wrote such a small utility, inspired by zig, to defer freeing of a pointer (only for scalars, but I wrap everything in derived types anyway) – what is your opinion?

module defer_dealloc_m

    implicit none(type, external)
    private
    public :: defer_dealloc_t

    type :: pointer_wrapper_t
        class(*), pointer :: ptr => null()
    end type

    integer, parameter :: MAX_CAPACITY = 128

    type :: defer_dealloc_t
        type(pointer_wrapper_t) :: pool(MAX_CAPACITY)
    contains
        procedure :: hook
        final :: cleanup
    end type

contains

    subroutine hook(cleaner, tgt) 
        class(defer_dealloc_t) :: cleaner
        class(*), target, intent(in) :: tgt
        integer :: i
        do i = 1, size(cleaner % pool)
            if (.not. associated(cleaner % pool(i) % ptr)) then
                cleaner % pool(i) % ptr => tgt; return
            end if
        end do
        error stop "pool capacity exhausted"
    end subroutine
     
    subroutine cleanup(cleaner)
        type(defer_dealloc_t) :: cleaner
        integer :: i

        do i = 1, size(cleaner % pool)
            if (associated(cleaner % pool(i) % ptr)) deallocate(cleaner % pool(i) % ptr)
        end do
    end subroutine

end module

program test_foo

    use defer_dealloc_m
    implicit none(type, external)

    integer, pointer :: a, b

    block
        type(defer_dealloc_t) :: defer_dealloc

        allocate(a, source=10)
        allocate(b, source=30)

        ! now a should be auto-cleaned when exiting the scope
        call defer_dealloc % hook(a)

        print *, a, b
    end block

    ! illegal
    print *, a, b

end program

Looks like an interesting strategy. If you’re interested in safer use of pointers I’d recommend looking into GitHub - sourceryinstitute/smart-pointers: An object-oriented, extensible reference-counting utility for Fortran