- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I am trying to run a code that uses modules, and get a funny behavior :
Depending on the optimization I use and on other things which to me seem random (such as whether I print out intermediate stages of the calculation, the size of a particular array and on methods of calculation), I sometimes find that the output file is all zeros.
I know this sounds vauge, but it will take me some time to strip the code to something I can post here, so does this sound familiar ?
This is the second time that I see that changing the optimization options of ifort gets rid of a bug in a code with modules. (second time, but different code !)
Any idea before I post the code ?
I using the 10.1 on linux 64 bit machine (dell).
Thanks,
Barak
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Barak,
Have you (in Debug configuration) enabled test for uninitialized variables?
And have you enabled gen interfaces/check interfaces?
What you are describing is similar to what happens when you use uninitialized variables or when you are calling subroutines/functions with incorrect arguments.
Also, I would suggest using IMPLICIT NONE. This way if you forget to USE YourModule that the compiler won't generate automatic variables for those specified in the missing module.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Thanks for you help. I am attaching a stripped down version of the code, which is in two files "code1.f90" and "code2.f90" - took me some time to do that, and I do not think I canget it to be more compact since I find that changing little things (like in-run printing etc) can change the result - so what I attach is the most stable version of this bug...
When I compile without optimization
ifort -O0 code2.f90 code1.f90
I get the desired result. When I just do
ifort code2.f90 code1.f90
I get nonsense (i.e. the last column in the output is zero instead of 1).
I have a feeling its because the loops are resticted to run within a range that can change (but that has a maximum allowed set by the parameters in code2.f90). The reason for that is that I saw something similar in a different code (which I can send later).
Any help would be much appreciated - for the moment I do not have any means to use the intel debugger since my sys admin did not install it !
Barak Bringoltz
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
code2.f90 :
module parameters_analysis
implicit none
integer,parameter:: MNdim = 2
integer,parameter:: MNcnfg = 1
integer,parameter:: MNcol = 50
integer,parameter:: MNm = 100
integer,parameter:: MNfug = 1
integer,parameter:: MNp = 0
!*** global variables **********
integer, save:: Ndim,Ncnfg
integer, save:: Ncol
integer, save:: Nm,Np,Nfug
real*8,dimension(MNm), save:: m ! an array containing different values of mass
integer:: im
real*8,dimension(MNfug), save:: fug ! an array containing different values of exp(mu)
integer:: ifug
real*8,dimension(2*MNp+1), save:: p ! an array containing different values of momentum
integer:: ip
contains
subroutine mpi_analysis
implicit none
!parameters:
Ndim=MNdim
Ncnfg=MNcnfg
Ncol=MNcol
Nm=MNm
Nfug=MNfug
Np=MNp
!custom couplings: preparing the beta,m,p-grids and the things to measure
do im=1,Nm
m(im)=real(im-1)/Nm
enddo
do ifug=1,Nfug
fug(ifug)=real(ifug-1)/Nfug
enddo
do ip=1,2*Np+1
p(ip)=real(ip-1)/Np
enddo
!main program:
call dirac_analysis
return
end subroutine mpi_analysis
end module parameters_analysis
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
!***********************************************************************
module gauge_and_Dirac
use parameters_analysis
implicit none
complex*16, dimension(MNm,MNfug,MNcnfg), save:: Sigma
end module gauge_and_Dirac
!***********************************************************************
! main program
!***********************************************************************
program main_analysis
use parameters_analysis
use gauge_and_Dirac
implicit none
call mpi_analysis
stop
end program main_analysis
!***********************************************************************
! main routine
!***********************************************************************
subroutine dirac_analysis
use parameters_analysis
use gauge_and_Dirac
implicit none
Sigma = (0.0d0,0.0d0)
call PsibarPsi(-1,1,'D')
call PsibarPsi(0,1,'-')
return
end subroutine dirac_analysis
!***********************************************************************
subroutine PsibarPsi(rank,cnfg,alg)
use parameters_analysis
use gauge_and_Dirac
implicit none
character(1):: alg
character(7):: filename
integer:: i,cnfg
integer:: fileunit,rank
real*8:: ASigma_r
if (rank==-1) then
do im=1,Nm
do ifug=1,Nfug
if (alg=='D')then
do i=1,Ndim*Ncol
Sigma(im,ifug,cnfg) = 1.0d0
enddo
elseif(alg=='C')then
do i=1,Ncol*Ndim/2
Sigma(im,1,cnfg) = 2.0d0
end do
endif
enddo
enddo
elseif (rank>=0) then
filename='outfile'
fileunit=10
open(unit=fileunit,file=filename,form='formatted')
do im=1,Nm
do ifug=1,Nfug
ASigma_r = real(Sigma(1,1,1))
write(fileunit,12) m(im), fug(ifug), ASigma_r
write(6,12) m(im), fug(ifug), ASigma_r
12 format(3(f16.8,2x))
enddo
enddo
close(fileunit)
endif
return
end subroutine PsibarPsi
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
On running on 10.0.027, x64, Windows compiling without optimizations and compiling with full optimizations produced similar results. +/- 3.0E-8.
This is within theprecision of the calculations and considering that optimizations may reorder sequence of calculations.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Last column in both cases is 1.0000000
You also might consider specifying in the option switches, or !DEC$REAL:8, or using dble(x) in place of real(x)
The 10.1.013 is on my other system, but that is running x32.
Jim
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I'm not talking about 10^-8 issues, but rather that the third columns is all zeros when I use just
ifort code2.f90 code1.90
and all ones when I do
ifort -O3 code2.f90 code1.90
I've just did some more checks on a couple of other linux clusters :
1) I did not reproduced this behavior on a relatively older cluster
2) I did reproduce this bug on a new cluster
I do not know the versions of ifort on these machines (will know once sys admin is back from holiday) but this makes me think there's an issue with the newer versions of the comiler.
So .... it might be useful if you check the older version - I think the 64 vs 32 bit issue may not be relevant - as I said I get 0.000000 instead of 1.000000 (or for that matter instead of any other number)
Best,
Barak
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I have reproduced the bug on a 10.0.025 but not on the 8.1 version of ifort.
Also, I see another bug - this one occurs when you use the -O3 option and disappears when you don't. Also I again see this bug when I use 10.0.025 and 10.0.026 but not on 8.1
Barak
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I just realized you did ot reproduce the bug with full optimizations and without optimizations at all. I get the same, but :
Did you try the default (which is -O2, I believe) - its then that the bug rears its ugly head !
Can you try again with the default on the 10.0.026 ?
ifort code2.f90 code1.f90
or for that matter
ifort -O2 code2.f90 code1.f90
?
Thanks !

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page