Skip to content

Commit

Permalink
NWTClib: call GetNewUnit in every file open command
Browse files Browse the repository at this point in the history
Add `!$OMP critical` around all `GetNewUnit` + `open(*)` call pairs
  • Loading branch information
andrew-platt committed Nov 28, 2024
1 parent 4943c19 commit 77bca40
Showing 1 changed file with 39 additions and 36 deletions.
75 changes: 39 additions & 36 deletions modules/nwtc-library/src/NWTC_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2309,7 +2309,7 @@ SUBROUTINE OpenBInpFile ( Un, InFile, ErrStat, ErrMsg )

! Argument declarations.

INTEGER(IntKi), INTENT(IN) :: Un !< Logical unit for the input file.
INTEGER(IntKi), INTENT(INOUT) :: Un !< Logical unit for the input file.
INTEGER(IntKi), INTENT(OUT) :: ErrStat !< Error status: returns "fatal" if the file doesn't exist or can't be opened
CHARACTER(*), INTENT(OUT) :: ErrMsg !< Error message
CHARACTER(*), INTENT(IN) :: InFile !< Name of the input file.
Expand Down Expand Up @@ -2339,7 +2339,10 @@ SUBROUTINE OpenBInpFile ( Un, InFile, ErrStat, ErrMsg )


! Open input file. Make sure it worked.
!$OMP critical
call GetNewUnit(Un,ErrStat,ErrMsg); if (ErrStat >= AbortErrLev) return
OPEN( Un, FILE=TRIM( InFile ), STATUS='OLD', FORM='UNFORMATTED', ACCESS='STREAM', IOSTAT=ErrStat, ACTION='READ' )
!$OMP end critical

IF ( ErrStat /= 0 ) THEN
ErrStat = ErrID_Fatal
Expand All @@ -2360,15 +2363,18 @@ SUBROUTINE OpenBOutFile ( Un, OutFile, ErrStat, ErrMsg )

! Argument declarations.

INTEGER(IntKi), INTENT(IN) :: Un !< Logical unit for the output file
INTEGER(IntKi), INTENT(INOUT) :: Un !< Logical unit for the output file
INTEGER(IntKi), INTENT(OUT) :: ErrStat !< Error status
CHARACTER(*), INTENT(OUT) :: ErrMsg !< Error message
CHARACTER(*), INTENT(IN) :: OutFile !< Name of the output file



! Open output file. Make sure it worked.
!$OMP critical
call GetNewUnit(Un,ErrStat,ErrMsg); if (ErrStat >= AbortErrLev) return
OPEN( Un, FILE=TRIM( OutFile ), STATUS='UNKNOWN', FORM='UNFORMATTED' , ACCESS='STREAM', IOSTAT=ErrStat, ACTION='WRITE' )
!$OMP end critical

IF ( ErrStat /= 0 ) THEN
ErrStat = ErrID_Fatal
Expand Down Expand Up @@ -2407,21 +2413,14 @@ SUBROUTINE OpenEcho ( Un, OutFile, ErrStat, ErrMsg, ProgVer )
ErrMsg = ''


! Get a unit number for the echo file:

IF ( Un < 0 ) THEN
CALL GetNewUnit( Un, ErrStat2, ErrMsg2 )
CALL SetErrStat(ErrStat2, ErrMsg2,ErrStat, ErrMsg, RoutineName )
END IF


! Open the file for writing:

!$OMP critical
call GetNewUnit(Un,ErrStat,ErrMsg); if (ErrStat >= AbortErrLev) return
CALL OpenFOutFile( Un, OutFile, ErrStat2, ErrMsg2 )
!$OMP end critical
CALL SetErrStat(ErrStat2, ErrMsg2,ErrStat, ErrMsg, RoutineName )
IF ( ErrStat >= AbortErrLev ) RETURN


! Write a heading line to the file

IF ( PRESENT( ProgVer ) ) THEN
Expand All @@ -2444,7 +2443,7 @@ SUBROUTINE OpenFInpFile ( Un, InFile, ErrStat, ErrMsg )

! Argument declarations.

INTEGER, INTENT(IN) :: Un !< Logical unit for the input file.
INTEGER, INTENT(INOUT) :: Un !< Logical unit for the input file.
CHARACTER(*), INTENT(IN) :: InFile !< Name of the input file.
INTEGER(IntKi), INTENT(OUT) :: ErrStat !< Error status
CHARACTER(*), INTENT(OUT) :: ErrMsg !< Error message
Expand All @@ -2470,8 +2469,10 @@ SUBROUTINE OpenFInpFile ( Un, InFile, ErrStat, ErrMsg )
ELSE

! Open input file. Make sure it worked.

!$OMP critical
call GetNewUnit(Un,ErrStat,ErrMsg); if (ErrStat >= AbortErrLev) return
OPEN( Un, FILE=TRIM( InFile ), STATUS='OLD', FORM='FORMATTED', IOSTAT=IOS, ACTION='READ' )
!$OMP end critical

IF ( IOS /= 0 ) THEN
CALL SetErrStat( ErrID_Fatal, 'Cannot open file "'//TRIM( InFile )//'".', ErrStat,ErrMsg,RoutineName)
Expand All @@ -2488,7 +2489,7 @@ SUBROUTINE OpenFOutFile ( Un, OutFile, ErrStat, ErrMsg )

! Argument declarations.

INTEGER, INTENT(IN) :: Un !< Logical unit for the output file.
INTEGER, INTENT(INOUT) :: Un !< Logical unit for the output file.
CHARACTER(*), INTENT(IN) :: OutFile !< Name of the output file.

INTEGER(IntKi), INTENT(OUT) :: ErrStat !< Error status
Expand All @@ -2503,8 +2504,10 @@ SUBROUTINE OpenFOutFile ( Un, OutFile, ErrStat, ErrMsg )


! Open output file. Make sure it worked.

!$OMP critical
call GetNewUnit(Un,ErrStat,ErrMsg); if (ErrStat >= AbortErrLev) return
OPEN( Un, FILE=TRIM( OutFile ), STATUS='UNKNOWN', FORM='FORMATTED', IOSTAT=IOS, ACTION="WRITE" )
!$OMP end critical


IF ( IOS /= 0 ) THEN
Expand All @@ -2525,7 +2528,7 @@ SUBROUTINE OpenFUnkFile ( Un, OutFile, FailAbt, Failed, Exists, ErrStat, ErrMsg

! Argument declarations.

INTEGER, INTENT(IN) :: Un !< Logical unit for the output file.
INTEGER, INTENT(INOUT) :: Un !< Logical unit for the output file.
INTEGER(IntKi), INTENT(OUT) :: ErrStat !< Error status: returns "fatal" if the file doesn't exist or can't be opened
CHARACTER(*), INTENT(OUT) :: ErrMsg !< Error message

Expand All @@ -2548,8 +2551,10 @@ SUBROUTINE OpenFUnkFile ( Un, OutFile, FailAbt, Failed, Exists, ErrStat, ErrMsg


! Open output file. Make sure it worked.

!$OMP critical
call GetNewUnit(Un,ErrStat,ErrMsg); if (ErrStat >= AbortErrLev) return
OPEN( Un, FILE=TRIM( OutFile ), STATUS='UNKNOWN', FORM='FORMATTED', IOSTAT=IOS )
!$OMP end critical


IF ( IOS /= 0 ) THEN
Expand All @@ -2572,7 +2577,7 @@ SUBROUTINE OpenFUnkFileAppend ( Un, OutFile, ErrStat, ErrMsg )

! Argument declarations.

INTEGER, INTENT(IN) :: Un ! Logical unit for the output file.
INTEGER, INTENT(INOUT) :: Un ! Logical unit for the output file.
CHARACTER(*), INTENT(IN) :: OutFile ! Name of the output file.

INTEGER(IntKi), INTENT(OUT), OPTIONAL :: ErrStat ! Error status; if present, program does not abort on error
Expand All @@ -2590,11 +2595,14 @@ SUBROUTINE OpenFUnkFileAppend ( Un, OutFile, ErrStat, ErrMsg )

inquire(file=TRIM( OutFile ), exist=FileExists)

!$OMP critical
call GetNewUnit(Un,ErrStat,ErrMsg); if (ErrStat >= AbortErrLev) return
if (FileExists) then
OPEN( Un, FILE=TRIM( OutFile ), STATUS='OLD', POSITION='APPEND', FORM='FORMATTED', IOSTAT=IOS, ACTION="WRITE" )
else
OPEN( Un, FILE=TRIM( OutFile ), STATUS='UNKNOWN', FORM='FORMATTED', IOSTAT=IOS, ACTION="WRITE" )
end if
!$OMP end critical


IF ( IOS /= 0 ) THEN
Expand Down Expand Up @@ -2623,7 +2631,7 @@ SUBROUTINE OpenUInBEFile( Un, InFile, RecLen, ErrStat, ErrMsg )

! Argument declarations.

INTEGER, INTENT(IN) :: Un !< Logical unit for the input file
INTEGER, INTENT(INOUT) :: Un !< Logical unit for the input file
CHARACTER(*), INTENT(IN) :: InFile !< Name of the input file
INTEGER, INTENT(IN) :: RecLen !< The input file's record length in bytes
INTEGER(IntKi), INTENT(OUT) :: ErrStat !< Error status: returns "fatal" if the file doesn't exist or can't be opened
Expand All @@ -2649,8 +2657,10 @@ SUBROUTINE OpenUInBEFile( Un, InFile, RecLen, ErrStat, ErrMsg )


! Open the file.

!$OMP critical
call GetNewUnit(Un,ErrStat,ErrMsg); if (ErrStat >= AbortErrLev) return
CALL OpenUnfInpBEFile ( Un, InFile, RecLen, Error )
!$OMP end critical

IF ( Error ) THEN
ErrStat = ErrID_Fatal
Expand All @@ -2671,7 +2681,7 @@ SUBROUTINE OpenUInfile ( Un, InFile, ErrStat, ErrMsg )

! Argument declarations.

INTEGER, INTENT(IN) :: Un !< Logical unit for the input file
INTEGER, INTENT(INOUT) :: Un !< Logical unit for the input file
INTEGER(IntKi), INTENT(OUT) :: ErrStat !< Error status: returns "fatal" if the file doesn't exist or can't be opened
CHARACTER(*), INTENT(OUT) :: ErrMsg !< Error message

Expand All @@ -2698,8 +2708,10 @@ SUBROUTINE OpenUInfile ( Un, InFile, ErrStat, ErrMsg )


! Open the file.

!$OMP critical
call GetNewUnit(Un,ErrStat,ErrMsg); if (ErrStat >= AbortErrLev) return
OPEN ( Un, FILE=TRIM( InFile ), STATUS='UNKNOWN', FORM=UnfForm, ACCESS='SEQUENTIAL', IOSTAT=IOS, ACTION='READ' )
!$OMP end critical

IF ( IOS /= 0 ) THEN
ErrStat = ErrID_Fatal
Expand All @@ -2718,7 +2730,7 @@ SUBROUTINE OpenUOutfile ( Un, OutFile, ErrStat, ErrMsg )

! Argument declarations.

INTEGER, INTENT(IN) :: Un !< Logical unit for the output file
INTEGER, INTENT(INOUT) :: Un !< Logical unit for the output file
INTEGER(IntKi), INTENT(OUT) :: ErrStat !< Error status: returns "fatal" if the file doesn't exist or can't be opened
CHARACTER(*), INTENT(OUT) :: ErrMsg !< Error message

Expand All @@ -2732,8 +2744,10 @@ SUBROUTINE OpenUOutfile ( Un, OutFile, ErrStat, ErrMsg )


! Open the file.

!$OMP critical
call GetNewUnit(Un,ErrStat,ErrMsg); if (ErrStat >= AbortErrLev) return
OPEN ( Un, FILE=TRIM( OutFile ), STATUS='UNKNOWN', FORM=UnfForm, ACCESS='SEQUENTIAL', IOSTAT=IOS, ACTION='WRITE' )
!$OMP end critical

IF ( IOS /= 0 ) THEN
ErrStat = ErrID_Fatal
Expand Down Expand Up @@ -4615,9 +4629,6 @@ RECURSIVE SUBROUTINE ReadComFile ( FileInfo, FileIndx, AryInd, StartLine, LastLi
RETURN
END IF

CALL GetNewUnit ( UnIn, ErrStatLcl, ErrMsg2 )
CALL SetErrStat( ErrStatLcl, ErrMsg2, ErrStat, ErrMsg, RoutineName )

CALL OpenFInpFile ( UnIn, FileInfo%FileList(FileIndx), ErrStatLcl, ErrMsg2 )
CALL SetErrStat( ErrStatLcl, ErrMsg2, ErrStat, ErrMsg, RoutineName )
IF ( ErrStat >= AbortErrLev ) RETURN
Expand Down Expand Up @@ -4846,7 +4857,6 @@ SUBROUTINE ReadFASTbin ( UnIn, Init, FASTdata, ErrStat, ErrMsg )


! Open data file.

CALL OpenBInpFile ( UnIn, FASTdata%File, ErrStat2, ErrMsg2 )
CALL SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName )
IF (ErrStat >= AbortErrLev) THEN
Expand All @@ -4855,15 +4865,12 @@ SUBROUTINE ReadFASTbin ( UnIn, Init, FASTdata, ErrStat, ErrMsg )
END IF



! Process the requested data records of this file.

CALL WrScr ( NewLine//' =======================================================' )
CALL WrScr ( ' Reading in data from file "'//TRIM( FASTdata%File )//'".'//NewLine )


! Read some of the header information.

READ (UnIn, IOSTAT=ErrStat2) FileType
IF ( ErrStat2 /= 0 ) THEN
CALL SetErrStat ( ErrID_Fatal, 'Fatal error reading FileType from file "'//TRIM( FASTdata%File )//'".', ErrStat, ErrMsg, RoutineName )
Expand Down Expand Up @@ -6410,8 +6417,6 @@ RECURSIVE SUBROUTINE ScanComFile ( FirstFile, ThisFile, LastFile, StartLine, Las

! Open the input file.
UnIn = -1
CALL GetNewUnit ( UnIn, ErrStatLcl, ErrMsg2 )

CALL OpenFInpFile ( UnIn, Filename, ErrStatLcl, ErrMsg2 )
IF ( ErrStatLcl /= 0 ) THEN
CALL SetErrStat( ErrStatLcl, ErrMsg2, ErrStat, ErrMsg, RoutineName )
Expand Down Expand Up @@ -6720,8 +6725,6 @@ SUBROUTINE WrBinFAST(FileName, FileID, DescStr, ChanName, ChanUnit, TimeData, Al

! Generate the unit number for the binary file
UnIn = 0
CALL GetNewUnit( UnIn, ErrStat2, ErrMsg2 )
CALL SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName )

!...............................................................................................................................
! Open the binary file for output
Expand Down

0 comments on commit 77bca40

Please sign in to comment.