I am stuck with segmentation fault at an allocatable array memberof a derived type in the following simple program. This segmentation fault occurs only on one machine (with Intel Fortran 14.0.3 on openSUSE) but not on the other machine (with Intel Fortran 14.0.2 on Ubuntu) that I tried. Also, if I change one of the integer parameters in the program, the program ends normally.
Could anybody reproduce the prolem? Could anybody tell me what is wrong with the code?
Below are the three source code files.
main_dbg.f90
.. whether the segmentation fault occurs or not depends on the values of n1
and n2
in this file.
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
.. segmentation fault occurs at the forall
construct in this file.
!*******************************************************************
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
Below is a shell script to compile the source codes above and run the generated executable.
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"
The standard output looked as following.
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
I found that adding
ulimit -s unlimited
at the beginning (after #/bin/bash
) of compile_run.sh
prevents the segmentation fault. Are the allocatable arrays in fortran stored in stack, not in heap?