Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28632 Discussions

forrtl: severe (174): SIGSEGV, segmentation fault occurred

harshal05
Beginner
1,203 Views

Dear Team, 

 

I am able to compile the calc_MAMJ_sedi.f90 code but the executable is showing the below error 

 

Threshold Value:30 Category=hw
forrtl: severe (174): SIGSEGV, segmentation fault occurred
Image PC Routine Line Source
calc_MAMJ_sedi 000000000040C0F4 Unknown Unknown Unknown
libpthread-2.22.s 00002ADB6853FB20 Unknown Unknown Unknown
calc_MAMJ_sedi 00000000004042C9 MAIN__ 108 calc_MAMJ_sedi.f90
calc_MAMJ_sedi 0000000000402A9E Unknown Unknown Unknown
libc-2.22.so 00002ADB689706D5 __libc_start_main Unknown Unknown
calc_MAMJ_sedi 00000000004029A9 Unknown Unknown Unknown

 

A command used for compilation :  ifort -O2 -traceback calc_MAMJ_sedi.f90 -o calc_MAMJ_sedi

 

The source code of calc_MAMJ_sedi.f90,

------------------------------------------------

PROGRAM SEDI_skill

IMPLICIT NONE

! THE NUMBER OF VARIABLES(M) AND THE NUMBER OF OBSERVAIONS(N), M X N

LOGICAL :: OK

logical :: iret,system
CHARACTER (LEN = 2) :: ch2
INTEGER,parameter :: nlon=61,nlat=61
INTEGER,parameter :: ndaym=7,ninit=15,npent=4,yr_st=2003,nyr=15
INTEGER,parameter :: m=21+2,nprcntl=2,nth=6
INTEGER :: i,ic,j,n,ii,jj,k,ik,kk,nt,imem,day_skip,ipent
CHARACTER (LEN=200) :: file1,file2,flin,pathmax,pathmin
INTEGER :: init,iyr,irec,i1,i2,j1,j2,k1,k2,day_st1(ninit),day_st,tst,ten
INTEGER ::ip,th(nth),ith
!-------------------------------------------------------------------------------------
REAL, ALLOCATABLE :: xdatmax(:,:,:,:,:)
REAL, ALLOCATABLE :: ydatmax(:,:,:,:,:)
REAL :: UNDEF,am,rchv,ofrq,ffrq,ht,fa,ta,tb,tc,td,ss,hval
REAL :: sindex(nlon,nlat)
CHARACTER :: cyr*4,cdate*4,cpent*1,cth*2,cprcntl*2(nprcntl)
CHARACTER :: cdate1*4(ninit),ccat*5
!-------------------------------------------------------------------------------------

data cdate1 /'0301', '0308', '0315', '0322', '0329', &
'0405', '0412', '0419', '0426', '0504', &
'0511', '0518', '0525', '0601', '0608'/

!data day_st1 / 60 ,67 ,74 ,81 ,88 , &
! 95 ,102 ,109 ,116 ,124 , &
! 131 ,138 ,145 ,152 ,159/
data day_st1 / 61 ,68 ,75 ,82 ,89 , &
96 ,103 ,110 ,117 ,125 , &
132 ,139 ,146 ,153 ,160/

data cprcntl/'95','99'/
data th/30,40,50,60,70,80/

!m= 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23
!p=clim,sd,1,5,10,15,20,25,30,35,40,45,50,55,60,65,70,75,80,85,90,95,99/
!-------------------------------------------------------------------------------------
undef=99.9
day_skip=59 !till 28th Feb
!--------------------------------------------------------------------------------------------------------
ALLOCATE(ydatmax(1:nlon,1:nlat,1:ndaym,1:ninit,1:nyr))
ALLOCATE(xdatmax(1:nlon,1:nlat,1:ndaym,1:ninit,1:nyr))
!--------------------------------

iret=system('mkdir -p data/')

do ith=1,nth
write(cth,'(I2.2)')th(ith)

do ip=1,nprcntl
if(ip==1)then
ccat='hw'
hval=3.0
endif
if(ip==2)then
ccat='shw'
hval=4.0
endif
write(*,*)'Threshold Value:',cth, ' Category=',ccat


do ipent=1,npent
write(cpent,'(I1.1)')ipent
if(ipent==1)tst=1
if(ipent==2)tst=8
if(ipent==3)tst=15
if(ipent==4)tst=22
ten=tst+6
!--------------------------------
DO init=1,ninit
cdate=cdate1(init)
day_st=day_st1(init)
DO iyr=1,nyr
write(cyr,'(i4.4)')yr_st+iyr-1
file1='/home/ERPAS/imdoper/Backup_Aditya/ht_wave/for_weekly_run/obs/heatwave_calc/new_criteria/ERPv2/ht_wv_days/'//cyr//'/MAMJ_hv_'//cyr//'.bin'
open (11,file=file1,form='unformatted',access='direct',recl=nlon*nlat)
ic=0
do k=day_st-day_skip+tst,day_st-day_skip+ten
! do k=day_st-day_skip,day_st-day_skip+6
ic=ic+1
read(11,rec=k)ydatmax(:,:,ic,init,iyr)
enddo
close(11)
file1='/home/ERPAS/imdoper/Backup_Aditya/ht_wave/for_weekly_run/model/new_criteria/ERPv2/ht_wv_days/'//cdate//'/ht_wv_'//cprcntl(ip)//'_'//cyr//'.bin'
open (11,file=file1,form='unformatted',access='direct',recl=nlon*nlat)
ic=0
do k=tst,ten
ic=ic+1
read(11,rec=k)xdatmax(:,:,ic,init,iyr)
enddo
close(11)
ENDDO
ENDDO
!--------------------------------------------------------------------------------------------------------
DO j=1,nlat
DO i=1,nlon
ta=0.0;tb=0.0;tc=0.0;td=0.0

DO kk=tst,ten
DO init=1,ninit
DO iyr=1,nyr
if(ydatmax(i,j,kk,init,iyr).ne.undef) then

if(ydatmax(i,j,kk,init,iyr)==hval) then
ofrq=1.0
else
ofrq=0.0
endif
if(xdatmax(i,j,kk,init,iyr).gt.float(th(ith))) then
ffrq=1.0
else
ffrq=0.0
endif
!
!obs ------>
! | yes no
! | ta tb
!fct| tc td
! \/
!
if(ofrq.eq.1.0)then
if(ffrq.eq.1.0) then
ta=ta+1.0
else
tc=tc+1.0
endif
else
if(ffrq.eq.1.0) then
tb=tb+1.0
else
td=td+1.0
endif
endif

endif
ENDDO ! nyr
ENDDO ! ninit
ENDDO ! kk
if(ta+tc.eq.0.0.or.tb+td.eq.0.0) then
ss=undef
else
HT=ta/(ta+tc)
FA=tb/(tb+td)
call sedi(ht,fa,undef,ss)
endif
sindex(i,j)=ss
ENDDO ! nlon
ENDDO ! nlat

file1='data/sedi_MAMJ_W'//cpent//'_'//cth//'_'//trim(ccat)//'.bin'
open (11,file=file1,form='unformatted',access='direct',recl=nlon*nlat)
write(11,rec=1)sindex
close(11)

enddo ! npent

enddo ! nprcntl

!deallocate (xdatmax, ydatmax)
enddo ! nth

STOP
contains
!----------------------------------------------------------------------------------
SUBROUTINE sedi(h,f,undef,ss)
IMPLICIT NONE
real,INTENT(IN) :: h,f,undef
real,INTENT(out) :: ss
real :: hm1,fm1,an,ad
!
if(h.eq.undef.or.f.eq.undef) then
ss=undef
return
endif
hm1=1.0-h
fm1=1.0-f
an=(f*hm1)/(fm1*h)
ad=f*fm1*h*hm1
if(an.gt.0.0.and.ad.gt.0.0) then
ss=log(an)/log(ad)
else
ss=undef
endif
RETURN
END SUBROUTINE sedi

END PROGRAM

------------------------------------------------------------

 

Can you suggest me what approach I should use as I have used multiple optimization flag (O0-3) but not working. 

Tested with Fortran compiler,

intel/16.0.3.210

intel/17.0.4.196

intel/17.0.5.239

intel/18.0.5.274

intel/19.0.1.144

0 Kudos
6 Replies
Arjen_Markus
Honored Contributor I
1,193 Views

Usually, with this type of errors: try building with debug options on and with array bound checking and possibly other diagnostics options as well. The command-line options needed can be found in the online help or via "ifort -help".

Also: if you post code, then it is best to use the "</>" button in the expanded toolbar. That way the formatting of code is preserved.

0 Kudos
harshal05
Beginner
1,180 Views

Dear, 

Thanks for your reply.

I tried with the debug flag -g and array boundary check but it is creating any difference.  It is showing the same error  using traceback it redirects to line number 108 which contains an "if statement" and if I am changing the optimization levels it shows for another "if statement". 

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,158 Views

A potential problem with your code is your choice of value for undef at 99.9. You should be aware that with floating point numbers, that fractional values often are approximations. In particular, fractions that are multiples of 0.1 would require an infinite number of bits, and yet would not be exact. This may be a case that one version of the compiler rounds up and the other version of the compiler rounds down. Therefore your (expression .eq. undef) will fail to match when it was expected (required) to match.

 

Try using (abs(expression - undef) < tiny(undef)) or some other larger, but smaller value

(abs(expression - undef) < 0.1) ! between 99.8 and 100.

 

I suspect the .eq. issue exposed itself because the xxx.bin file was written with one rounding direction and the compiled version is using the other rounding direction and thus "undef" has different identities.

 

Jim Dempsey

 

0 Kudos
JohnNichols
Valued Contributor III
1,145 Views
PROGRAM SEDI_skill

IMPLICIT NONE

! THE NUMBER OF VARIABLES(M) AND THE NUMBER OF OBSERVAIONS(N), M X N

LOGICAL :: OK

logical :: iret,system
CHARACTER (LEN = 2) :: ch2
INTEGER,parameter :: nlon=61,nlat=61
INTEGER,parameter :: ndaym=7,ninit=15,npent=4,yr_st=2003,nyr=15
INTEGER,parameter :: m=21+2,nprcntl=2,nth=6
INTEGER :: i,ic,j,n,ii,jj,k,ik,kk,nt,imem,day_skip,ipent
CHARACTER (LEN=200) :: file1,file2,flin,pathmax,pathmin
INTEGER :: init,iyr,irec,i1,i2,j1,j2,k1,k2,day_st1(ninit),day_st,tst,ten
INTEGER ::ip,th(nth),ith
!-------------------------------------------------------------------------------------
REAL, ALLOCATABLE :: xdatmax(:,:,:,:,:)
REAL, ALLOCATABLE :: ydatmax(:,:,:,:,:)
REAL :: UNDEF,am,rchv,ofrq,ffrq,ht,fa,ta,tb,tc,td,ss,hval
REAL :: sindex(nlon,nlat)
CHARACTER :: cyr*4,cdate*4,cpent*1,cth*2,cprcntl*2(nprcntl)
CHARACTER :: cdate1*4(ninit),ccat*5
!-------------------------------------------------------------------------------------

data cdate1 /'0301', '0308', '0315', '0322', '0329', &
'0405', '0412', '0419', '0426', '0504', &
'0511', '0518', '0525', '0601', '0608'/

!data day_st1 / 60 ,67 ,74 ,81 ,88 , &
! 95 ,102 ,109 ,116 ,124 , &
! 131 ,138 ,145 ,152 ,159/
data day_st1 / 61 ,68 ,75 ,82 ,89 , &
96 ,103 ,110 ,117 ,125 , &
132 ,139 ,146 ,153 ,160/

data cprcntl/'95','99'/
data th/30,40,50,60,70,80/

!m= 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23
!p=clim,sd,1,5,10,15,20,25,30,35,40,45,50,55,60,65,70,75,80,85,90,95,99/
!-------------------------------------------------------------------------------------
undef=99.9
day_skip=59 !till 28th Feb
!--------------------------------------------------------------------------------------------------------
ALLOCATE(ydatmax(1:nlon,1:nlat,1:ndaym,1:ninit,1:nyr))
ALLOCATE(xdatmax(1:nlon,1:nlat,1:ndaym,1:ninit,1:nyr))
!--------------------------------

iret=system('mkdir -p data/')

do ith=1,nth
write(cth,'(I2.2)')th(ith)

do ip=1,nprcntl
if(ip==1)then
ccat='hw'
hval=3.0
endif
if(ip==2)then
ccat='shw'
hval=4.0
endif
write(*,*)'Threshold Value:',cth, ' Category=',ccat


do ipent=1,npent
write(cpent,'(I1.1)')ipent
if(ipent==1)tst=1
if(ipent==2)tst=8
if(ipent==3)tst=15
if(ipent==4)tst=22
ten=tst+6
!--------------------------------
DO init=1,ninit
cdate=cdate1(init)
day_st=day_st1(init)
DO iyr=1,nyr
write(cyr,'(i4.4)')yr_st+iyr-1
file1='/home/ERPAS/imdoper/Backup_Aditya/ht_wave/for_weekly_run/obs/heatwave_calc/new_criteria/ERPv2/ht_wv_days/'//cyr//'/MAMJ_hv_'//cyr//'.bin'
open (11,file=file1,form='unformatted',access='direct',recl=nlon*nlat)
ic=0
do k=day_st-day_skip+tst,day_st-day_skip+ten
! do k=day_st-day_skip,day_st-day_skip+6
ic=ic+1
read(11,rec=k)ydatmax(:,:,ic,init,iyr)
enddo
close(11)
file1='/home/ERPAS/imdoper/Backup_Aditya/ht_wave/for_weekly_run/model/new_criteria/ERPv2/ht_wv_days/'//cdate//'/ht_wv_'//cprcntl(ip)//'_'//cyr//'.bin'
open (11,file=file1,form='unformatted',access='direct',recl=nlon*nlat)
ic=0
do k=tst,ten
ic=ic+1
read(11,rec=k)xdatmax(:,:,ic,init,iyr)
enddo
close(11)
ENDDO
ENDDO
!--------------------------------------------------------------------------------------------------------
DO j=1,nlat
DO i=1,nlon
ta=0.0;tb=0.0;tc=0.0;td=0.0

DO kk=tst,ten
DO init=1,ninit
DO iyr=1,nyr
if(ydatmax(i,j,kk,init,iyr).ne.undef) then

if(ydatmax(i,j,kk,init,iyr)==hval) then
ofrq=1.0
else
ofrq=0.0
endif
if(xdatmax(i,j,kk,init,iyr).gt.float(th(ith))) then
ffrq=1.0
else
ffrq=0.0
endif
!
!obs ------>
! | yes no
! | ta tb
!fct| tc td
! \/
!
if(ofrq.eq.1.0)then
if(ffrq.eq.1.0) then
ta=ta+1.0
else
tc=tc+1.0
endif
else
if(ffrq.eq.1.0) then
tb=tb+1.0
else
td=td+1.0
endif
endif

endif
ENDDO ! nyr
ENDDO ! ninit
ENDDO ! kk
if(ta+tc.eq.0.0.or.tb+td.eq.0.0) then
ss=undef
else
HT=ta/(ta+tc)
FA=tb/(tb+td)
call sedi(ht,fa,undef,ss)
endif
sindex(i,j)=ss
ENDDO ! nlon
ENDDO ! nlat

file1='data/sedi_MAMJ_W'//cpent//'_'//cth//'_'//trim(ccat)//'.bin'
open (11,file=file1,form='unformatted',access='direct',recl=nlon*nlat)
write(11,rec=1)sindex
close(11)

enddo ! npent

enddo ! nprcntl

!deallocate (xdatmax, ydatmax)
enddo ! nth

STOP
contains
!----------------------------------------------------------------------------------
SUBROUTINE sedi(h,f,undef,ss)
IMPLICIT NONE
real,INTENT(IN) :: h,f,undef
real,INTENT(out) :: ss
real :: hm1,fm1,an,ad
!
if(h.eq.undef.or.f.eq.undef) then
ss=undef
return
endif
hm1=1.0-h
fm1=1.0-f
an=(f*hm1)/(fm1*h)
ad=f*fm1*h*hm1
if(an.gt.0.0.and.ad.gt.0.0) then
ss=log(an)/log(ad)
else
ss=undef
endif
RETURN
END SUBROUTINE sedi

END PROGRAM
JohnNichols
Valued Contributor III
1,144 Views

hval=3.0

These numbers are not going to be exact, they will have a positive tail at about 10 decimal places. You should do as Jim suggests or you will find problems.  So you number is 3 + error ===  error is always the same. 

jimdempseyatthecove
Honored Contributor III
1,129 Views

Good follow-up John. Convergence limits should be based on use of the EPSILON function.

For example, to be within 3 bits of a value X, use something like

IF(abs(Y-X) < EPSILON(X) * X *  THEN

(2^3 =

 

Jim Dempsey

Reply