Ошибка сегментации с отложенными функциями и ключевым словом non_overridable

Я занимаюсь разработкой объектно-ориентированного кода Фортрана для численной оптимизации с полиморфизмом, поддерживаемым абстрактными типами. Поскольку это хорошая практика TDD, я пытаюсь написать все тесты оптимизации в абстрактном типе class(generic_optimizer)который затем должен запускаться каждым экземпляром класса, например, type(newton_raphson),

Все тесты по оптимизации содержат вызов call my_problem%solve(...), который определяется как deferred в абстрактном типе и, конечно, имеет различную реализацию в каждом производном типе.

Проблема заключается в следующем: если в каждом неабстрактном классе я определяю отложенную функцию как non_overridableЯ получаю ошибку сегментации, такую ​​как:

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 ()

После некоторых проб и ошибок я заметил, что могу избежать ошибки, если удаляю non_overridable декларация. В этом случае это не проблема, но я хотел обеспечить, чтобы два уровня полиморфизма были маловероятны для этого кода. Вместо этого я нарушал какие-либо требования стандарта?

Вот пример кода, который воспроизводит ошибку. Я тестировал его с gfortran 5.3.0 и 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

1 ответ

Чтобы сузить проблему, я удалил абстрактный код и элементы данных из кода OP, так что

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

С этим кодом Gfortran-6 дает

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

в то время как ifort-{14,16} и Oracle Fortran 12,5 дают

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

Я также попытался заменить функции подпрограммами (чтобы вывести, какие процедуры на самом деле вызываются):

    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

со всеми остальными частями остались прежними. Затем Гфортран-6 дает

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

в то время как ifort-{14,16} и Oracle Fortran 12,5 дают

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

Если я удалю non_overridable Исходя из приведенных выше кодов, gfortran дает тот же результат, что и другие компиляторы. Таким образом, это может быть конкретной проблемой для Gfortran + non_overridable (если приведенный выше код соответствует стандартам)...

(Причиной, по которой OP получил ошибку сегментации, может быть то, что gfortran получил доступ к deferred процедура в родительском типе (generic_type) имеющий нулевой указатель; если это так, история становится последовательной.)


редактировать

Такое же исключительное поведение gfortran происходит также, когда мы объявляем Type1 как abstract, В частности, если мы изменим определение Type1 как

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

и основная программа как

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

    call t2 % test( 2.0 )
end program

мы получаем

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

Если мы в дальнейшем сделаем square() в Type1 будет deferred (т. е. реализации не дано) и, таким образом, сделать код почти эквивалентным случаю OP,

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

тогда ifort-16 и Oracle-12.5 дают 4.0 с call t2 % test( 2.0 )в то время как gfortran-6 приводит к ошибке сегментации. Действительно, если мы скомпилируем как

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

мы получаем

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.

Так что в целом, кажется, что обязательное имя square() в Type1 (который не имеет реализации) ошибочно вызывается gfortran (возможно, с нулевым указателем). И что более важно, если мы уроним non_overridable из определения типа 2, gfortran также дает 4.0 (без ошибки сегментации).

Другие вопросы по тегам