- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
With the linux* version of ifx in the 2024.0.x release there is a known bug with the new LLVM Memory Sanitizer feature. This does not affect Windows users. A fix is coming in the 2024.1 Update Release.
There are several workaround until that Update 1 release fixes the issue:
Workaround: For now, yes, simply replace
-check all
or
-check uninit
with
-check all,nouninit
or
-check nouninit
OR you can unset the env var LIBRARY_PATH or remove the path in this variable to <oneAPI root dir>/2024.0.0/compiler/2024.0/lib
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I hit this ifx bug with my program kinds.f90 which ifx compiled but stopped running about halfway through when I used ```-check all```.
The workaround of unsetting LIBRARY_PATH did not fix the problem, but doing that and also using ```-check all,nounit``` did.
The 379-line program (sorry I failed to find a short one hitting the bug in the same way) :
! Fortran 95 free source form program kinds.f90 by J F Harper,
! Mathematics, Victoria University of Wellington, New Zealand, 13 Dec 2023.
! email: john DOT harper AT vuw DOT ac DOT nz
! It prints various properties of the available real and integer kinds.
! This version compiled and ran correctly with ifort, g95, AMD flang, and also
! with gfortran if the -freal... and -Ofast options were not used. It works
! around various compiler bugs, and prints '???' on lines revealing some of
! them. See the Warnings below.
!
! If there are at most 5 real kinds with different precisions or 6 integer
! kinds with different ranges, all are tested (but see WARNING 2 below.)
! If there may be more kinds the program says so.
!
! IEEE arithmetic is in the f2003 standard but not f95, and compilers
! may but need not provide its three intrinsic modules. Only 5 of its
! properties are tested: whether 'NAN','INF' and '-INF' are readable into
! variables of each real kind, and if so whether NaN /= NaN, Inf > huge,
! -Inf < -huge, and what you get from reading 'INF'. (Some compilers give
! Inf, some give +Inf, some give Infinity, and g95 real(10) gives NaN).
! This program does not use any intrinsic modules; some compilers that don't
! provide them do support NaN and the Infs. The program also does not test
! overflowing arithmetic operations. If it did, some compilers would
! not compile it, some would crash at run-time, some would run happily.
!
! WARNING 1: gfortran has options that change the precision of various
! real and integer kinds. Using -freal-M-real-N (where M = 4 or 8,
! N = 4, 8, 10 or 16, but N /= M) with this program may fail to find
! some valid kinds, because selected_real_kind ignores these options
! and literal constants with _ (e.g. 1.0_4) are unchanged.
! These options can also make krN /= rkN below.
! WARNING 2: Silverfrost has (had?) a bug giving -1 for selected_int_kind(0)
! so this program starts with selected_int_kind(1). That prevents it
! detecting an integer kind using 4 or fewer bits even if one exists.
! WARNING 3: Intel Fortran (ifort) has options -assume byterecl and
! -assume nobyterecl that return RECL in bytes or longwords. That affects
! the values of iolen and IOlength given by this program; see
! https://software.intel.com/sites/default/files/m/f/8/5/8/0/6366-ifort.txt
! WARNING 4: NaN, Inf results may be wrong if compiled with the -Ofast option
! WARNING 5: AMD flang compiler bugs treat ESw.dEe format as ESw.d and make
! huge==Inf and tiny==0 in quad precision.
! Recent revisions:
! 14/03/22 INF,NAN are now read with format * not F4.0; ninf initialised to 0
! to avoid an ifort problem (standard-conforming?); ninfkinds now *12
! and ninf1,2,3,4,5 are written with ES12.0E4 format.
! 17/03/22 forall replaced by transfer and array assignment; NAN etc improved.
! Space between columns reduced.
! 18/03/22 Word "Description", and changing E into e in ES formats removed.
! 23/03/22 Now more like kinds03.f90. Bug fix in both. G95 says 'Not OK'
! when dealing with NAN INF -INF . That's a compiler bug.
! 15/09/23 Warning 4 above.
! 09/12/23 Warning 5 above; '???' printed if compiler bug detected; 'OK' not
! now printed; Lr(r,x) now copes with x==Inf and x==-Inf; table of
! properties of real kinds has 12 not 11 spaces in each column.
! 13/12/23 Improvements above; line used in more places to avoid a g95 bugmodule realintkinds
implicit none
private
public realkinds,intkinds
! set up real kinds (compilers must offer at least two of them)
integer ,parameter:: rk1 = selected_real_kind(1), maxkr = 5
real(rk1),parameter:: r1 = 1
integer ,parameter:: kr1 = kind(r1) ! see WARNING 1 above
integer ,parameter::srk2 = selected_real_kind(precision(r1)+1)
integer ,parameter:: rk2 = (srk2+rk1+sign(1,srk2)*(srk2-rk1))/2
real(rk2),parameter:: r2 = 1
integer ,parameter:: kr2 = kind(r2)
integer ,parameter::srk3 = selected_real_kind(precision(r2)+1)
integer ,parameter:: rk3 = (srk3+rk2+sign(1,srk3)*(srk3-rk2))/2
real(rk3),parameter:: r3 = 1
! rk3 = srk3 if that's a valid real kind, rk2 if not
integer ,parameter:: kr3 = kind(r3)
integer ,parameter::srk4 = selected_real_kind(precision(r3)+1)
integer ,parameter:: rk4 = (srk4+rk3+sign(1,srk4)*(srk4-rk3))/2
real(rk4),parameter:: r4 = 1
! rk4 = srk4 if that's a valid real kind, rk3 if not
integer ,parameter:: kr4 = kind(r4)
integer ,parameter::srk5 = selected_real_kind(precision(r4)+1)
integer ,parameter:: rk5 = (srk5+rk4+sign(1,srk5)*(srk5-rk4))/2
real(rk5),parameter:: r5 = 1
! rk5 = srk5 if that's a valid real kind, rk4 if not
integer ,parameter:: kr5 = kind(r5)
integer ,parameter:: kraray(0:maxkr) = (/-1,kr1,kr2,kr3,kr4,kr5/)
! set up integer kinds (compilers must offer at least one)
integer ,parameter::maxik = 6, dp = kind(1d0), &
& ik1 = selected_int_kind(1) ! Can't have (0): Silverfrost bug
integer(ik1),parameter:: i1 = 1_ik1
integer ,parameter:: sik2 = selected_int_kind(range(i1)+1), &
& ik2 = (sign(1,sik2)*(sik2-ik1) + sik2+ik1)/2 integer(ik2),parameter:: i2 = 1_ik2
! ik2 = sik2 if that's a valid integer kind, ik1 if not
integer ,parameter:: sik3 = selected_int_kind(range(i2)+1), &
& ik3 = (sign(1,sik3)*(sik3-ik2) + sik3+ik2)/2
integer(ik3),parameter:: i3 = 1_ik3
! ik3 = sik3 if that's a valid integer kind, ik2 if not
integer ,parameter:: sik4 = selected_int_kind(range(i3)+1), &
& ik4 = (sign(1,sik4)*(sik4-ik3) + sik4+ik3)/2
integer(ik4),parameter:: i4 = 1_ik4
! ik4 = sik4 if that's a valid integer kind, ik3 if not
integer ,parameter:: sik5 = selected_int_kind(range(i4)+1), &
& ik5 = (sign(1,sik5)*(sik5-ik4) + sik5+ik4)/2
integer(ik5),parameter:: i5 = 1_ik5
! ik5 = sik5 if that's a valid integer kind, ik4 if not
integer ,parameter:: sik6 = selected_int_kind(range(i5)+1), &
& ik6 = (sign(1,sik6)*(sik6-ik5) + sik6+ik5)/2
integer(ik6),parameter:: i6 = 1_ik6
! ik6 = sik6 if that's a valid integer kind, ik5 if not
contains
elemental character(3) function tf(OK,ios) ! returns 'Yes', ' No', or ' '
logical, intent(in):: OK
integer, intent(in):: ios
tf = merge(merge('Yes',' No',OK),' ',ios==0)
end function tf
subroutine realkinds
integer :: i,nkr ! nkr = min(4, no. of different real kinds)
integer,parameter:: nilist = 9 ! no. of integer properties of reals
real(kr5):: rlist(maxkr,3)
integer :: ilist(maxkr,nilist),ios(maxkr),twopwr(maxkr),iolen=0,iolen1=0
logical,dimension(maxkr) :: nanOK,posOK,negOK,twopwrOK
character:: neg0(maxkr)*4, cninf*12,line*(25+maxkr*12),crlist(3)*12,&
cilist(nilist)*25,ck(maxkr)*9,tfmt*32
real(kr1):: ninf1(3)=0.0_kr1,neg01 = -0.0_kr1
real(kr2):: ninf2(3)=0.0_kr2,neg02 = -0.0_kr2
real(kr3):: ninf3(3)=0.0_kr3,neg03 = -0.0_kr3
real(kr4):: ninf4(3)=0.0_kr4,neg04 = -0.0_kr4
real(kr5):: ninf5(3)=0.0_kr5,neg05 = -0.0_kr5
data cilist/'kind . . . . . . . .','minexponent','maxexponent . . . .',&
'range','digits . . . . . . .','precision','radix . . . . . . .',&
'bits (from iolength)','bits (from IEEE 754)'/
data crlist/'epsilon','huge','tiny'/
!! cilist(1:7:2) = cilist(1:7:2)//' . .'
cninf = 'NAN INF -INF'
do nkr = maxkr,1,-1 ! loop to set nkr = no. of different precisions
if(kraray(nkr) /= kraray(nkr-1)) exit
end do
tfmt = '(1X,A,T33,A4,:,6X,99(A5,:,6X))' rlist(1,:) = real((/epsilon(r1),huge(r1),tiny(r1)/),kr5)
rlist(2,:) = real((/epsilon(r2),huge(r2),tiny(r2)/),kr5)
rlist(3,:) = real((/epsilon(r3),huge(r3),tiny(r3)/),kr5)
rlist(4,:) = real((/epsilon(r4),huge(r4),tiny(r4)/),kr5)
rlist(5,:) = real((/epsilon(r5),huge(r5),tiny(r5)/),kr5)
ilist(1,1:7) = (/kr1,minexponent(r1),maxexponent(r1),range(r1), &
& digits(r1),precision(r1),radix(r1)/)
ilist(2,1:7) = (/kr2,minexponent(r2),maxexponent(r2),range(r2), &
& digits(r2),precision(r2),radix(r2)/)
ilist(3,1:7) = (/kr3,minexponent(r3),maxexponent(r3),range(r3), &
& digits(r3),precision(r3),radix(r3)/)
ilist(4,1:7) = (/kr4,minexponent(r4),maxexponent(r4),range(r4), &
& digits(r4),precision(r4),radix(r4)/)
ilist(5,1:7) = (/kr5,minexponent(r5),maxexponent(r5),range(r5), &
& digits(r5),precision(r5),radix(r5)/)
inquire(iolength=iolen1) 1.0
iolen = -1 ! in case nkr > 5
do i = 1,nkr
if (i==1) inquire(iolength=iolen) r1
if (i==2) inquire(iolength=iolen) r2
if (i==3) inquire(iolength=iolen) r3
if (i==4) inquire(iolength=iolen) r4
if (i==5) inquire(iolength=iolen) r5
ilist(i,8) = iolen*bit_size(1)/iolen1
if (iolen == iolen1) then
ck(i) = 'single'
else if (iolen==2*iolen1) then
ck(i) = 'double'
else if (iolen==4*iolen1.and.ilist(i,6)>4*ilist(1,6)) then
ck(i) = 'quad'
else if (iolen >2*iolen1.and.iolen<=4*iolen1) then
ck(i) = 'extended'
else
ck(i) = merge('lower ','higher',iolen < iolen1)
end if
ilist(i,9) = ilist(i,5) + Lr(ilist(i,7),real(ilist(i,3),kr5))&
& + merge(2,1,index(ck(i),'extended')>0)
end do
print*
print "(99(A,:))",repeat(' ',17),adjustr(ck(1:nkr)//' '),' precision'
! Print integer properties of real kinds (kind,minexpoment,maxexponent,
! range, digits, precision, radix, bits needed (2 ways)
do i = 1,nilist
write(line,"(A)") repeat(' ',3)//cilist(i)//' '
write(line(25:),"(I4,4X,99(I8,:,4X))") ilist(1:nkr,i)
print *,trim(line)
end do
! Print real properties of real kinds (epsilon,huge,tiny)
do i = 1,3
write(line,"(4X,A,T18,99(ES12.2E4,:))") crlist(i),rlist(1:nkr,i)
if(index(line,'I')>0.or.index(line,'0.00E+00')>0)&
write(line(len_trim(line)+1:),*)' ???'
print "(A)",trim(line)
twopwr(1:nkr) = Lr(2,rlist(1:nkr,i)) ! flang can give -huge(1)-1 !
twopwrOK(1:nkr) = twopwr(1:nkr)<huge(1).and.twopwr(1:nkr)>-huge(1)
write(line, "(T18,A,I4,99(I12,:))") merge('~','=',i==2)//' 2.0** ',&
& twopwr(1:nkr)
print "(A)", trim(line)//allOK(twopwrOK(1:nkr))
end do
! Test whether -0.0 is printed with its sign
write(neg0,'(F4.1)') neg01,neg02,neg03,neg04,neg05
print "(1X,A,T18,99(8X,A4,:))",'-0.0 is written as',(neg0(i),i=1,nkr)
! Try reading NAN, INF,-INF from cninf into each real kind. Verbose because
! ninf1,ninf2,etc won't fit into one 2-D array: they are of different kinds.
do i = 1,nkr
if(i==1)read(cninf,*,iostat=ios(i)) ninf1
if(i==2)read(cninf,*,iostat=ios(i)) ninf2
if(i==3)read(cninf,*,iostat=ios(i)) ninf3
if(i==4)read(cninf,*,iostat=ios(i)) ninf4
if(i==5)read(cninf,*,iostat=ios(i)) ninf5
end do
! Report on readability of NAN etc into each real kind, and what it gives
if(all(ios(1:nkr)==0)) then
tfmt = "(1X,A,T21,99(A9,3X,:))"
do i = 1,3
call readcheck(i,nkr)
end do
nanOK = (/ninf1(1)/=ninf1(1),ninf2(1)/=ninf2(1),&
& ninf3(1)/=ninf3(1),ninf4(1)/=ninf4(1),ninf5(1)/=ninf5(1)/)
posOK = (/ninf1(2)>huge(r1),ninf2(2)>huge(r2),&
& ninf3(2)>huge(r3),ninf4(2)>huge(r4),ninf5(2)>huge(r5)/)
negOK = (/ninf1(3)<-huge(r1),ninf2(3)<-huge(r2),&
& ninf3(3)<-huge(r3),ninf4(3)<-huge(r4),ninf5(3)<-huge(r5)/)
call querycheck(' NaN /= NaN?',nanOK)
call querycheck('+Inf > huge?',posOK)
call querycheck('-Inf < -huge?',negOK)
print *, '(IEEE modules and '// &
'arithmetic NaNs and overflows were not tested.)'
else
do i = 1,nkr
do i = 1,nkr
if(ios(i)/=0) print *,'"'//trim(cninf)//'" cannot be read '//&
'as three '//trim(ck(i))//'-precision "numbers"'
end do
end if
print *
print *,'NOTE 1: '//trim(merge( &
& 'No higher-precision real kind is available.', &
& 'Warning: there may be more real kinds. ',nkr<maxkr))
contains
subroutine readcheck( n,nkr)
integer,intent(in)::n,nkr
integer j
character ninfkinds(maxkr)*12
logical infOK(nkr)
write(ninfkinds,'(ES12.0E4)') & ! 14/03/22
ninf1(n),ninf2(n),ninf3(n),ninf4(n),ninf5(n)
infOK(1:nkr) = (ninfkinds(1)==ninfkinds(1:nkr))
write(line,tfmt) 'Reading '//adjustr(cninf(4*n-3:4*n))//' gives',&
(trim(adjustl(ninfkinds(j))),j=1,nkr)
print "(A)",trim(line)//allOK(infOK(1:nkr))
end subroutine readcheck
subroutine querycheck( query,isitOK)
character(*),intent(in)::query
logical,intent(in):: isitOK(:)
write(line,tfmt)query,(tf(isitOK(i),ios(i)),i=1,nkr)
print "(A)",trim(line)//allOK(isitOK(1:nkr))
end subroutine querycheck
character(12) function allOK(isitOK)
logical,intent(in) :: isitOK(:)
allOK = ' '//trim(merge(' ','???',all(isitOK(1:nkr))))
end function allOK
end subroutine realkinds
elemental integer function Lr(r,x) ! Gives nearest integer to log_r(x)
integer,intent(in) :: r ! Needed as g95 quad precision log
real(kr5),intent(in) :: x ! is not yet provided, and kr5 is
real(kr2) sigfigs, tenpower ! quad precision in some systems.
character(453) xchar ! kr2 is double precision in all.
integer Esignposn !,ios
write(xchar,"(ES43.34E4)") x
if(index(xchar,'I')/=0)then ! x might be +Inf or -Inf
Lr = huge(1)*merge(-1,1,index(xchar,'-')>0) ! no g95 kr5 sign
else
Esignposn = scan(xchar,'+-',back=.true.)
! read(xchar(:Esignposn-2),*,iostat=ios) sigfigs
read(xchar(:Esignposn-2),*) sigfigs
! if(ios/=0) print *,'debug 3 ios in Lr=',ios
read(xchar( Esignposn: ),*) tenpower
Lr = nint((log(sigfigs)+log(10d0)*tenpower)/log(real(r,kr2)))
end if
end function Lr
! Give useful properties of the (first 6) integer kinds
subroutine intkinds
integer,parameter::ikarray(0:maxik) = (/-1,ik1,ik2,ik3,ik4,ik5,ik6/)
integer:: i,i1c,i4c,iolen=0,k,nik ! nik = min(6,number of integer kinds)
integer(ik6):: ilist(maxik,6)
character :: ck(maxik)*22 = ' ', line*128, near*3
character(*),parameter:: fsu = ' file storage unit',&
surprise = ' - surprising? See NOTE 3 above.'
ilist(1,1:3) = (/digits(i1),radix(i1),range(i1)/) ! RHS default int.
ilist(2,1:3) = (/digits(i2),radix(i2),range(i2)/)
ilist(3,1:3) = (/digits(i3),radix(i3),range(i3)/)
ilist(4,1:3) = (/digits(i4),radix(i4),range(i4)/)
ilist(5,1:3) = (/digits(i5),radix(i5),range(i5)/)
ilist(6,1:3) = (/digits(i6),radix(i6),range(i6)/)
! ilist(:,4) becomes iolen in do loop later
! Doing ilist(:,5:6) element-by-element works around an ifort 12.1 bug
ilist(1,5) = bit_size(i1) ! RHS kind ik1
ilist(2,5) = bit_size(i2) ! RHS kind ik2
ilist(3,5) = bit_size(i3) ! RHS kind ik3
ilist(4,5) = bit_size(i4) ! RHS kind ik4
ilist(5,5) = bit_size(i5) ! RHS kind ik5
ilist(6,5) = bit_size(i6) ! RHS kind ik6
ilist(1,6) = huge(i1) ! RHS kind ik1
ilist(2,6) = huge(i2) ! RHS kind ik2
ilist(3,6) = huge(i3) ! RHS kind ik3
ilist(4,6) = huge(i4) ! RHS kind ik4
ilist(5,6) = huge(i5) ! RHS kind ik5
ilist(6,6) = huge(i6) ! RHS kind ik6
do nik = maxik,1,-1 ! this loop finds nik
if (ikarray(nik) /= ikarray(nik-1)) exit
end do
iolen = -1 ! in case nik > 6
do k = 1,nik
if (k==1) inquire(iolength=iolen) i1
if (k==2) inquire(iolength=iolen) i2
if (k==3) inquire(iolength=iolen) i3
if (k==4) inquire(iolength=iolen) i4
if (k==5) inquire(iolength=iolen) i5
if (k==6) inquire(iolength=iolen) i6
ilist(k,4) = iolen
if (ikarray(k)==kind(1)) ck(k) = '(default integer kind)'
end do
print "(/,A)",' kind digits radix range iolen bit_ huge '
print "( A)",' size '
do k = 1,nik
print "(I4,4I6,I5,4X,I0,1X,A)", &
& ikarray(k),(ilist(k,i),i=1,6),trim(ck(k))
near = merge(' = ',' ~ ',ilist(k,6)<1000)
write(line,"(T42,A,T55,A,ES10.3)" ) &
& e2less1(k,ilist),near,real(ilist(k,6),dp)
print "(A)",trim(line)
end do
print "(A)",' NOTE 2: '//trim(merge( &
& 'No higher integer kind is available. ',&
& 'Warning: there may be more integer kinds.',nik<maxik))
print "(A,I0,A)",' NOTE 3: file storage unit = ',&
& ilist(nik,5)/ilist(nik,4),' bits.'
print "(/,A,/)",' IOlength for 1,4 characters:'
inquire(iolength=i1c) 'a'
inquire(iolength=i4c)'abcd'
print "(1X,A,T24,I3,A)",'for 1 character:',i1c,fsu//plural(i1c),&
'for 4 characters:',i4c,fsu//plural(i4c)//&
trim(merge(surprise,repeat(" ",len(surprise)),i4c/=i1c*4))
end subroutine intkinds
character(1) function plural(n)
integer, intent(in) :: n
plural = merge('s',' ',n>1)
end function plural
character(12) function e2less1(k,ilist)
! k = kind; checks huge = radix**digits-1
integer , intent(in) :: k
integer(ik6), intent(in) :: ilist(:,:)
integer(ik6) :: OK
character(1):: op
OK = ilist(k,6)-2_ik6**ilist(k,1)+1_ik6
op = merge('=',merge('>','<',OK>0),OK==0)
write(e2less1,"(2(A,I0),A)")op//' ',ilist(k,2), &
& '**',ilist(k,1),' - 1'
end function e2less1
end module realintkinds
program kinds
use realintkinds, only: realkinds,intkinds
implicit none
print "(/,A)", ' Properties of real kinds:'
call realkinds
print "(/,A)", ' Properties of integer kinds:'
call intkinds
print "(/,A)",' ISO_FORTRAN_ENV was not tested. It''s an F2003 feature'//&
' tested in kinds03.f90'
print "(/,A)",' WARNING: compiling with the -Ofast option may '//&
'give some wrong NaN, Inf results'
end program kinds
```
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Can you please attach your example as a file? I'm getting A LOT of syntax errors from the copy/paste.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You can paste as plain text or code. On the toolbar for the post, far right is this triple dots, for more editor controls:
If you expand that toolbar with the triple dots, you will see a "</>" editor control., this is for pasting in text or code
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Sorry that the cut and paste failed, and that it took so long for my university's spam-stopping system to wake up after its Christmas close-down. (It thinks all my email from Intel is phishing and I have to tell it not to every time.)
In addition I had revised my latest version of the program (attached) on 20 Dec 2023 and it does not now stop halfway through with ifort or ifx 2024.0.2
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Also, the uninitialized checking in this new ifx is really good at finding actual use of uninitialized data. If you can also post the output from the error dump, I can help decode it. It is a bit cryptic. Read from the bottom up. Make sure to compile with -g -traceback along with -check uninit, and unsetting the LIBRARY_PATH
Reading from the bottom up, what is the highest stack location in YOUR code that you recognize? Focus on that line. Is it a READ or a STORE error? Let's see what uninit found. ifort was NOT good at finding memory errors. There may be something of concern.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Attached is a gzip'd tar file with a simple minded example using -check uninit successfully on Linux.
RUN is my script.
test.f90 is the source
test.log is the output. Notice that 2 uninitialized values are reported (read up from the bottom) one each on lines 3 and 4. If I take out the print of jj, there are no messages. The compiler optimized the assignment out.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@JFH thanks for the example kinds.f90
I am also getting a Memory Sanitizer use of uninitalized data. It is in the Fortran Runtime library. and specifically for KIND=16. WHich may not be surprising. that code path does not get a lot of testing (not a lot of use of KIND=16).
Obviously the code works correctly if you use -check,nouninit but that is disabling this check.
But I suspect the Memory Sanitizer is correct and we may have some use of uninitialized data for the FRTL function NEQ for KIND=16. I'll have my team look at that code and see if there (or where) the use of unitialized data is occuring. There is struct IO_CTX we use in the FRTL. It's possible we are touching data that is allocated but not initialized. Probably harmless for results but is somethign we should fix. as you probably notices, it's when it does the test for
NaN /= NaN? Yes Yes Yes
for the KIND=16 case.
I can reduce the example to this specific test and send it over to our FRTL team.
./a.out
Properties of real kinds:
single double quad precision
kind . . . . . . . . 4 8 16
minexponent -125 -1021 -16381
maxexponent . . . . 128 1024 16384
range 37 307 4931
digits . . . . . . . 24 53 113
precision 6 15 33
radix . . . . . . . 2 2 2
bits (from iolength) 32 64 128
bits (from IEEE 754) 32 64 128
epsilon 1.19E-0007 2.22E-0016 1.93E-0034
= 2.0** -23 -52 -112
huge 3.40E+0038 1.80E+0308 1.19E+4932
~ 2.0** 128 1024 16384
tiny 1.18E-0038 2.23E-0308 3.36E-4932
= 2.0** -126 -1022 -16382
-0.0 is written as -0.0 -0.0 -0.0
Reading NAN gives NaN NaN NaN
Reading INF gives Infinity Infinity Infinity
Reading -INF gives -Infinity -Infinity -Infinity
==253505==WARNING: MemorySanitizer: use-of-uninitialized-value
#0 0x6556c0 in __neq (/nfs/pdx/disks/cts1/quad/rwgreen/tuesday/a.out+0x6556c0) (BuildId: c3aa5d6d17f3cf05f438e19848f270f486b473f5)
#1 0x573ed1 in __for_ieee_quiet_ne_k16_ (/nfs/pdx/disks/cts1/quad/rwgreen/tuesday/a.out+0x573ed1) (BuildId: c3aa5d6d17f3cf05f438e19848f270f486b473f5)
#2 0x4a35a9 in realintkinds_MP_realkinds_ /nfs/site/home/rwgreen/quad/tuesday/kinds.f90:216:42
#3 0x4bf3e9 in MAIN__ /nfs/site/home/rwgreen/quad/tuesday/kinds.f90:372:8
#4 0x40d3e8 in main (/nfs/pdx/disks/cts1/quad/rwgreen/tuesday/a.out+0x40d3e8) (BuildId: c3aa5d6d17f3cf05f438e19848f270f486b473f5)
#5 0x7f79b1caab49 in __libc_start_call_main (/lib64/libc.so.6+0x27b49) (BuildId: 245240a31888ad5c11bbc55b18e02d87388f59a9)
#6 0x7f79b1caac0a in __libc_start_main@GLIBC_2.2.5 (/lib64/libc.so.6+0x27c0a) (BuildId: 245240a31888ad5c11bbc55b18e02d87388f59a9)
#7 0x40d2b4 in _start (/nfs/pdx/disks/cts1/quad/rwgreen/tuesday/a.out+0x40d2b4) (BuildId: c3aa5d6d17f3cf05f438e19848f270f486b473f5)
Uninitialized value was created by an allocation of '$io_ctx' in the stack frame
#0 0x4a6dc2 in realintkindsrealkinds_MP_readcheck_ /nfs/site/home/rwgreen/quad/tuesday/kinds.f90:237
SUMMARY: MemorySanitizer: use-of-uninitialized-value (/nfs/pdx/disks/cts1/quad/rwgreen/tuesday/a.out+0x6556c0) (BuildId: c3aa5d6d17f3cf05f438e19848f270f486b473f5) in __neq
Exiting
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@JFH I need you to check something. The check uninit may be correct.
nkr is 3 in this case, correct?
Yet around line 215 you have:
nanOK = (/ninf1(1)/=ninf1(1),ninf2(1)/=ninf2(1),&
& ninf3(1)/=ninf3(1),ninf4(1)/=ninf4(1),ninf5(1)/=ninf5(1)/)
I do not see that you ever initialized ninf4(1) nor ninf5(1). Probably because nkr is 3 so only ninf1 through ninf3 had values read into them. Are you assuming ninf4(1) and ninf5(1) are 0.0 even though you did not initialize them? check uninit catch ANY use of array elements that have not been explicitly initialized.
confirm that you initialized ninf4(1) and ninf5(1). Else check uninit is correct.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Ah. I have been there before. ninf4 and ninf5 are initialized with the value zero when they are declared on lines 126 and 127:
real(kr4):: ninf4(3)=0.0_kr4,neg04 = -0.0_kr4
real(kr5):: ninf5(3)=0.0_kr5,neg05 = -0.0_kr4
As you found, when compiling with ifort or ifx so that nkr is 3, they are not given other values at line 215 but I don't see how they could be treated as uninitialized then.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Ron, has this bug been addressed in the latest ifx 2024.0.2?
Thanks,
Marcos
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
No, 2024.0.2 still has this issue. Fixes will come in 2024.1.0, which is a few months away.
- 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
This is fixed in 2024.1.0.
Keep in mind that ALL linked libraries MUST be built with -fsanitize=memory. 3rd party libraries like MKL, MPI, etc may not have such versions and will give false positives.

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