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

Replacing the first record in a sequential formatted file

NotThatItMatters
Beginner
3,659 Views

This is perhaps an "add on" to dboggs query "Deleting records from a sequential formatted file".  I have a sequential formatted file with an initial "record" which has the number of records in the file.  Obviously I do not tend to know this value a priori.  Therefore, I run my code to the end and make a CALL at the end which is the following:

SUBROUTINE CLEAN_UP_FILE(INPUT_CODE, NUMBER_OF_RECS)
!  This routine cleans up the sequential file.  It is important
!  that the RECL for opening the file is the length of the first
!  line in the file and that the record IS the first line.
    USE VERSION_INFORMATION, ONLY : VERSION_INFO
    INTEGER, INTENT(IN) :: INPUT_CODE, NUMBER_OF_TIMES

    CLOSE(UNIT = INPUT_CODE)
    OPEN(UNIT = INPUT_CODE, FILE = FILENAME, ACCESS = 'DIRECT', &
      FORM = 'FORMATTED', RECL = 17)
    IF (NUMBER_OF_TIMES > 0) THEN
        WRITE(UNIT = INPUT_CODE, FMT = '(I6,1X,A10)', REC = 1) &
          NUMBER_OF_TIMES, VERSION_INFO
    END IF
    CLOSE(UNIT = INPUT_CODE)
END SUBROUTINE CLEAN_UP_FILE

This in general "works" but as of late, there is a particular file input/output sequence where it fails with an Intel(r) Visual Fortran run-time error.

The error message reads "forrtl: FormatMessage failed for system message number 1450."  I have little idea what that could mean.

The second message box reads

forrtl: severe (30): open failure unit XXX, file YYY.  Stack trace terminated abnormally.

Is there something inherently wrong about what I am doing in the SUBROUTINE?

0 Kudos
24 Replies
andrew_4619
Honored Contributor III
3,029 Views

I would add a iostat=istat on the CLOSE and the OPEN and look at non zero Istat values. As discussed in other threads it is probably a timing issue where the Fortran run time has 'closed' the file but windows is still doing its stuff and the file is still locked. 

So if the open fails make a short delay of a few millseconds and try again is a common approach and then after a couple of failed attempts give up!

0 Kudos
dboggs
New Contributor I
3,029 Views

I'm a bit confused. Is this a sequential-access file or a direct-access file? It seems you are trying to have it be both. I don't think you can do that.

0 Kudos
andrew_4619
Honored Contributor III
3,029 Views

FORMATTED (not binary), direct access, but you have a fixed record length.

0 Kudos
Kevin_D_Intel
Employee
3,029 Views

I believe the 1450 being a system-level message: https://msdn.microsoft.com/en-us/library/windows/desktop/ms681385(v=vs.85).aspx, means ERROR_NO_SYSTEM_RESOURCES.

I wonder if this is related to the non-freeing of handles we have been hearing about from others in our PSXE 2016 release. Had you upgraded to PSXE 2016 or any other version recently?

 

0 Kudos
NotThatItMatters
Beginner
3,029 Views

I use that option (ACCESS = 'DIRECT', FORM = 'FORMATTED') ALL THE TIME with fixed record length lines which are formatted.  It turns out this file itself is NOT fixed record length, but as I said this "trick" is how I attempt to put the number of records at the beginning of this file when I do not know the number of records a priori but will know this at the end of the run.  And as I also said, the method has "always" worked.  I am just noting with the latest Fortran compiler (16.0) and one particular file, this is giving me problems.

0 Kudos
andrew_4619
Honored Contributor III
3,029 Views

I had not noticed the 1450 error code. Kevin could well be correct at #5. As the good doctor suggested in another post try:

subroutine check_handles
    USE IFWIN, only: handle, dword, GetCurrentProcess
    IMPLICIT NONE
    INTEGER(HANDLE)    :: ThisProcess
    INTEGER(DWORD)     :: ret, CurHandles
    interface ! not included in IFWIN module
        function GetProcessHandleCountX (hProcess, pdwHandleCount) BIND(C,NAME="GetProcessHandleCount")
            import
            integer(DWORD) :: GetProcessHandleCountX
            !DEC$ ATTRIBUTES STDCALL :: GetProcessHandleCountX
            integer(HANDLE), VALUE, INTENT(IN) :: hProcess
            integer(DWORD), INTENT(INOUT) :: pdwHandleCount
        end function GetProcessHandleCountX
    end interface
    ThisProcess = GetCurrentProcess()
    ret = GetProcessHandleCountX(ThisProcess, CurHandles)
    ! now output CurHandles in some useful way 
    !
end subroutine check_handles

And monitor what CurHandles is doing. I find on PSXE 16.0 it grows and grow and eventually the machine will crash. For this reason I cannot deploy anything built with with 16.0

0 Kudos
jimdempseyatthecove
Honored Contributor III
3,029 Views

Was the original first record of that file first written with the DIRECT and FORMATTED? (then presumably closed then reopened for sequential access).

Jim Dempsey

 

0 Kudos
NotThatItMatters
Beginner
3,029 Views

No.  The file was opened with

OPEN(UNIT = 10, FILE = FILENAME)

and then written with

WRITE(10,'(I6,1X,A10)') SENTINEL_VALUE, VERSION_INFO

SENTINEL_VALUE is just an INTEGER place holder.

0 Kudos
jimdempseyatthecove
Honored Contributor III
3,029 Views

I'd suggest you investigate STREAM formatted files. Look in the user documentation regarding "Record Types" to give you some background on the different record types. Then consult "stream WRITE statements".

Jim Dempsey

0 Kudos
mecej4
Honored Contributor III
3,029 Views

Just to make things clear, here is reconstructed code to reproduce the behavior in NotThatItMatters' description.

program countrecs
implicit none
integer i,j
integer kount   ! a number whose value depends on the number of records written to file
character(len=30) :: header='File XYZ written by PQR, nnnn '
!
! write formatted sequential file with dummy header line
!
open(unit=11,file='myda.txt',status='replace')
write(11,'(A)')header       !place holder
kount=1
do i=1,11
   j=i*i*i+(102-i)*(102-i)
   write(11,100)i,j
   kount=kount+i
end do
close(11)
!
! update header with correct Kount
!
write(header(26:29),'(i4)')kount  ! revised header line
!
! reopen file and write updated header line as first "direct" record
!
open(unit=11,file='myda.txt',form='formatted',access='direct',recl=len(header))
write(11,fmt='(A)',rec=1)header
close(11)
100 format('This is record ',I,' tag: ',I0)
end program

Quite a bit of trickery to get around the fact that a sequential access formatted file will receive an unwanted end-of-file following the last WRITE to it. Part of the blame goes to using file/disk paradigms, originally designed into Fortran to work on mainframes with tape and other record oriented storage devices, on operating systems with a  "getta byte, getta byte, getta byte byte byte" philosophy (dirisive comment attributed to Dave Cutler, one of the architects of NT, see https://en.wikipedia.org/wiki/Dave_Cutler ).

If we can have circular (ring) buffers, why can't we have circular (ring) files?

0 Kudos
NotThatItMatters
Beginner
3,029 Views

Thank you all.  I put the check_handles code snippet in my code and outputted every time step.  The handles grow, grow, grow until they reach CurHandles 16711680 for the last 6841 time steps.  The crash then happens.

 

0 Kudos
Kevin_D_Intel
Employee
3,029 Views

Thank you mecej4. Your reconstructed test case with the 16.0 compiler does exhibit the increase in handles across the complete execution confirming this is another instance related to the handle leak others have reported. With 15.0, the number of handles increases/decreases across the entire execution.

https://software.intel.com/en-us/forums/intel-visual-fortran-compiler-for-windows/topic/593874
https://software.intel.com/en-us/forums/topic/591225
https://software.intel.com/en-us/forums/topic/590293

I added this as another instance and elevated the impact of this issue to help expedite a fix.

I don't know how much this might help, but the issue is avoidable with non-multithreaded libraries (/nothreads).

(Internal tracking id: DPD200375683)

(Resolution Update on 11/26/2015): This defect is fixed in the Intel® Parallel Studio XE 2016 Update 1 Release (PSXE 2016.1.051 / CnL 2016.1.146 - Windows)

0 Kudos
andrew_4619
Honored Contributor III
3,029 Views

@kevin: What is the effect of  /nothreads vs /threads (default option it would seem) compile option? I have just hunted for some info and failed :-(

0 Kudos
mecej4
Honored Contributor III
3,029 Views

I combined the source codes in #7 and #11 to answer the question in #14. The code outputs handle counts of zero when compiled with /nothreads and either IFort 15.0.4 or 16.0.0. Without /nothreads, it gives handle counts of 4 every iteration using 15.0.4, whereas the handle counts increase from 5 to 35 over 10 iterations using 16.0.0.

program countrecs
implicit none
integer i,j,ihndl,i0h,iter
integer kount   ! a number whose value depends on the number of records written to file
character(len=30) :: header='File XYZ written by PQR, nnnn '
!
! write formatted sequential file with dummy header line
!
call Check_Handles(i0h)  ! initial handle count
do iter=1,10
   open(unit=11,file='myda.txt',status='replace')
   write(11,'(A)')header       !place holder
   kount=1
   do i=1,10
      j=i*i*i+(102-i)*(102-i)
      write(11,100)i,j
      kount=kount+i
   end do
   close(11)
   !
   ! update header with correct Kount
   !
   write(header(26:29),'(i4)')kount  ! revised header line
   !
   ! reopen file and write updated header line as first "direct" record
   !
   open(unit=11,file='myda.txt',form='formatted',access='direct',recl=len(header))
   write(11,fmt='(A)',rec=1)header
   close(11)
   call Check_Handles(ihndl)
   write(*,'(1x,2I10)')iter,ihndl-i0h
end do
100 format('This is record ',I0,' tag: ',I0)
end program

subroutine check_handles(CurHandles)
    USE IFWIN, only: handle, dword, GetCurrentProcess
    IMPLICIT NONE
    INTEGER(HANDLE)    :: ThisProcess
    INTEGER(DWORD)     :: ret, CurHandles
    interface ! not included in IFWIN module
        function GetProcessHandleCountX (hProcess, pdwHandleCount) BIND(C,NAME="GetProcessHandleCount")
            import
            integer(DWORD) :: GetProcessHandleCountX
            !DEC$ ATTRIBUTES STDCALL :: GetProcessHandleCountX
            integer(HANDLE), VALUE, INTENT(IN) :: hProcess
            integer(DWORD), INTENT(INOUT) :: pdwHandleCount
        end function GetProcessHandleCountX
    end interface
    ThisProcess = GetCurrentProcess()
    ret = GetProcessHandleCountX(ThisProcess, CurHandles)
    return
end subroutine check_handles

 

0 Kudos
Kevin_D_Intel
Employee
3,029 Views

@app4619 - /threads and /nothreads are covered here, https://software.intel.com/en-us/node/579624. The effect of the latter is to link with a non-multithreaded library.

The docs don't specifically mention what happens under the hood but you can see this with the linker's Show Progress (/VERBOSE:LIB) option. Adding /nothreads in the Additional Options under the IDE or via the command using say /libs:dll /nothreads along with the linker option, the resulting difference is linking libifcorertd.lib (for /nothreads) versus the default libifcorermd.lib.

0 Kudos
andrew_4619
Honored Contributor III
3,029 Views

Is /nothreads actually compatible with a windows application ( /SUBSYSTEM:WINDOWS )?  And  how do you set it In VS? Under the project properties > fortran > Libraries there are a number of options no none with /nothreads. I put .nothreads on the command line entry and got a warning about overriding threads for each source file.  

ifort /nologo /debug:full /Od /stand:f08 /Qdiag-disable:7025,5142,6477 /warn:declarations /warn:unused /warn:truncated_source /warn:interfaces /module:"Debug\\" /object:"Debug\\" /Fd"Debug\vc120.pdb" /traceback /check:bounds /check:stack /libs:static /threads /dbglibs /c /nothreads /Qlocation,link,....
ifort: command line warning #10121: overriding '/threads' with '/nothreads'

but it did build and run. The handles creep seemed unchanged though.......

 

 

0 Kudos
mecej4
Honored Contributor III
3,029 Views

app4619 wrote:

...

ifort /nologo /debug:full /Od /stand:f08 /Qdiag-disable:7025,5142,6477 /warn:declarations /warn:unused /warn:truncated_source /warn:interfaces /module:"Debug\\" /object:"Debug\\" /Fd"Debug\vc120.pdb" /traceback /check:bounds /check:stack /libs:static /threads /dbglibs /c /nothreads /Qlocation,link,....
ifort: command line warning #10121: overriding '/threads' with '/nothreads'

but it did build and run. The handles creep seemed unchanged though.......

Did you specify /nothreads in the ifort invocation that did the linking, as well? If not, more overriding of libraries specified in OBJ files may have taken place. You could check the EXE file with the Dependency Tool, if you have it.

0 Kudos
DavidWhite
Valued Contributor II
3,029 Views

I'm seeing similar handles problems in my applications.

In one, applying /nothreads resulted in the number of handles being reduced from up to 5 million to around 400.  I'm happy with this.

However, in the other, the number of handles keeps increasing, and since this may be applied in an environment where it does not get restarted very often, I would like to know if there is anything else I need to change.

I can't see that either Libifcorermd or Libifcorertd are linked into the application.  The only one I can find is libifcoremt.  Is this one OK?

Thanks,

David

0 Kudos
andrew_4619
Honored Contributor III
3,029 Views

Thanks for the suggestions mecej4 but on further inspection for each source we get:

1>ifort: command line warning #10121: overriding '/threads' with '/nothreads'
1>ifort: warning #10153: option '/ML' has been replaced with '/MT'

MTd is /libs:static /threads /dbglibs so it looks like the nothreads option is rejected at compile time. Which is back to my earlier question - Is /nothreads actually compatible with a windows application ( /SUBSYSTEM:WINDOWS )?  I would suspect not.

 

0 Kudos
andrew_4619
Honored Contributor III
2,901 Views

...and looking at \verbose:lib link output it links with the MT libs which is why I see no change in behaviour.

0 Kudos
Reply