Verifying the dynamic status of actual argument

Hi there, this is my first post here so I apologize in advance if my question is not appropriately formatted for this forum. In particular, I wasn’t sure about the title for this post.

I have the following question. Suppose I have an abstract derived type and a subroutine with a polymorphic dummy argument of this type. Is there a way for me to verify at run time if the actual argument is an object belonging to a proper extension of this abstract type?

For instance, consider the following.

module mytype_mod
  implicit none

  type, abstract :: mytype_t
    contains
      procedure(mytype_binding), pass,  deferred :: do_stuff
  end type
 
  abstract interface
    subroutine mytype_binding ( this )
      import :: mytype_t
      implicit none
      class(mytype_t), intent(in) :: this
    end subroutine
  end interface

  contains

  subroutine mysub ( myobj )
    implicit none
    class(mytype_t), intent(in) :: myobj
  
    call myobj%do_stuff()

  end subroutine

end module

program test
  use mytype_mod
  implicit none

  class(mytype_t), allocatable :: myvar
 
  ! A segmentation fault is about to occur.
  call mysub ( myvar )

end program

I guess I should also ask if there is in general a way to verify if the actual argument isn’t an unallocated variable but I guess the answer for that is a big no.

Thanks in advance.

1 Like

If the argument is declared optional in the procedure, you can use the fact that An unallocated variable passed as an argument is not PRESENT.

If the argument is not optional and not allocatable, then it is invalid to pass an unallocated variable as an argument, hence your segfault. Also, it is not valid to pass an actual argument whose declared type is not an extension of the declared type of the dummy argument, which would be caught at compile time.

TLDR, if you declare an argument as class(thing), intent(in) :: arg, you’re guaranteed that the actual argument will be an extension of thing.

In principle you can check if a child type belongs to a particular type hierarchy using the two intrinsic functions:

  • extends_type_of(a,mold) - Query dynamic type for extension.
  • same_type_as(a,b) - Query dynamic types for equality.

The functions return a logical value. Circumstances where you’d use them are rare.

1 Like

Thank you all for your time.

I’m worried that code like the one I showed is too easy to break with the kind of programming mistake like mine above. Considering I can declare a variable of abstract type so long it has either the pointer or allocatable attributes, would you say it is advisable to always declare polymorphic dummy arguments as either optional, pointer or allocatable, specially if the type is abstract?

Thank you again.

No. I’d say it’s advisable not to pass unallocated arguments to procedures unless their purpose is to allocate them. Adding optional, pointer, or allocatable expresses something other than your intention, and lets the bug propagate to a place other than where the actual error in logic occurs.

'Aight. Thanks!

@Noob welcome to the forum! I recommend to always develop in “Debug” mode. For GFortran you can use:

$ gfortran -fcheck=all -g a.f90

Then your code above gives:

$ ./a.out                      
At line 36 of file a.f90
Fortran runtime error: Allocatable actual argument 'myvar' is not allocated

Error termination. Backtrace:
#0  0x104a53bd3 in ???
#1  0x104a547a7 in ???
#2  0x104a54be3 in ???
#3  0x104697dc3 in test
	at /tmp/b/a.f90:36
#4  0x104697e0f in main
	at /tmp/b/a.f90:30

The stacktrace does not resolve for me on macOS (that’s a GFortran limitation) but it gives you a very nice error message with what happened and line numbers in the stack.

The ideal is that in Debug mode your code almost cannot segfault, you will always get some nice runtime error message. Most Fortran compilers do not reach the ideal, but they are close, as you can see above.

The unresolved symbols typically come from shared (system) libraries. See: debugging - Why gfortran does not give symbolic backtrace? - Stack Overflow

If I link libgfortran statically, the first few unresolved symbols dissappear:

$ gfortran -fcheck=all -g -static-libgfortran -fbacktrace backtrace.f90 
$ ./a.out
At line 36 of file backtrace.f90
Fortran runtime error: Allocatable actual argument 'myvar' is not allocated

Error termination. Backtrace:
#0  0x10ac65fce in test
	at /tmp/backtrace.f90:36
#1  0x10ac6601f in main
	at /tmp/backtrace.f90:30
2 Likes

The stacktraces work correctly on Linux for me, but not on macOS. I installed GFortran using Spack.