5

次の単純なプログラムで、派生型の割り当て可能な配列メンバーでセグメンテーション違反が発生しました。このセグメンテーション違反は、1 台のマシン (openSUSE で Intel Fortran 14.0.3 を使用) でのみ発生し、別のマシン (Ubuntu で Intel Fortran 14.0.2 を使用) では発生しませんでした。また、プログラム内の整数パラメータの 1 つを変更すると、プログラムは正常に終了します。

誰でも問題を再現できますか?コードの何が問題なのか誰か教えてもらえますか?

以下に、3 つのソース コード ファイルを示します。

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.f90forall..このファイルのコンストラクトで セグメンテーション違反が発生します。

!*******************************************************************
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

以下は、上記のソース コードをコンパイルし、生成された実行可能ファイルを実行するためのシェル スクリプトです。

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

ulimit -s unlimited の先頭 ( の後#/bin/bash) に追加するとcompile_run.sh、セグメンテーション違反が防止されることがわかりました 。Fortran の割り当て可能な配列は、ヒープではなくスタックに格納されていますか?

4

1 に答える 1

3

これは、いくつかの多次元ループが問題を引き起こす同様の質問(2D 配列のセグメンテーション違反)の重複である可能性があります。forallリンクされた質問の OP は Intel フォーラムでこれを尋ねました ( ifort v 14.0 / 15.0 "-g" オプションにより segFault が発生します)。最新の返信は次のようになります。

回避策 #1 は、スタック サイズの制限を増やすことです。私はあなたのテストケースで成功しました: ulimit -s unlimited

回避策 2 は、次のように、FORALL の代わりに DO ループを使用することです。

また、リンクされた質問のケーシーのコメントによると、この問題はifort16では発生しないため、ifort14/15に固有のコンパイラの問題である可能性があります。


詳細情報(ほんの少しの実験):

ulimit -s 4000スタックサイズをifort14.0.1に制限して使うと私のパソコンでも同じ問題が再現され、-heap-arraysオプションで消えました。そのため、最初は size の自動配列または一時配列が存在する可能性があると考えていましn1 * n2 * n3たが、元のコードにはそのようなものはないようです...アタッチしても助けに-assume realloc_lhsもなり-check -warnませんでした。

そこで、doorを使用して同じ計算を実行するテスト プログラムを作成しましたforall

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

これは、パターン [4] のみが-heap-arrays添付されていない場合に失敗することを意味します。不思議なことに、配列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ループの特定のケース (オプションなしでも) でのみ問題が発生するようです (ただし、オプションはメッセージを表示しません)。参考までに、上記のパターンはすべて gfortran 4.8/5.2 および Oracle fortran 12.4 で動作します。-g-check -warn

于 2016-01-30T21:12:57.523 に答える