Fortran 可分配数组是用户定义类型的成员

5
我在以下简单程序的派生类型的可分配数组成员中遇到了分段错误问题。这个分段错误只发生在一台机器上(使用Intel Fortran 14.0.3和openSUSE),但我尝试过的另一台机器(使用Intel Fortran 14.0.2和Ubuntu)上没有出现。此外,如果我更改程序中的一个整数参数,程序将正常结束。
有人能够复制这个问题吗?有人能告诉我代码哪里出错了吗?
下面是三个源代码文件。
main_dbg.f90 ..是否出现分段错误取决于此文件中n1和n2的值。
PROGRAM dbg
  USE tktype
  USE mymodule, ONLY : MyClass, MyClass_constructor
  IMPLICIT NONE

  INTEGER(I4B)                :: n1,n2,n3
  TYPE(MyClass)               :: o_MyClass

  n1=23
  n2=32
  ! .. this does not work.
  ! n2=31 
  ! .. this works.
  n3 = n1*n2
  write(*,'(1X,A,I10)') 'n1=', n1
  write(*,'(1X,A,I10)') 'n2=', n2
  write(*,'(1X,A,I10)') 'n3=', n3

  o_MyClass = MyClass_constructor(n1, n2, n3) 

  call o_MyClass%destructor()
  write(*,*) '***************************'
  write(*,*) '   Normal End :)           '
  write(*,*) '***************************'

END PROGRAM dbg

strange.f90 ..在这个文件中,forall结构出现了分段错误。

!*******************************************************************
MODULE mymodule
!*******************************************************************
  USE tktype
  IMPLICIT NONE
  PRIVATE

  PUBLIC MyClass
  PUBLIC MyClass_constructor

  TYPE :: MyClass
     PRIVATE
     REAL(DP),     DIMENSION(:),     ALLOCATABLE :: arrA
     COMPLEX(DPC), DIMENSION(:,:,:), ALLOCATABLE :: arrB
   CONTAINS
     PROCEDURE :: destructor
  END TYPE MyClass

! ================================================================
CONTAINS
! ================================================================

  ! ****************************************************************
  FUNCTION MyClass_constructor(n1, n2, n3) RESULT(this)
  ! ****************************************************************
    TYPE(MyClass)                :: this
    INTEGER(I4B),    INTENT(IN)  :: n1, n2, n3
    ! local variables
    INTEGER(I4B) :: j1, j2, j3

    write(*,'(1X,A)') 'entered constructor..'

    allocate(this%arrA(n2))
    allocate(this%arrB(n1, n2, n3))

    this%arrA = 1.0_dp

    write(*,*) 'size(this%arrB,1) =', size(this%arrB,1)
    write(*,*) 'n1                = ', n1
    write(*,*) 'size(this%arrB,2) =', size(this%arrB,2)
    write(*,*) 'n2                = ', n2
    write(*,*) 'size(this%arrB,3) =', size(this%arrB,3)
    write(*,*) 'n3                = ', n3

    forall(j1=1:n1, j2=1:n2, j3=1:n3)
       this%arrB(j1,j2,j3)  = this%arrA(j2) 
    end forall

    write(*,'(1X,A)') '..leaving constructor'

  END FUNCTION MyClass_constructor


  ! ****************************************************************
  SUBROUTINE destructor(this)
  ! ****************************************************************
    CLASS(MyClass),             INTENT(INOUT) :: this

    deallocate(this%arrA)
    deallocate(this%arrB)

  END SUBROUTINE destructor

END MODULE mymodule

tktype.f90

! ********************************************************************
MODULE tktype
! ********************************************************************
!   module tktype is an extraction of module nrtype in Numerical Recipes in 
!   Fortran 90.
! ********************************************************************
  !   Symbolic names for kind types of 4-, 2-, and 1-byte integers:
  INTEGER, PARAMETER :: I4B = SELECTED_INT_KIND(9)
  INTEGER, PARAMETER :: I2B = SELECTED_INT_KIND(4)
  INTEGER, PARAMETER :: I1B = SELECTED_INT_KIND(2)
  !   Symbolic names for kind types of single- and double-precision reals:
  INTEGER, PARAMETER :: SP = KIND(1.0)
  INTEGER, PARAMETER :: DP = KIND(1.0D0)
  !   Symbolic names for kind types of single- and double-precision complex:
  INTEGER, PARAMETER :: SPC = KIND((1.0,1.0))
  INTEGER, PARAMETER :: DPC = KIND((1.0D0,1.0D0))
  !   Symbolic name for kind type of default logical:
  INTEGER, PARAMETER :: LGT = KIND(.true.)
END MODULE tktype

以下是一个shell脚本,用于编译上面的源代码并运行生成的可执行文件。
compile_run.sh
#!/bin/bash

ifort -v 
echo "compiling.."
ifort -o tktype.o -c -check -g -stand f03 tktype.f90
ifort -o strange.o -c -check -g -stand f03 strange.f90
ifort -o main_dbg.o -c -check -g -stand f03 main_dbg.f90
ifort -o baabaa strange.o tktype.o main_dbg.o
echo "..done"
echo "running.."
./baabaa
echo "..done"

标准输出如下所示。
ifort version 14.0.3
compiling..
..done
running..
 n1=        23
 n2=        32
 n3=       736
 entered constructor..
 size(this%arrB,1) =          23
 n1                =           23
 size(this%arrB,2) =          32
 n2                =           32
 size(this%arrB,3) =         736
 n3                =          736
./compile_run.sh: line 11: 17096 Segmentation fault      ./baabaa
..done

编辑于2016-01-30

我发现在compile_run.sh的开头(在#/bin/bash之后)添加ulimit -s unlimited可以防止分段错误。 Fortran中的可分配数组是存储在堆栈中而不是堆中吗?

1个回答

3
这可能是类似问题(2D数组出现分段错误)的重复。在该问题中,一些多维forall循环导致了问题。链接问题的OP在Intel论坛上提出了这个问题(ifort v 14.0 / 15.0“-g”选项导致segFault),最新的回答如下:

解决方法#1是增加堆栈大小限制。使用ulimit-s无限可以成功运行您的测试用例。

解决方法#2是使用DO循环代替FORALL,如下所示:

此外,根据链接问题中casey的评论,这个问题在ifort16中不会发生,因此我猜它可能是ifort14/15特有的编译器问题。

更多信息(只是一些实验):

通过将堆栈大小限制为ulimit -s 4000并使用ifort14.0.1,在我的计算机上重现了相同的问题,并且使用-heap-arrays选项后该问题消失了。因此,我最初认为可能存在一些自动数组或大小为n1 * n2 * n3的数组临时变量,但在原始代码中似乎没有这样的东西...附加-assume realloc_lhs-check -warn也没有帮助。

所以我编写了一个测试程序,使用doforall执行相同的计算:

program main
    implicit none
    integer, parameter :: dp  = KIND(1.0D0)
    integer, parameter :: dpc = KIND((1.0D0,1.0D0))
    type Mytype
        real(dp),     allocatable :: A(:)
        complex(dpc), allocatable :: B(:,:,:)
    endtype
    type(Mytype) :: t
    integer :: n1, n2, n3, j1, j2, j3

    n1 = 23
    n2 = 32
    n3 = n1 * n2   !! = 736

    allocate( t% A( n2 ), t% B( n1, n2, n3 ) )

    t% A(:) = 1.0_dp

    print *, "[1] do (3-dim)"
    do j3 = 1, n3
    do j2 = 1, n2
    do j1 = 1, n1
        t% B( j1, j2, j3 ) = t% A( j2 ) 
    enddo
    enddo
    enddo

    print *, "[2] do (1-dim)"
    do j2 = 1, n2
        t% B( :, j2, : ) = t% A( j2 ) 
    enddo

    print *, "[3] forall (1-dim)"
    forall( j2 = 1:n2 )
        t% B( :, j2, : ) = t% A( j2 ) 
    end forall

    print *, "[4] forall (3-dim)"   ! <-- taken from the original code
    forall( j1 = 1:n1, j2 = 1:n2, j3 = 1:n3 )
        t% B( j1, j2, j3 ) = t% A( j2 )
    end forall

    print *, "all passed."
end program

其中模式[4]对应于OP使用的模式。限制堆栈大小并编译不带选项(ulimit -s 4000; ifort test.f90)会产生以下输出。

 [1] do (3-dim)
 [2] do (1-dim)
 [3] forall (1-dim)
 [4] forall (3-dim)
Segmentation fault

这意味着当未使用-heap-arrays选项时,只有模式[4]会失败。奇怪的是,当数组AB在派生类型之外声明时,问题就消失了,即以下程序可在没有任何选项的情况下正常工作。
program main
    implicit none
    integer, parameter :: dp  = KIND(1.0D0)
    integer, parameter :: dpc = KIND((1.0D0,1.0D0))
    real(dp),     allocatable :: A(:)
    complex(dpc), allocatable :: B(:,:,:)
    integer :: n1, n2, n3, j1, j2, j3

    n1 = 23
    n2 = 32
    n3 = n1 * n2   !! = 736

    allocate( A( n2 ), B( n1, n2, n3 ) )

    A(:) = 1.0_dp

    print *, "[1] do (3-dim)"
    do j3 = 1, n3
    do j2 = 1, n2
    do j1 = 1, n1
        B( j1, j2, j3 ) = A( j2 ) 
    enddo
    enddo
    enddo

    print *, "[2] do (1-dim)"
    do j2 = 1, n2
        B( :, j2, : ) = A( j2 ) 
    enddo

    print *, "[3] forall (1-dim)"
    forall( j2 = 1:n2 )
        B( :, j2, : ) = A( j2 ) 
    end forall

    print *, "[4] forall (3-dim)"
    forall( j1 = 1:n1, j2 = 1:n2, j3 = 1:n3 )
        B( j1, j2, j3 ) = A( j2 )
    end forall

    print *, "all passed."
end program

看起来问题只发生在某些特定情况下的多维 forall 循环中(即使没有使用 -g 选项),这可能是因为使用堆栈上的内部临时数组(尽管 -check -warn 选项没有消息)。FYI,所有上述模式都适用于 gfortran 4.8/5.2 和 Oracle fortran 12.4。

1
warn 是否产生了关于临时数组创建的警告? - Vladimir F Героям слава
1
没有来自-check-warn等的消息...这可能是与链接问题相同的问题。 - roygvib
@roygvib 感谢您尝试重现问题并进行更多尝试,以及指向相关帖子。很高兴知道这是一个已知的问题,有一个已知的解决方法,并在更新版本的ifort中得到修复。我现在感觉更安全了。 - norio
@norio 嗨,没问题,很高兴能帮忙! - roygvib

网页内容由stack overflow 提供, 点击上面的
可以查看英文原文,
原文链接