6

I am developing an object-oriented Fortran code for numerical optimization with polymorphism supported by abstract types. Because it is a good TDD practice, I'm trying to write all optimization tests in the abstract type class(generic_optimizer), which then should be run by each instantiated class, e.g., by type(newton_raphson).

All the optimization tests feature a call to call my_problem%solve(...), which is defined as deferred in the abstract type and of course features a different implementation in each derived type.

The issue is: if in each non-abstract class I define the deferred function as non_overridable, I get segmentation fault such as:

Program received signal SIGSEGV, Segmentation fault.
0x0000000000000000 in ?? ()

(gdb) where
#0  0x0000000000000000 in ?? ()
#1  0x0000000000913efe in __newton_raphson_MOD_nr_solve ()
#2  0x00000000008cfafa in MAIN__ ()
#3  0x00000000008cfb2b in main ()
#4  0x0000003a3c81ed5d in __libc_start_main () from /lib64/libc.so.6
#5  0x00000000004048f9 in _start ()

After some trial-and-error, I've noticed that I can avoid the error if I remove the non_overridable declaration. In this case it is not an issue, but I wanted to enforce that since two levels of polymorphism are unlikely for this code. Was I violating any requirements from the standard, instead?

Here is a sample code that reproduces the error. I've been testing it with gfortran 5.3.0 and 6.1.0.

module generic_type_module
    implicit none
    private

    type, abstract, public :: generic_type
        real(8) :: some_data
        contains
        procedure (sqrt_interface), deferred :: square_root
        procedure, non_overridable           :: sqrt_test
    end type generic_type

    abstract interface
       real(8) function sqrt_interface(this,x) result(sqrtx)
          import generic_type
          class(generic_type), intent(in) :: this
          real(8), intent(in) :: x
       end function sqrt_interface
    end interface

    contains

    subroutine sqrt_test(this,x)
        class(generic_type), intent(in) :: this
        real(8), intent(in) :: x
        print *, 'sqrt(',x,') = ',this%square_root(x)
    end subroutine sqrt_test

end module generic_type_module

module actual_types_module
    use generic_type_module
    implicit none
    private

    type, public, extends(generic_type) :: crashing
       real(8) :: other_data
       contains
       procedure, non_overridable :: square_root => crashing_square_root
    end type crashing
    type, public, extends(generic_type) :: working
       real(8) :: other_data
       contains
       procedure :: square_root => working_square_root
    end type working

    contains

    real(8) function crashing_square_root(this,x) result(sqrtx)
       class(crashing), intent(in) :: this
       real(8), intent(in) :: x
       sqrtx = sqrt(x)
    end function crashing_square_root
    real(8) function working_square_root(this,x) result(sqrtx)
       class(working), intent(in) :: this
       real(8), intent(in) :: x
       sqrtx = sqrt(x)
    end function working_square_root

end module actual_types_module

program deferred_test
    use actual_types_module
    implicit none
    type(crashing) :: crashes
    type(working)  :: works

    call works%sqrt_test(2.0_8)
    call crashes%sqrt_test(2.0_8)

end program
Federico Perini
  • 1,414
  • 8
  • 13

1 Answers1

1

To narrow down the problem, I removed the abstract attribute and data members from the OP's code such that

module types
    implicit none

    type :: Type1
    contains
        procedure :: test
        procedure :: square => Type1_square
    endtype

    type, extends(Type1) :: Type2
    contains
       procedure, non_overridable :: square => Type2_square
    endtype

contains

    subroutine test( this, x )
        class(Type1) :: this
        real :: x
        print *, "square(", x, ") = ",this % square( x )
    end subroutine

    function Type1_square( this, x ) result( y )
       class(Type1) :: this
       real :: x, y
       y = -100      ! dummy
    end function

    function Type2_square( this, x ) result( y )
       class(Type2) :: this
       real :: x, y
       y = x**2
    end function

end module

program main
    use types
    implicit none
    type(Type1) :: t1
    type(Type2) :: t2

    call t1 % test( 2.0 )
    call t2 % test( 2.0 )
end program

With this code, gfortran-6 gives

square(   2.00000000     ) =   -100.000000
square(   2.00000000     ) =   -100.000000

while ifort-{14,16} and Oracle fortran 12.5 give

square(   2.000000     ) =   -100.0000    
square(   2.000000     ) =    4.000000

I also tried replacing the functions with subroutines (to print which routines are actually called):

    subroutine test( this, x )
        class(Type1) :: this
        real :: x, y
        call this % square( x, y )
        print *, "square(", x, ") = ", y
    end subroutine

    subroutine Type1_square( this, x, y )
        class(Type1) :: this
        real :: x, y
        print *, "Type1_square:"
        y = -100      ! dummy
    end subroutine

    subroutine Type2_square( this, x, y )
        class(Type2) :: this
        real :: x, y
        print *, "Type2_square:"
        y = x**2
    end subroutine

with all the other parts kept the same. Then, gfortran-6 gives

Type1_square:
square(   2.00000000     ) =   -100.000000    
Type1_square:
square(   2.00000000     ) =   -100.000000

while ifort-{14,16} and Oracle fortran 12.5 give

Type1_square:
square(   2.000000     ) =   -100.0000    
Type2_square:
square(   2.000000     ) =    4.000000 

If I remove non_overridable from the above codes, gfortran gives the same result as the other compilers. So, this may be a specific issue to gfortran + non_overridable (if the above code is standard-conforming)...

(The reason why OP got segmentation fault may be that gfortran accessed the deferred procedure in the parent type (generic_type) having null pointer; if this is the case, the story becomes consistent.)


Edit

The same exceptional behavior of gfortran occurs also when we declare Type1 as abstract. Specifically, if we change the definition of Type1 as

    type, abstract :: Type1    ! now an abstract type (cannot be instantiated)
    contains
        procedure :: test
        procedure :: square => Type1_square
    endtype

and the main program as

program main
    use types
    implicit none
    type(Type2) :: t2

    call t2 % test( 2.0 )
end program

we get

ifort-16    : square(   2.000000     ) =    4.000000    
oracle-12.5 : square( 2.0 ) =  4.0
gfortran-6  : square(   2.00000000     ) =   -100.000000  

If we further make square() in Type1 to be deferred (i.e., no implementation given) and so make the code almost equivalent to the OP's case,

type, abstract :: Type1  ! now an abstract type (cannot be instantiated)
contains
    procedure :: test
    procedure(Type1_square), deferred :: square  ! has no implementation yet
endtype

abstract interface
    function Type1_square( this, x ) result( y )
        import
        class(Type1) :: this
        real :: x, y
    end function
end interface

then ifort-16 and Oracle-12.5 gives 4.0 with call t2 % test( 2.0 ), while gfortran-6 results in segmentation fault. Indeed, if we compile as

$ gfortran -fsanitize=address test.f90   # on Linux x86_64

we get

ASAN:SIGSEGV    (<-- or "ASAN:DEADLYSIGNAL" on OSX 10.9)
=================================================================
==22045==ERROR: AddressSanitizer: SEGV on unknown address 0x000000000000 
                (pc 0x000000000000 bp 0x7fff1d23ecd0 sp 0x7fff1d23eac8 T0)
==22045==Hint: pc points to the zero page.

So overall, it seems as if the binding name square() in Type1 (which has no implementation) is called erroneously by gfortran (possibly with null pointer). And more importantly, if we drop non_overridable from the definition of Type2, gfortran also gives 4.0 (with no segmentation fault).

roygvib
  • 7,218
  • 2
  • 19
  • 36
  • very interesting @roygvib, thanks! Looks like gfortran assumes the parent routine is called even when non_overridable is specified from an extended type, then. Reading "Modern Fortran Explained" by Metcalf, Reid, Cohen, I found: - If the `non_overridable` attribute appears, that type-bound procedure cannot be overridden during type extension; - `non_overridable` is incompatible with `deferred`, since that requires the type-bound procedure to be overridden; - Overriding a type-bound procedure is not permitted if the inherited one has the `non_overridable` attribute. – Federico Perini Nov 11 '16 at 12:54
  • Hi, I have considered your original code again, but it still looks to me that your code is correct... My understanding is that, regardless of whether we attach `non_overridable` to a type-bound procedure of Type2, its implementation (i.e., Type2_square) should be called from an instance of Type2. (My understanding is that `non_overridable` prohibits square() to be overwritten by a child type of Type2 (say Type3), so it has no effect on the behavior of Type2 itself.) – roygvib Nov 13 '16 at 22:58
  • As for the sentence "`non_overridable` is incompatible with `deferred`" in Chap.14.6.1 of "Modern Fortran Explained" (I bought the Kindle version :), I guess this means that we cannot write something like `procedure(...), deferred, non_overridable :: square`, i.e., we cannot specify the two keywords at the same time. On the other hand, it is probably OK to use `procedure(...), deferred :: square` for Type1 and `procedure, non_overridable :: square => Type2_square` for Type2 (probably...). – roygvib Nov 13 '16 at 23:03
  • So, if the above interpretation seems reasonable, I would really appreciate if you open a ticket on GCC bugzilla (I guess +4 upvotes on your question implies "go ahead"). It may be also very useful to ask opinions in [comp.lang.fortran](https://groups.google.com/forum/#!forum/comp.lang.fortran), because there are many such threads (whether some code is standard-conforming, or a bug of codes or compilers). – roygvib Nov 13 '16 at 23:12
  • 1
    thanks @roygvib, I've opened a ticket on GCC Bugzilla. Cheers! – Federico Perini Nov 21 '16 at 08:17