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

Access violation after read beyond end of formatted file

Quintin_Hill
Novice
1,005 Views

After switching part of my code to use 64-bit reals as opposed to 32-bit reals,  I have been experiencing crashes.

The traceback starts as follows:
forrtl: severe (157): Program Exception - access violation
Image              PC                Routine            Line        Source
libifcoremdd.dll   000007FEDE2F6AA6  Unknown               Unknown  Unknown
libifcoremdd.dll   000007FEDE3331DD  Unknown               Unknown  Unknown
....

And then refers to a routine that is modelled by the below routine:

SUBROUTINE ReadAFile(cFile)
CHARACTER(*), INTENT(IN) :: cFile
CHARACTER(2048) :: cRemain
INTEGER :: iStat
OPEN(9, FILE = cFile, ACTION = 'READ', STATUS = 'OLD', IOSTAT = iStat)
IF (iStat .NE. 0) RETURN
DO
READ(9, '(A)', IOSTAT = iStat) cRemain ! Traceback refers to this line of code
IF (iStat .EQ. -1) EXIT
IF (iStat .NE. 0) RETURN
! PRINT *, TRIM(cRemain)
! Do stuff with cRemain
END DO
CLOSE(9, IOSTAT = iStat)
IF (iStat .NE. 0) RETURN
END SUBROUTINE ReadAFile

The crash is only happening on the 64th call to this routine.  All runtime checks are selected but no other error occurs.  While investigating this I noticed that READ is not returning an IOSTAT of -1 at the end of the file when the crash occurs. By printing cRemain after the READ I get "0" for the blank line at the end of the file than gibberish for some extra lines (depends on compilation options 1 more line for 32-bit, 5 lines for 64-bit binary).  I'm guessing that somehow the stack has been corrupted but I have can't see why this would be the case.  The program crashes when compiled under Intel Visual Fortran Compiler 18.0.2.185 and Intel Visual Fortran Compiler XE 14.0.6.241; it does not crash when compiled with gfortran.  I tried putting all arrays on the heap and boosting the stack size in the linker options but this did not help. Does anyone have any suggestions how this could be further debugged?

0 Kudos
13 Replies
Steve_Lionel
Honored Contributor III
1,005 Views

I'd guess that the problem is actually elsewhere in your program, where it is overwriting data that doesn't belong to it. Have you tried a more recent version of the compiler (18.0.2 is current)?

0 Kudos
andrew_4619
Honored Contributor II
1,005 Views
Do you have all the compile time. CHecks on, particularly interface checking?
0 Kudos
Quintin_Hill
Novice
1,005 Views

I am using Intel Visual Fortran Compiler 18.0.2.185 which is the latest.  My command line is:

/nologo /debug:full /Od /heap-arrays0 /fpp /warn:declarations /warn:unused /warn:ignore_loc /warn:truncated_source /warn:uncalled /warn:interfaces /assume:byterecl /Qtrapuv /module:"x64\Debug\\" /object:"x64\Debug\\" /Fd"x64\Debug\vc140.pdb" /traceback /check:pointer /check:bounds /check:uninit /check:format /check:output_conversion /check:arg_temp_created /check:stack /libs:dll /threads /dbglibs /c

And no warnings are found.   Everything is in modules so interfaces are enforced.  It is strange as before moving to 64-bit REALs in one module the application had been working without any issue.

0 Kudos
mecej4
Honored Contributor III
1,005 Views

You have noted twice that the problems followed your changing 32-bit reals in your program to 64-bit reals, yet the code snippet that you presented has no reals of any size. Does it not seem reasonable, then, as Steve Lionel suggested, that the root cause is in some parts of the code that you have not shown -- parts that do something with real variables, rather than character strings as in the code snippet above?

Have you tried running with different options and/or building a 32-bit EXE instead?

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,005 Views

>> It is strange as before moving to 64-bit REALs in one module the application had been working without any issue.

Does your code contain named commons where different compilation units, using the same named common, map the data differently? If so, changing the real type from 32-bit to 64-bit will change the byte offset from start of named common and therefor my clobber data in other same-named common.

Jim Dempsey

0 Kudos
Quintin_Hill
Novice
1,006 Views

I have tried a 32-bit executable (still breaks slightly different garbage lines) and dropping AVX targetting.   I have no COMMON blocks in my code.  I'm trying to reduce the code while still reproducing the problem, just calling the routine where it crashes 64 times is not sufficient, it needs to be embedded in a wider application.  Thank you for all the suggestions so far.

0 Kudos
Quintin_Hill
Novice
1,006 Views

After further testing it seems that the switch from 32-bit to 64-bit reals caused Release builds to break using Intel Visual Fortran Compiler XE 14.0.6.241.  Even without this change Release builds using Intel Visual Fortran Compiler 18.0.2.185 and Debug builds using either compiler break (with particular inputs).  So I still need to narrow this down to work out why this behaviour is happening.

0 Kudos
Quintin_Hill
Novice
1,006 Views

I have further reduced the code and now have a 64 line program that reproduces the error:

PROGRAM CrashTest
  IMPLICIT NONE

  CHARACTER(*), PARAMETER :: cFile1 = &
       'Path omitted'
  CHARACTER(*), PARAMETER :: cFile2 = &
       'Path omitted'

  CALL ReadAFile(cFile1)
  CALL ReadAFile(cFile2)

CONTAINS

  SUBROUTINE ReadAFile(cFile)

    Character(*), INTENT(IN)  :: cFile
    REAL    :: r1, r2
    Integer :: iStat, iUnit, i, iPos
    LOGICAL :: lProcessed
    Character(256)  :: cValue
    Character(2048) :: cRemain

    lProcessed = .FALSE.
    cRemain = ''

    iUnit = 9
    Open(iUnit, FILE = cFile, ACTION = 'READ', STATUS = 'OLD', IOSTAT = iStat)
    If (iStat .NE. 0) RETURN

    Read(iUnit, '(A)', IOSTAT = iStat) cRemain
    IF (iStat .NE. 0) THEN
       CLOSE(iUnit, IOSTAT = iStat)
       RETURN
    END IF

    Do While (.TRUE.)
       cRemain = ADJUSTL(cRemain)
       iPos = INDEX(cRemain, ' ')
       cValue = ADJUSTL(cRemain(1:iPos-1))
       cRemain = cRemain(iPos+1:)

       If (cValue(1:LEN('VERTICAL')).EQ.'VERTICAL') Then
          IF (TRIM(cFile) .EQ. cFile2) Then

             DO i = 1, 4
                READ(iUnit,*, IOSTAT = iStat) r1, r2
                IF (iStat .NE. 0) RETURN
             END DO
             lProcessed = .TRUE.

          END IF

       Endif

       Read(iUnit, '(A)', IOSTAT = iStat)cRemain
       If (iStat .NE. 0) EXIT
       IF (lProcessed) PRINT *, "Near End of file: ", TRIM(cRemain)
    Enddo

    Close(iUnit, IOSTAT = iStat)

  END SUBROUTINE ReadAFile

END PROGRAM CrashTest

I'm investigating what is special about the input files.  But the content of the file referenced by cFile2 is important, that of cFile1 is not so important (I could use any file of the same format, except the file referered to by cFile2 including a duplicate copy with a different name).  I will work on reducing the input files so that I can share something here.

0 Kudos
Quintin_Hill
Novice
1,006 Views

I have reduced the two files, mostly by redacting the content by overwriting with "A"s as the file length seems important.  So code now has:

  CHARACTER(*), PARAMETER :: cFile1 = &
	       'C:\Test\crashfile1.txt'
  CHARACTER(*), PARAMETER :: cFile2 = &
	       'C:\Test\crashfile2.txt'

I attach the two files that reproduce the crash.  It would be good if someone else could test this.  I assume they are not munged upon uploading to check here are the md5sums:

f95b74262ac4ce2454897c3c122f84d3 *crashfile1.txt
189f11d1dcd46a446dda2f18c46ed0b3 *crashfile2.txt

 

0 Kudos
mecej4
Honored Contributor III
1,006 Views

I see the crash with 18.0.2, 32 and 64 bit, 17.0.4, 64 bit. No crash with 17.0.4, 32 bit and 7.0, 32-bit, Lahey 7.1, NAG 6.2, Gfortran 6.3.

0 Kudos
andrew_4619
Honored Contributor II
1,006 Views

Does that work if it is not a "contained" subroutine? It looks to me like you should file a ticket on this one at the Intel service centre.

0 Kudos
Quintin_Hill
Novice
1,006 Views

@mecej4: Thank you for reproducing this.

@andrew_4619: I've not tried it as an external subroutine, originally it lived in a separate module though.  I've submitted it to the Intel service centre as request 03393555.

0 Kudos
Ron_Green
Moderator
1,006 Views

This bug is fixed in 2019 Update 4.

0 Kudos
Reply