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

bug with open statement

jvandeven
New Contributor I
6,859 Views

I recently upgraded to VS2015 and IVF Composer 2016.  Since upgrading the Fortran compiler, the application I work with returns error code 30 on an OPEN statement.  A file is created, but cannot be written to.  I have tried various permutations of the OPEN statement including:

call get_unit( file_id )
open ( unit = file_id, file = file_name, status = 'replace', iostat = istat )
if ( istat.ne.0 ) then

    open ( newunit = file_id, file = file_name, status = 'replace', action = 'write', iostat = istat )
    open ( newunit = file_id, file = file_name, status = 'replace', iostat = istat )
    open ( newunit = file_id, file = file_name, iostat = istat )

None of these seems to help.  The affected code writes output to a number of CSV (comma separated varaible) files.  The OPEN statement works fine to begin with, but appears to fail after a sufficiently large number of data points have been written to disk (ie, it will write 10 variables of size X, and 8 variables of size Y, where Y>X).  I am returning to IVF Composer 2015, update 4 - which processes the data without incident - until this problem can be resolved.

I have tried doing a complete rebuild (both after "cleaning" the solution, and deleting the x64 working directory), tried working on different drives, tried rebooting the computer, and tried working on different computers.  None of these quick fixes helped.

Hope that someone is able to identify the root cause of this issue,

Justin.

 

0 Kudos
54 Replies
andrew_4619
Honored Contributor III
3,140 Views

The problem definition  is not 100% clear to me , you open a file, your write some data and then subsequent writes fail, is that it? That being the case it the the writes that fail not the open? What error code is generated if any, do the writes have IOSTAT reported?

 

0 Kudos
jvandeven
New Contributor I
3,140 Views

I provide some of the relevant code here for clarity - the error comes up in the OPEN statement of the SUBROUTINE csv_file_write_r, with IOSTAT = 30.

I have spent the whole day on this problem, and any help would be much appreciated...

SUBROUTINE 1

        csv_variable = alc_dy(1:pop_numb_h,1:SamplePeriodAll)
        grid_filename = trim(job_dir) // '\alc_dy.csv' //char(0)
        call csv_file_write_r( grid_filename, 2 )
    
        csv_variable = ful_dy(1:pop_numb_h,1:SamplePeriodAll)
        grid_filename = trim(job_dir) // '\ful_dy.csv' //char(0)
        call csv_file_write_r( grid_filename, 2 )
    
        csv_variable = ihr_dy(1:pop_numb_h,1:SamplePeriodAll)
        grid_filename = trim(job_dir) // '\ihr_dy.csv' //char(0)
        call csv_file_write_r( grid_filename, 2 )

        csv_variable = isr_dy(1:pop_numb_h,1:SamplePeriodAll)
        grid_filename = trim(job_dir) // '\isr_dy.csv' //char(0)
        call csv_file_write_r( grid_filename, 2 )
    
        csv_variable = tbc_dy(1:pop_numb_h,1:SamplePeriodAll)
        grid_filename = trim(job_dir) // '\tbc_dy.csv' //char(0)
        call csv_file_write_r( grid_filename, 2 )

END SUBROUTINE 1

SUBROUTINE csv_file_write_r

!*************************************************************
!
!    CSV_FILE_WRITE_R writes real data to CSV file
!
!  Modified:
!
!    28 APRIL 2015
!
!  Author:
!
!    Justin van de Ven
!
!  Parameters:
!
!    file_name        : full name of file to be saved
!    flag            : 0 if unassigned, 1 if integer, 2 if currency, 3 if other real
!    mm                : number of rows in matrix
!    nn                : number of cols in matrix
!    sig_figs        : significant figures to save for (other) real variable (OPTIONAL)
!
!*************************************************************

USE simulated_data
USE global_ParamStore
USE global_CommonAll
USE global_csv_file_rw

IMPLICIT none


integer(4), intent(in) :: flag
integer(4), intent(in), optional :: sig_figs
character(*) :: file_name

! local variables
integer(4) :: file_id, istat, ii, jj
character(csv_rw_nn*24) :: output_line


!*************************************************************
!    begin code
!*************************************************************


!*************************************************************
!    open file to write to
!*************************************************************
call get_unit( file_id )
open ( newunit = file_id, file = file_name, status = 'replace', action = 'write', iostat = istat )
if ( istat.ne.0 ) then

    !$OMP CRITICAL(error_1)
        print *, 'error writing CSV file'
        print *, 'could not open "' // trim ( file_name ) // '".'
        pause 'press enter to exit'
        continue
        stop
        continue
    !$OMP END CRITICAL(error_1)
end if


!*************************************************************
!    write output to file
!*************************************************************
do ii = 1, csv_rw_mm

    output_line = '  '
    do jj = 1, csv_rw_nn
    
        call csv_data_append( flag, csv_variable(ii,jj), output_line, sig_figs )
    end do
    write ( file_id, '(a)' ) trim ( output_line )
end do
close ( file_id, status = 'save', iostat = istat )
if ( istat.ne.0 ) then

    continue
end if

END SUBROUTINE csv_file_write_r

0 Kudos
andrew_4619
Honored Contributor III
3,140 Views

You are opening a file writing and then closing it and then repeating the process. The file fails to open because Windows has not released it from the last write/close, there is often some delay. If when you have the open fail error you have a short wait and try again it will probably open OK. This is a common problem and you will find some other threads on the same subject in the forum though they may be hard to find as the descriptions are often not that specific.

 

0 Kudos
jvandeven
New Contributor I
3,140 Views

That would make sense if I was writing to the same file in each iteration.  But I am writing to a series of *.csv files (alc_dy.csv, ful_dy.csv, ihr_dy.csv, isr_dy.csv, tbc_dy.csv in the above example).  Furthermore, in the debugger, I have tried going back and forth through the code to find some combination of commands that will work, and there is substantial delay between executions in that case, none of which makes any difference.  As soon as the IOSTAT = 30 error pops up, no further instances of the OPEN statement work - all return the IOSTAT = 30 error.

0 Kudos
Arjen_Markus
Honored Contributor II
3,140 Views

Your call to get_unit is superfluous, due to the use of the newunit keyword. But your use of !$OMP CRITICAL suggests that you are using OpenMP. Could it be that you enter a race condition? I think the critical section should be the output entire routine or at least the OPEN statement.

0 Kudos
andrew_4619
Honored Contributor III
3,140 Views

Interesting. I note you are using NEWUNIT is the unit number always coming back as the same number for each open?

Is there some issue with runing out of system resources, e.g. windows file handles?

What is the job_dir, does it have any restriction? e.g. on some windows there are a maximum number of files in the root folder.

I am in the zone of wild guessing BTW....

0 Kudos
jvandeven
New Contributor I
3,140 Views

arjenmarkus wrote:

Your call to get_unit is superfluous, due to the use of the newunit keyword. But your use of !$OMP CRITICAL suggests that you are using OpenMP. Could it be that you enter a race condition? I think the critical section should be the output entire routine or at least the OPEN statement.

That's true - I have only added "newunit" recently, in an effort to resolve this problem, having previously relied upon a routine I wrote some time ago to ensure that an appropriate file unit was selected.  Also, the OMP statement defined in the code is somewhat unnecessary, as the portion of the code that calls this routine is not parallelised (it is added just in case.

 

0 Kudos
jvandeven
New Contributor I
3,140 Views

app4619 wrote:

Interesting. I note you are using NEWUNIT is the unit number always coming back as the same number for each open?

Is there some issue with runing out of system resources, e.g. windows file handles?

What is the job_dir, does it have any restriction? e.g. on some windows there are a maximum number of files in the root folder.

I am in the zone of wild guessing BTW....

No the unit number isn't always comming up with the same number (my original code routinely set the unit number to 1, and I thought this might be causing the problem, even though there is a close statement between uses).

I am unsure about the possibility of "running out of system resources" - I recently updated to Windows 2010, but this code worked fine on that OS with the 2015.4 compiler.  There is no restriction on "job_dir".

Your guess is a bit better than mine at present, as I have run out of ideas...

0 Kudos
Arjen_Markus
Honored Contributor II
3,140 Views

Hm, perhaps you should opt for a different solution: open the files once and pass the relevant LU-number to the subroutine. To "ensure" (*) that the data have been written to the files, you can use the flush statement.

(*) Always to discretion of the operating system which may have completely different ideas about file management than you.

 

0 Kudos
jvandeven
New Contributor I
3,140 Views

arjenmarkus wrote:

Hm, perhaps you should opt for a different solution: open the files once and pass the relevant LU-number to the subroutine. To "ensure" (*) that the data have been written to the files, you can use the flush statement.

(*) Always to discretion of the operating system which may have completely different ideas about file management than you.

 

If I understand you correctly, you are suggesting that I collect a full set of unit numbers before starting to write the output (otherwise there isn't much difference to what I have been doing).  This work-around might work, but will result in very messy code, as there are a lot of individual files to write.  It is also a problem that is likely to pop up elsewhere in my code, introducing a great deal of scope for error...

0 Kudos
andrew_4619
Honored Contributor III
3,140 Views

OK before the open statement add a sleep or sleepqq to put in a long delay e.g. 2000mS and see if the problem goes away. If it does than it very strongly suggests it is a timing problem.

 

0 Kudos
andrew_4619
Honored Contributor III
3,140 Views

When  you updated to 2016 did you keep 2015 update 4? If so in VS  "tools > options > Intel compiler and tools >  Visual Fortran > compilers" you can select the older compiler and then do a full rebuild to see if it is version specific as you indicate it might be in the OP.

 

0 Kudos
jvandeven
New Contributor I
3,140 Views

app4619 wrote:

When  you updated to 2016 did you keep 2015 update 4? If so in VS  "tools > options > Intel compiler and tools >  Visual Fortran > compilers" you can select the older compiler and then do a full rebuild to see if it is version specific as you indicate it might be in the OP.

 

Unfortunately I didn't - I just tried uninstalling IVF 2016, and re-installing 2015.4, but the install window for 2015.4 closed without proceeding.  I figured that there is a conflict somewhere, and am now doing a complete uninstall of both VS and IVF, and reinstalling to 2015.4.  

Also, adding a lag didn't help...

 

0 Kudos
jvandeven
New Contributor I
3,140 Views

Having re-installed the 2015.4 compiler, and re-run my test case, I can confirm that the OPEN IOSTAT=30 error code only appears in my application when the 2016.0 compiler is used (everything else being unchanged, including the code, OS, and debug environment VS2015).  As noted above, this issue only seems to arise when multiple files, each with fairly sizeable data sets, are written.  I found no problem writing a lot of data (e.g. 10+GB) in just a few files.  It is the combination of multiple files, with sizeable datasets.  I hope that someone is able to track down the source of this issue.

0 Kudos
andrew_4619
Honored Contributor III
3,140 Views

sounds like it could be a Fortran/system bug relating to buffering data or the like. Is there a test case you could submit via premier support maybe? 

0 Kudos
jimdempseyatthecove
Honored Contributor III
3,140 Views

Some portions of your code are missing. Use the {...} code button to insert code examples (e.g. the argument list to your subroutine is missin).

Due to missing code, unknown to us is what happens in csv_data_append with respect to the size of output_line and the passing of the missing optional argument sig_figs.

Have you compiled this with the interface checking?

In your error block (where you have continue) make a function call to GETLASTERROR() to see what it returns.

Also try using a fixed unit number. Some of the versions of the compiler had issues with get_unit and newunit (I think it was an integer(1) rollover issue).

Jim Dempsey

0 Kudos
jvandeven
New Contributor I
3,140 Views

Thanks for your reply Jim.  I provide more detail of the code here.  First, in the calling subroutine, pop_numb_h = 95000 and SamplePeriodAll = 100.  csv_variable is type real, and is a global variable, accessible both to the calling subroutine, and the subroutine csv_file_write_r.  

CALLING SUBROUTINE:

 

csv_rw_mm = pop_numb_h
	csv_rw_nn = SamplePeriodAll
	allocate( csv_variable(csv_rw_mm,csv_rw_nn) )

	csv_variable = age(1:pop_numb_h,:)
	grid_filename = trim(job_dir) // '\age.csv' //char(0)
	call csv_file_write_r( grid_filename, 1 )

	if ( allocated( alc_dy ) ) then
		
		csv_variable = alc_dy(1:pop_numb_h,1:SamplePeriodAll)
		grid_filename = trim(job_dir) // '\alc_dy.csv' //char(0)
		call csv_file_write_r( grid_filename, 2 )
	
		csv_variable = ful_dy(1:pop_numb_h,1:SamplePeriodAll)
		grid_filename = trim(job_dir) // '\ful_dy.csv' //char(0)
		call csv_file_write_r( grid_filename, 2 )
	
		csv_variable = ihr_dy(1:pop_numb_h,1:SamplePeriodAll)
		grid_filename = trim(job_dir) // '\ihr_dy.csv' //char(0)
		call csv_file_write_r( grid_filename, 2 )

		csv_variable = isr_dy(1:pop_numb_h,1:SamplePeriodAll)
		grid_filename = trim(job_dir) // '\isr_dy.csv' //char(0)
		call csv_file_write_r( grid_filename, 2 )
	
		csv_variable = tbc_dy(1:pop_numb_h,1:SamplePeriodAll)
		grid_filename = trim(job_dir) // '\tbc_dy.csv' //char(0)
		call csv_file_write_r( grid_filename, 2 )

 

SUBROUTINES THAT WRITE THE OUTPUT

SUBROUTINE csv_file_write_r( file_name, flag, sig_figs )

!*************************************************************
!
!	CSV_FILE_WRITE_R writes real data to CSV file
!
!  Modified:
!
!    28 APRIL 2015
!
!  Author:
!
!    Justin van de Ven
!
!  Parameters:
!
!	file_name		: full name of file to be saved
!	flag			: 0 if unassigned, 1 if integer, 2 if currency, 3 if other real
!	mm				: number of rows in matrix
!	nn				: number of cols in matrix
!	sig_figs		: significant figures to save for (other) real variable (OPTIONAL)
!
!*************************************************************

USE simulated_data
USE global_ParamStore
USE global_CommonAll
USE global_csv_file_rw

IMPLICIT none


integer(4), intent(in) :: flag
integer(4), intent(in), optional :: sig_figs
character(*) :: file_name

! local variables
integer(4) :: file_id, istat, ii, jj
character(csv_rw_nn*24) :: output_line


!*************************************************************
!	begin code
!*************************************************************


!*************************************************************
!	open file to write to
!*************************************************************
open ( newunit = file_id, file = file_name, status = 'replace', action = 'write', iostat = istat )
if ( istat.ne.0 ) then

	!$OMP CRITICAL(error_1)
		print *, 'error writing CSV file'
		print *, 'could not open "' // trim ( file_name ) // '".'
		pause 'press enter to exit'
		continue
		stop
		continue
	!$OMP END CRITICAL(error_1)
end if


!*************************************************************
!	write output to file
!*************************************************************
do ii = 1, csv_rw_mm

	output_line = '  '
	do jj = 1, csv_rw_nn
	
		call csv_data_append( flag, csv_variable(ii,jj), output_line, sig_figs )
	end do
	write ( file_id, '(a)' ) trim ( output_line )
end do
close ( file_id, status = 'save', iostat = istat )
if ( istat.ne.0 ) then

    continue
end if


END SUBROUTINE csv_file_write_r
SUBROUTINE csv_data_append ( flag, datum, output_line, sig_figs )

!*************************************************************
!
! CSV_DATA_APPEND appends new variable onto the end of a CSV record.
!
!  Parameters:
!
!	flag:		0 = unassigned, 1 = integer, 2 = currency, 3 = real
!	datum:		number to be added to text file
!	output line: the CSV record
!	sig_figs:	number of significant figures to be written (for real numbers)
!
!*************************************************************

IMPLICIT none


integer(4), intent(in), optional :: sig_figs 
integer(4), intent(in) :: flag
real(8), intent(in) :: datum
character(*) :: output_line

! local variables
integer(4) :: ii, intgr, numb_width, flag_h, sig_figs1
character(20) :: fmat


!*************************************************************
!	begin code
!*************************************************************
! locate last used location in RECORD.
ii = len_trim ( output_line )
if ( present(sig_figs) ) then

	sig_figs1 = min(15,sig_figs)
else

	sig_figs1 = 5
end if

! append comma
if ( ii.gt.0 ) then
! not first record

	ii = ii + 1
    output_line(ii:ii) = ','
end if

! append value after identifying relevant detail
if ( datum.eq.0.0 ) then
! record as 0

	ii = ii + 1
	output_line(ii:ii) = '0'
else
	
	if ( flag.eq.0 ) then
		
		if ( datum.eq.real(idint(datum)) ) then
		! record as integer

			flag_h = 1
		else

			flag_h = 3
		end if
	else
		
		flag_h = flag
	end if
	if ( flag_h.eq.1 ) then
	! treat as integer
		
		intgr = nint( datum )
		call i4_width( numb_width, intgr )
		write ( fmat, '(a,i2,a)' ) '(i', numb_width, ')'
		write ( output_line(ii+1:ii+numb_width), fmat ) intgr
	elseif ( flag_h.eq.2 ) then
	! treat as currency
		
		call c_width( numb_width, datum )
		write ( fmat, '(a,i2,a)' ) '(f', numb_width, '.2)'
		write ( output_line(ii+1:ii+numb_width), fmat ) datum
	else
	! treat as general real

		if ( sig_figs1.le.5 ) then
			
			call r8_stat( fmat, flag_h, sig_figs1, numb_width, datum )
			if ( flag_h.eq.1 ) then
			! treat as an integer
			
				intgr = nint( datum )
				write ( output_line(ii+1:ii+numb_width), fmat ) intgr
			else
			
				write( output_line(ii+1:ii+numb_width), fmat ) datum
			end if
		else
			
			numb_width = 4 + sig_figs1 + 3
			write ( fmat, '(a,i2,a,i2,a)' ) '(1PG', numb_width,'.', sig_figs1,'E3)'
			write( output_line(ii+1:ii+numb_width), fmat ) datum
		end if
	end if
end if


END SUBROUTINE csv_data_append
SUBROUTINE r8_stat( fmat, flag_h, sig_figs1, numb_width, rr )

!*************************************************************
!
!  r8_stat returns the format (fmat), and "width" (numb_width) 
!  of a real variable (rr), upto significant figures (sig_figs)
!
!  date:
!    30 April 2015
!
!  Author:
!	 Justin van de Ven
!
!  Parameters:
!
!    Input, real(8) rr, the number whose width is desired.
!
!    Output, character(integer(4) numb_width, the number of characters
!    necessary to represent rr in base 10, including a negative
!    sign if necessary.
!
!*************************************************************

IMPLICIT none


integer(4) :: flag_h
integer(4), intent(in) :: sig_figs1
real(8), intent(in) :: rr
integer(4), intent(out) :: numb_width
character(20), intent(out) :: fmat

! local variables
integer(4) :: base10, sig_figs_h, dec_width, flag_fp, rr_int
real(8) :: rr_abs0, rr_abs1, rr_error


!*************************************************************
!	begin code
!*************************************************************
flag_h = 0
sig_figs_h = sig_figs1
rr_abs1 = abs(rr)
base10 = int(log(rr_abs1) / log(10.0))

if ( base10.lt.0 ) then
	
	rr_abs0 = rr_abs1 * (10.0 ** real(sig_figs_h-base10))
else
	
	rr_abs0 = rr_abs1 * (10.0 ** real(sig_figs_h-1-base10))
end if
rr_abs1 = real(nint(rr_abs0 / 10.0)) * 10.0
rr_error = rr_abs1 - rr_abs0
do while ( nint(rr_error).eq.0 ) 
	
	sig_figs_h = sig_figs_h - 1
	rr_abs0 = rr_abs1 / 10.0
	rr_abs1 = real(nint(rr_abs0 / 10.0)) * 10.0
	rr_error = rr_abs1 - rr_abs0
end do


!*************************************************************
!	determine whether Exponential or Fixed point decimal more efficient
!*************************************************************
if ( sig_figs_h.eq.1 ) then

	if ( (base10.lt.6).and.(base10.gt.-4) ) then
	! fixed point format
		
		flag_fp = 1
	else
	! exponential format
		
		flag_fp = 0
	end if
else
	
	if ( (base10.lt.(sig_figs_h+4)).and.(base10.gt.-3) ) then
	! fixed point format
		
		flag_fp = 1
	else
	! exponential format
		
		flag_fp = 0
	end if
end if


!*************************************************************
!	evaluate width and fmat identifiers
!*************************************************************
if ( flag_fp.eq.1 ) then
! fixed format 
	
	if ( base10.ge.(sig_figs_h-1) ) then
	! assign as integer

		flag_h = 1
		rr_int = nint(rr)
		call i4_width( numb_width, rr_int )
		write ( fmat, '(a,i2,a)' ) '(i', numb_width, ')'
	else
	! assign as a decimal

		dec_width = sig_figs_h - base10
		if ( abs(rr).gt.1 ) then
			
			dec_width = max(1, dec_width - 1)
		end if
		
		numb_width = max(0, base10) + 2 + dec_width
		if ( rr.lt.0.0 ) then
			
			numb_width = numb_width + 1
		end if
		write ( fmat, '(a,i2,a,i2,a)' ) '(f', numb_width, '.', dec_width, ')'
	end if
else
! exponential

	dec_width = 1 + max(0, sig_figs_h - 2)
	numb_width = 6 + dec_width
	if ( rr.lt.0.0 ) then
		
		numb_width = numb_width + 1
	end if
	write ( fmat, '(a,i2,a,i2,a)' ) '(ES', numb_width, '.', dec_width, ')'
end if


END SUBROUTINE r8_stat
SUBROUTINE i4_width( numb_width, ii )

!*************************************************************
!
! I4_WIDTH returns the "width" of an I4.
!
!  Discussion:
!
!    The width of an integer is the number of characters necessary to print it.
!
!    The width of an integer can be useful when setting the appropriate output
!    format for a vector or array of values.
!
!    An I4 is an integer ( kind = 4 ) value.
!
!  Example:
!
!		II  I4_WIDTH
!    -----  -------
!    -1234    5
!     -123    4
!      -12    3
!       -1    2
!        0    1
!        1    1
!       12    2
!      123    3
!     1234    4
!    12345    5
!
!  Licensing:
!
!    This code is distributed under the GNU LGPL license.
!
!  Modified:
!
!    30 April 2015
!
!  Author:
!
!    John Burkardt
!	 Justin van de Ven (modified)
!
!  Parameters:
!
!    Input, integer ( kind = 4 ) II, the number whose width is desired.
!
!    Output, integer ( kind = 4 ) numb_width, the number of characters
!    necessary to represent the integer in base 10, including a negative
!    sign if necessary.
!
!*************************************************************

IMPLICIT none


integer(4), intent(in) :: ii
integer(4), intent(out) :: numb_width

! local variables
integer(4) :: ii_abs, kk 


!*************************************************************
!	begin code
!*************************************************************
if ( ii.eq.0 ) then
	
	numb_width = 1
else
	
	ii_abs = abs(ii)
	numb_width = 0
	kk = 1
	do while ( ii_abs.ge.kk ) 
		
		numb_width = numb_width + 1
		kk = kk * 10
	end do
	if ( ii.lt.0 ) then
		
		numb_width = numb_width + 1
	end if
end if


END SUBROUTINE i4_width
SUBROUTINE c_width( numb_width, rr )

!*************************************************************
!
!  C_WIDTH returns the "width" of a currency variable rr
!
!  date:
!    30 April 2015
!
!  Author:
!	 Justin van de Ven
!
!  Parameters:
!
!    Input, real(8) rr, the number whose width is desired.
!
!    Output, integer(4) numb_width, the number of characters
!    necessary to represent rr in base 10, including a negative
!    sign if necessary.
!
!*************************************************************

IMPLICIT none


real(8), intent(in) :: rr
integer(4), intent(out) :: numb_width

! local variables
integer(4) :: rr_int


!*************************************************************
!	begin code
!*************************************************************
rr_int = nint(rr*100.0)
call i4_width( numb_width, rr_int )
numb_width = max(4, numb_width+1)


END SUBROUTINE c_width

 

0 Kudos
jvandeven
New Contributor I
3,140 Views

app4619 wrote:

sounds like it could be a Fortran/system bug relating to buffering data or the like. Is there a test case you could submit via premier support maybe? 

Could be.  Unfortunately, I cannot send the full routine to premier support.  I will try to manufacture something similar that replicates the problem as soon as I have a spare moment.

0 Kudos
jvandeven
New Contributor I
3,140 Views

jimdempseyatthecove wrote:

Have you compiled this with the interface checking?

In your error block (where you have continue) make a function call to GETLASTERROR() to see what it returns.

Also try using a fixed unit number. Some of the versions of the compiler had issues with get_unit and newunit (I think it was an integer(1) rollover issue).

If you are referring to the /warn:interfaces compiler option, then yes, I have this enabled.  

I was under the impression that GETLASTERROR() would just return the compiler text associated with the IOSTAT = 30 error code.  As I know what this is (albeit, not particularly informative), I have not run this routine.

The code originally set the unit number to 1 for all instances, closing one before opening the next.  I only introduced the newunit option in case the unit number was somehow being corrupted.  This option seems to set a different (negative) integer in just about every instance it is used.

0 Kudos
andrew_4619
Honored Contributor III
3,024 Views

GETLASTERROR() will return a windows error rather than a Fortran error code so it might give some insight or maybe not.....

0 Kudos
Reply