首页 文章

用户定义类型的Fortran可分配阵列成员

提问于
浏览
3

在以下简单程序中,我在派生类型的可分配数组成员处遇到分段错误 . 此分段故障仅在一台计算机上发生(在openSUSE上使用英特尔Fortran 14.0.3),但在我尝试的其他计算机上(在Ubuntu上使用英特尔Fortran 14.0.2)则不会发生 . 此外,如果我更改程序中的一个整数参数,程序将正常结束 .

有人可以重现这个问题吗?谁能告诉我代码有什么问题?

以下是三个源代码文件 .

main_dbg.f90 ..是否发生分段错误取决于此文件中 n1n2 的值 .

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

Edit 2016-01-30

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

1 回答

  • 2

    这可能是类似问题(Segmentation fault on 2D array)的可能重复,其中一些多维 forall 循环导致问题 . 联系问题的OP在英特尔论坛(ifort v 14.0 / 15.0 "-g" option causes segFault)中提到了这个问题,最新回复如下:

    解决方法#1是增加堆栈大小限制 . 我使用测试用例成功:ulimit -s unlimited解决方法#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
    

    其中pattern [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 选项没有给出消息) . 仅供参考,以上所有模式均适用于gfortran 4.8 / 5.2和Oracle fortran 12.4 .

相关问题