Skip to content

Commit

Permalink
Set file units to -1 before calling file open* subs
Browse files Browse the repository at this point in the history
  • Loading branch information
andrew-platt committed Dec 3, 2024
1 parent 0548e92 commit bccfe13
Show file tree
Hide file tree
Showing 64 changed files with 177 additions and 75 deletions.
3 changes: 2 additions & 1 deletion glue-codes/fast-farm/src/FAST_Farm_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -73,6 +73,7 @@ SUBROUTINE Farm_PrintSum( farm, WD_InputFileData, ErrStat, ErrMsg )
CHARACTER(100) :: strModDescr

! Open the summary file and give it a heading.
UnSum = -1 ! set to -1 at start to find valid unit numbers in Open* calls
CALL OpenFOutFile ( UnSum, TRIM( farm%p%OutFileRoot )//'.sum', ErrStat, ErrMsg )
IF ( ErrStat /= ErrID_None ) RETURN

Expand Down Expand Up @@ -263,7 +264,7 @@ SUBROUTINE Farm_InitOutput( farm, ErrStat, ErrMsg )
!......................................................

! IF (farm%p%WrTxtOutFile) THEN

farm%p%UnOu = -1 ! set to -1 at start to find valid unit numbers in Open* calls
CALL OpenFOutFile ( farm%p%UnOu, TRIM(farm%p%OutFileRoot)//'.out', ErrStat, ErrMsg )
IF ( ErrStat >= AbortErrLev ) RETURN

Expand Down
1 change: 1 addition & 0 deletions glue-codes/fast-farm/src/FAST_Farm_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -415,6 +415,7 @@ SUBROUTINE Farm_ReadPrimaryFile( InputFile, p, WD_InitInp, AWAE_InitInp, SC_Init

! Initialize some variables:
UnEc = -1
UnIn = -1 ! set to -1 at start to find valid unit numbers in Open* calls
Echo = .FALSE. ! Don't echo until we've read the "Echo" flag
CALL GetPath( InputFile, PriPath ) ! Input files will be relative to the path where the primary input file is located.

Expand Down
8 changes: 6 additions & 2 deletions modules/aerodyn/src/AeroAcoustics_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -118,7 +118,7 @@ SUBROUTINE ReadPrimaryFile( InputFile, InputFileData, Default_DT, OutFileRoot, U
type(AA_InputFile), intent(inout) :: InputFileData ! All the data in the Noise input file
! Local variables:
integer(IntKi) :: I ! loop counter
integer(IntKi) :: UnIn,UnIn2 ! Unit number for reading file
integer(IntKi) :: UnIn,UnIn2 ! Unit number for reading file (set to -1 so that Open* calls will find a valid unit number)
character(1024) :: ObserverFile ! name of the files containing obesever location
integer(IntKi) :: ErrStat2, IOS,cou ! Temporary Error status
logical :: Echo ! Determines if an echo file should be written
Expand All @@ -130,7 +130,9 @@ SUBROUTINE ReadPrimaryFile( InputFile, InputFileData, Default_DT, OutFileRoot, U
ErrStat = ErrID_None
ErrMsg = ""

UnEc = -1
UnEc = -1
UnIn = -1
UnIn2 = -1
Echo = .FALSE.
CALL GetPath( InputFile, PriPath ) ! Input files will be relative to the path where the primary input file is located.

Expand Down Expand Up @@ -333,6 +335,7 @@ SUBROUTINE ReadBLTables( InputFile, AFI, InputFileData, ErrStat, ErrMsg )
! Initialize some variables:
ErrStat = ErrID_None
ErrMsg = ""
UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number

CALL GetPath( InputFile, PriPath ) ! Input files will be relative to the path where the primary input file is located.
nAirfoils = size(AFI)
Expand Down Expand Up @@ -438,6 +441,7 @@ SUBROUTINE ReadTICalcTables(InputFile, InputFileData, ErrStat, ErrMsg)
! Initialize some variables:
ErrStat = ErrID_None
ErrMsg = ""
UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number

CALL GetPath( InputFile, PriPath ) ! Input files will be relative to the path where the primary input file is located.

Expand Down
8 changes: 4 additions & 4 deletions modules/aerodyn/src/AeroAcoustics_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -198,10 +198,10 @@ typedef ^ ParameterType IntKi NumOuts
typedef ^ ParameterType IntKi NumOutsForPE - - - "Number of parameters in the output list (number of outputs requested)" -
typedef ^ ParameterType IntKi NumOutsForSep - - - "Number of parameters in the output list (number of outputs requested)" -
typedef ^ ParameterType IntKi NumOutsForNodes - - - "Number of parameters in the output list (number of outputs requested)" -
typedef ^ ParameterType IntKi unOutFile - - - "unit number for writing output file" "-"
typedef ^ ParameterType IntKi unOutFile2 - - - "unit number for writing output file" "-"
typedef ^ ParameterType IntKi unOutFile3 - - - "unit number for writing output file" "-"
typedef ^ ParameterType IntKi unOutFile4 - - - "unit number for writing output file" "-"
typedef ^ ParameterType IntKi unOutFile - -1 - "unit number for writing output file (set to -1 so that Open* calls will find a valid unit number)" "-"
typedef ^ ParameterType IntKi unOutFile2 - -1 - "unit number for writing output file (set to -1 so that Open* calls will find a valid unit number)" "-"
typedef ^ ParameterType IntKi unOutFile3 - -1 - "unit number for writing output file (set to -1 so that Open* calls will find a valid unit number)" "-"
typedef ^ ParameterType IntKi unOutFile4 - -1 - "unit number for writing output file (set to -1 so that Open* calls will find a valid unit number)" "-"
typedef ^ ParameterType CHARACTER(1024) RootName - - - "RootName for writing output files" -
typedef ^ ParameterType OutParmType OutParam {:} - - "Names and units (and other characteristics) of all requested output parameters" -
typedef ^ ParameterType ReKi StallStart {:}{:} - - "ation" -
Expand Down
8 changes: 4 additions & 4 deletions modules/aerodyn/src/AeroAcoustics_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -224,10 +224,10 @@ MODULE AeroAcoustics_Types
INTEGER(IntKi) :: NumOutsForPE !< Number of parameters in the output list (number of outputs requested) [-]
INTEGER(IntKi) :: NumOutsForSep !< Number of parameters in the output list (number of outputs requested) [-]
INTEGER(IntKi) :: NumOutsForNodes !< Number of parameters in the output list (number of outputs requested) [-]
INTEGER(IntKi) :: unOutFile !< unit number for writing output file [-]
INTEGER(IntKi) :: unOutFile2 !< unit number for writing output file [-]
INTEGER(IntKi) :: unOutFile3 !< unit number for writing output file [-]
INTEGER(IntKi) :: unOutFile4 !< unit number for writing output file [-]
INTEGER(IntKi) :: unOutFile = -1 !< unit number for writing output file (set to -1 so that Open* calls will find a valid unit number) [-]
INTEGER(IntKi) :: unOutFile2 = -1 !< unit number for writing output file (set to -1 so that Open* calls will find a valid unit number) [-]
INTEGER(IntKi) :: unOutFile3 = -1 !< unit number for writing output file (set to -1 so that Open* calls will find a valid unit number) [-]
INTEGER(IntKi) :: unOutFile4 = -1 !< unit number for writing output file (set to -1 so that Open* calls will find a valid unit number) [-]
CHARACTER(1024) :: RootName !< RootName for writing output files [-]
TYPE(OutParmType) , DIMENSION(:), ALLOCATABLE :: OutParam !< Names and units (and other characteristics) of all requested output parameters [-]
REAL(ReKi) , DIMENSION(:,:), ALLOCATABLE :: StallStart !< ation [-]
Expand Down
3 changes: 2 additions & 1 deletion modules/aerodyn/src/AeroDyn_Driver_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -216,7 +216,7 @@ subroutine Dvr_InitCase(iCase, dvr, ADI, FED, errStat, errMsg )
call Dvr_InitializeDriverOutputs(dvr, ADI, errStat2, errMsg2); if(Failed()) return
allocate(dvr%out%unOutFile(dvr%numTurbines))
endif
dvr%out%unOutFile = -1
dvr%out%unOutFile = -1 ! set to -1 so that Open* calls will find a valid unit number

! --- Initialize ADI
call Init_ADI_ForDriver(iCase, ADI, dvr, FED, dvr%dt, errStat2, errMsg2); if(Failed()) return
Expand Down Expand Up @@ -1702,6 +1702,7 @@ subroutine ReadDelimFile(Filename, nCol, Array, errStat, errMsg, nHeaderLines, p
character(len=2048) :: Filename_Loc ! filename local to this function
errStat = ErrID_None
errMsg = ""
UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number

Filename_Loc = Filename
if (present(priPath)) then
Expand Down
2 changes: 2 additions & 0 deletions modules/aerodyn/src/AeroDyn_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1317,6 +1317,8 @@ SUBROUTINE AD_PrintSum( InputFileData, p, p_AD, u, y, ErrStat, ErrMsg )
CHARACTER(ChanLen),PARAMETER :: TitleStr(2) = (/ 'Parameter', 'Units ' /)
CHARACTER(ChanLen),PARAMETER :: TitleStrLines(2) = (/ '---------------', '---------------' /)

UnSu = -1 ! set to -1 so that Open* calls will find a valid unit number

! Open the summary file and give it a heading.
CALL OpenFOutFile ( UnSu, TRIM( p%RootName )//'.sum', ErrStat, ErrMsg )
IF ( ErrStat >= AbortErrLev ) RETURN
Expand Down
5 changes: 3 additions & 2 deletions modules/aerodyn/src/BEMT.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2392,11 +2392,12 @@ subroutine WriteDEBUGValuesToFile(t, u, p, x, xd, z, OtherState, m, AFInfo)
integer, save :: DEBUG_BLADE
integer, save :: DEBUG_BLADENODE
integer, save :: DEBUG_nStep = 1
integer, save :: DEBUG_FILE_UNIT
integer, save :: DEBUG_FILE_UNIT = -1 ! set to -1 so that Open* calls will find a valid unit number

! character(*), parameter :: RoutineName = 'BEMT_UnCoupledSolve'

DEBUG_BLADE = 1 !size(u%Vx,2)
UnOut = -1 ! set to -1 so that Open* calls will find a valid unit number
DEBUG_BLADE = 1 !size(u%Vx,2)
DEBUG_BLADENODE = 23 !max(1, size(u%Vx,1) / 2 )

if (DEBUG_nStep == 1) then
Expand Down
1 change: 1 addition & 0 deletions modules/aerodyn/src/FVW_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ SUBROUTINE FVW_ReadInputFile( FileName, p, m, Inp, ErrStat, ErrMsg )
character(ErrMsgLen) :: ErrMsg2
ErrStat = ErrID_None
ErrMsg = ""
UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number
! Open file
CALL OpenFInpfile(UnIn, TRIM(FileName), ErrStat2, ErrMsg2)
if (Check( ErrStat2 /= ErrID_None , 'Could not open input file')) return
Expand Down
1 change: 1 addition & 0 deletions modules/aerodyn/src/FVW_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -130,6 +130,7 @@ subroutine ReadAndInterpGamma(CirculationFileName, s_CP_LL, L, Gamma_CP_LL, ErrS
real(ReKi), parameter :: ReNaN = huge(1.0_ReKi)
ErrStat = ErrID_None
ErrMsg = ''
iUnit = -1 ! set to -1 so that Open* calls will find a valid unit number
! ---
call OpenFInpFile(iUnit, CirculationFileName, errStat2, errMsg2); if(Failed()) return
nLines=line_count(iUnit)-1
Expand Down
6 changes: 5 additions & 1 deletion modules/aerodyn/src/UA_Dvr_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ module UA_Dvr_Subs
subroutine ReadDriverInputFile( inputFile, InitInp, ErrStat, ErrMsg )

character(1024), intent( in ) :: inputFile
type(UA_Dvr_InitInput), intent( out ) :: InitInp
type(UA_Dvr_InitInput), intent( out ) :: InitInp
integer, intent( out ) :: ErrStat ! returns a non-zero value when an error occurs
character(*), intent( out ) :: ErrMsg ! Error message if ErrStat /= ErrID_None

Expand All @@ -57,6 +57,7 @@ subroutine ReadDriverInputFile( inputFile, InitInp, ErrStat, ErrMsg )

! Initialize the echo file unit to -1 which is the default to prevent echoing, we will alter this based on user input
UnEchoLocal = -1
UnIn = -1 ! set to -1 at start to find valid unit numbers in Open* calls
ErrStat = ErrID_None
ErrMsg = ''
FileName = trim(inputFile)
Expand Down Expand Up @@ -426,6 +427,7 @@ subroutine ReadTimeSeriesData( inputsFile, nSimSteps, timeArr, AOAarr, Uarr, Ome
ErrStat = ErrID_None
ErrMsg = ''
nSimSteps = 0 ! allocate here in case errors occur
UnIn = -1 ! set to -1 at start to find valid unit numbers in Open* calls

FileName = trim(inputsFile)

Expand Down Expand Up @@ -632,6 +634,8 @@ subroutine WriteAFITables(AFI_Params, OutRootName, UseCm, UA_f_cn)
integer :: iTab, iRow, iStartUA
type(AFI_Table_Type), pointer :: tab !< Alias

unOutFile = -1 ! set to -1 so that Open* calls will find a valid unit number

if (UA_f_cn) then
Prefix='Cn_'
sFullyAtt='Cn_FullyAtt'
Expand Down
1 change: 1 addition & 0 deletions modules/aerodyn/src/UnsteadyAero.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1084,6 +1084,7 @@ subroutine UA_Init( InitInp, u, p, x, xd, OtherState, y, m, Interval, &
! Initialize variables for this routine
ErrStat = ErrID_None
ErrMsg = ""
p%unOutFile = -1 ! set to -1 so that Open* calls will find a valid unit number


! Initialize the NWTC Subroutine Library
Expand Down
6 changes: 6 additions & 0 deletions modules/aerodyn14/src/AeroSubs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ SUBROUTINE AD14_GetInput(InitInp, P, x, xd, z, m, y, ErrStat, ErrMess )

ErrStat = ErrID_None
ErrMess = ''
UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number

!-------------------------------------------------------------------------------------------------
! Open the AeroDyn input file
Expand Down Expand Up @@ -742,6 +743,7 @@ SUBROUTINE ADOut(InitInp, P, m, AD14_Ver, FileName, ErrStat, ErrMess )

ErrStat = ErrID_None
ErrMess = ""
UnOut = -1 ! set to -1 so that Open* calls will find a valid unit number

CALL OpenFOutFile( UnOut, FileName, ErrStatLcl, ErrMessLcl)
CALL SetErrStat(ErrStatLcl,ErrMessLcl,ErrStat,ErrMess,'ADOut' )
Expand Down Expand Up @@ -1025,6 +1027,7 @@ SUBROUTINE READFL(InitInp, P, x, xd, z, m, y, ErrStat, ErrMess )
DO NFOILID = 1, p%AirFoil%NUMFOIL

! Open the file for reading # of lines
NUNIT = -1 ! set to -1 so that Open* calls will find a valid unit number
CALL OpenFInpFile (NUNIT, TRIM(p%AirFoil%FOILNM(NFOILID)), ErrStatLcL, ErrMessLcl)
CALL SetErrStat( ErrStatLcL, ErrMessLcl, ErrStat, ErrMess, 'READFL')
IF (ErrStat >= AbortErrLev) THEN
Expand Down Expand Up @@ -1057,6 +1060,7 @@ SUBROUTINE READFL(InitInp, P, x, xd, z, m, y, ErrStat, ErrMess )
DO NFOILID = 1, p%AirFoil%NUMFOIL

! Open the file for reading inputs
NUNIT = -1 ! set to -1 so that Open* calls will find a valid unit number
CALL OpenFInpFile (NUNIT, TRIM(Adjustl(p%AirFoil%FOILNM(NFOILID))), ErrStatLcL, ErrMessLcl )
CALL SetErrStat( ErrStatLcL, ErrMessLcl, ErrStat, ErrMess, 'READFL')
IF (ErrStat >= AbortErrLev) THEN
Expand Down Expand Up @@ -1387,6 +1391,7 @@ SUBROUTINE READTwr(UnIn, InitInp, P, x, xd, z, m, y, ErrStat, ErrMess )
! Open the file for reading
!-------------------------------------------------------------------------------------------------
FilName = p%TwrProps%TwrFile
UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number
CALL OpenFInpFile (UnIn, TRIM(FilName), ErrStat, ErrMess )
IF ( ErrStat /= ErrID_None ) RETURN

Expand Down Expand Up @@ -4463,6 +4468,7 @@ SUBROUTINE DynDebug (Time, P, x, xd, z, m, y, ErrStat, ErrMess, RHScos, RHSsin)

ErrStat = ErrID_None
ErrMess = ""
UnDyn = -1 ! set to -1 so that Open* calls will find a valid unit number

!SAVE ! Save *all* local variables. Is this necessary, or is OnePass enough.

Expand Down
4 changes: 2 additions & 2 deletions modules/aerodyn14/src/DWM_driver_wind_farm_sub.f90
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ SUBROUTINE read_wind_farm_parameter(PriFile)
IMPLICIT NONE

CHARACTER(*), INTENT(IN) :: PriFile
INTEGER :: UnIn = 0
INTEGER :: UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number
INTEGER :: UnEc = -1
INTEGER :: I
CHARACTER(1024) :: DWM_Title,comment
Expand Down Expand Up @@ -877,4 +877,4 @@ SUBROUTINE rename_FAST_output(SimulationOrder_index)

END SUBROUTINE rename_FAST_output

END MODULE DWM_driver_wind_farm_sub
END MODULE DWM_driver_wind_farm_sub
2 changes: 2 additions & 0 deletions modules/awae/src/AWAE_Driver_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,7 @@ module AWAE_Driver_Subs
! ErrMsg = ""
!
! UnEc = -1
! UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number
! Echo = .FALSE.
! call GetPath( filename, PriPath ) ! Input files will be relative to the path where the driver input file is located.
!
Expand Down Expand Up @@ -271,6 +272,7 @@ module AWAE_Driver_Subs
! ErrStat = ErrID_None
! ErrMsg = ''
! UnEcho = -1
! UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number
! InputFileData%DT = Default_DT ! the glue code's suggested DT for the module (may be overwritten in ReadPrimaryFile())
!
! ! get the primary/platform input-file data
Expand Down
1 change: 1 addition & 0 deletions modules/awae/src/AWAE_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -539,6 +539,7 @@ SUBROUTINE AWAE_PrintSum( p, u, y, ErrStat, ErrMsg )

errStat = ErrID_None
errMsg = ""
UnSu = -1 ! set to -1 so that Open* calls will find a valid unit number

! Open the summary file and give it a heading.
CALL OpenFOutFile ( UnSu, TRIM( p%OutFileRoot )//'.sum', ErrStat, ErrMsg )
Expand Down
4 changes: 3 additions & 1 deletion modules/beamdyn/src/BeamDyn_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -577,6 +577,7 @@ SUBROUTINE BD_ReadPrimaryFile(InputFile,InputFileData,OutFileRoot,UnEc,ErrStat,E
ErrMsg = ""
Echo = .FALSE.
UnEc = -1
UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number
CALL GetPath( InputFile, PriPath ) ! Input files will be relative to the path where the primary input file is located.

CALL AllocAry( InputFileData%OutList, MaxOutPts, "Outlist", ErrStat2, ErrMsg2 )
Expand Down Expand Up @@ -1045,6 +1046,7 @@ SUBROUTINE BD_ReadBladeFile(BldFile,BladeInputFileData,UnEc,ErrStat,ErrMsg)

ErrStat = ErrID_None
ErrMsg = ""
UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number

CALL OpenFInpFile (UnIn,BldFile,ErrStat2,ErrMsg2)
CALL SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName )
Expand Down Expand Up @@ -1935,7 +1937,7 @@ SUBROUTINE BD_PrintSum( p, x, OtherState, m, InitInp, ErrStat, ErrMsg )
CHARACTER(80) :: OutPFmt ! Format to print list of selected output channels to summary file

! Open the summary file and give it a heading.

UnSu = -1 ! set to -1 so that Open* calls will find a valid unit number
CALL OpenFOutFile ( UnSu, TRIM( InitInp%RootName )//'.sum.yaml', ErrStat, ErrMsg )
IF ( ErrStat >= AbortErrLev ) RETURN

Expand Down
2 changes: 2 additions & 0 deletions modules/beamdyn/src/Driver_Beam_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -100,6 +100,7 @@ SUBROUTINE BD_ReadDvrFile(DvrInputFile,dt,InitInputData,DvrData,&
ErrStat = ErrID_None
ErrMsg = ""
UnEc = -1
UnIn = -1 ! set to -1 so that Open* calls will find a valid unit number

CALL OpenFInpFile(UnIn,DvrInputFile,ErrStat2,ErrMsg2); if (Failed()) return;

Expand Down Expand Up @@ -259,6 +260,7 @@ SUBROUTINE Dvr_InitializeOutputFile(OutUnit,IntOutput,RootName,ErrStat,ErrMsg)

ErrStat = ErrID_none
ErrMsg = ""
OutUnit = -1 ! set to -1 at start to find valid unit numbers in Open* calls

CALL OpenFOutFile ( OutUnit, trim(RootName)//'.out', ErrStat2, ErrMsg2 )
CALL SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName )
Expand Down
1 change: 1 addition & 0 deletions modules/elastodyn/src/ElastoDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -9633,6 +9633,7 @@ SUBROUTINE ED_PrintSum( p, OtherState, ErrStat, ErrMsg )
CHARACTER(ChanLen),PARAMETER :: TitleStrLines(2) = (/ '---------------', '---------------' /)

! Open the summary file and give it a heading.
UnSu = -1 ! set to -1 so that Open* calls will find a valid unit number
CALL OpenFOutFile ( UnSu, TRIM( p%RootName )//'.sum', ErrStat, ErrMsg )
IF ( ErrStat /= ErrID_None ) RETURN

Expand Down
Loading

0 comments on commit bccfe13

Please sign in to comment.