Skip to content

Commit

Permalink
IfW_uniform: remove file passing option
Browse files Browse the repository at this point in the history
  • Loading branch information
andrew-platt committed Dec 23, 2024
1 parent eab6ed1 commit 24e2e50
Show file tree
Hide file tree
Showing 8 changed files with 4 additions and 103 deletions.
2 changes: 0 additions & 2 deletions modules/inflowwind/src/InflowWind.f90
Original file line number Diff line number Diff line change
Expand Up @@ -255,8 +255,6 @@ SUBROUTINE InflowWind_Init( InitInp, InputGuess, p, ContStates, DiscStates, Cons
Uniform_InitInput%RefHt = InputFileData%Uniform_RefHt
Uniform_InitInput%RefLength = InputFileData%Uniform_RefLength
Uniform_InitInput%PropagationDir = InputFileData%PropagationDir
Uniform_InitInput%UseInputFile = InitInp%WindType2UseInputFile
Uniform_InitInput%PassedFileInfo = InitInp%WindType2Info

p%FlowField%FieldType = Uniform_FieldType
call IfW_UniformWind_Init(Uniform_InitInput, SumFileUnit, p%FlowField%Uniform, InitOutData%WindFileInfo, TmpErrStat, TmpErrMsg); if (Failed()) return
Expand Down
2 changes: 0 additions & 2 deletions modules/inflowwind/src/InflowWind.txt
Original file line number Diff line number Diff line change
Expand Up @@ -91,8 +91,6 @@ typedef ^ ^ CHARACTER(1024) RootName
typedef ^ ^ IntKi FilePassingMethod - 0 - "Method for file passing {0: None (read from file), 1: as FileInfoType to parse, 2: as InputFileType already parsed}" -
typedef ^ ^ FileInfoType PassedFileInfo - - - "If we don't use the input file, pass everything through this [FilePassingMethod = 1]" -
typedef ^ ^ InflowWind_InputFile PassedFileData - - - "If we don't use the input file, pass everything through this [FilePassingMethod = 2]" -
typedef ^ ^ LOGICAL WindType2UseInputFile - .TRUE. - "Flag for toggling file based IO in wind type 2." -
typedef ^ ^ FileInfoType WindType2Info - - - "Optional slot for wind type 2 data if file IO is not used." -
typedef ^ ^ LOGICAL OutputAccel - .FALSE. - "Flag to output wind acceleration" -
typedef ^ ^ Lidar_InitInputType lidar - - - "InitInput for lidar data" -
typedef ^ ^ Grid4D_InitInputType FDext - - - "InitInput for 4D external wind data" -
Expand Down
8 changes: 2 additions & 6 deletions modules/inflowwind/src/InflowWind_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -182,12 +182,8 @@ subroutine IfW_UniformWind_Init(InitInp, SumFileUnit, UF, FileDat, ErrStat, ErrM
UF%RefHeight = InitInp%RefHt
UF%RefLength = InitInp%RefLength

! Read wind data from file or init input data
if (InitInp%UseInputFile) then
call ProcessComFile(InitInp%WindFileName, WindFileInfo, TmpErrStat, TmpErrMsg)
else
call NWTC_Library_CopyFileInfoType(InitInp%PassedFileInfo, WindFileInfo, MESH_NEWCOPY, TmpErrStat, TmpErrMsg)
end if
! Read wind data from file
call ProcessComFile(InitInp%WindFileName, WindFileInfo, TmpErrStat, TmpErrMsg)
call SetErrStat(TmpErrStat, TmpErrMsg, ErrStat, ErrMsg, RoutineName)
if (ErrStat >= AbortErrLev) return

Expand Down
1 change: 0 additions & 1 deletion modules/inflowwind/src/InflowWind_IO.txt
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,6 @@ typedef ^ ^ ReKi RefHt
typedef ^ ^ ReKi RefLength - - - "Reference length for linear horizontal and vertical sheer" -
typedef ^ ^ ReKi PropagationDir - - - "Direction of wind propagation" radians
typedef ^ ^ logical UseInputFile - .true. - "Flag for toggling file based IO in wind type 2." -
typedef ^ ^ FileInfoType PassedFileInfo - - - "Optional slot for wind type 2 data if file IO is not used." -

#----------------------------------------------------------------------------------------------------------------------------------
typedef ^ Grid3D_InitInputType IntKi ScaleMethod - 0 - "Turbulence scaling method [0=none, 1=direct scaling, 2= calculate scaling factor based on a desired standard deviation]" -
Expand Down
12 changes: 0 additions & 12 deletions modules/inflowwind/src/InflowWind_IO_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,6 @@ MODULE InflowWind_IO_Types
REAL(ReKi) :: RefLength = 0.0_ReKi !< Reference length for linear horizontal and vertical sheer [-]
REAL(ReKi) :: PropagationDir = 0.0_ReKi !< Direction of wind propagation [radians]
LOGICAL :: UseInputFile = .true. !< Flag for toggling file based IO in wind type 2. [-]
TYPE(FileInfoType) :: PassedFileInfo !< Optional slot for wind type 2 data if file IO is not used. [-]
END TYPE Uniform_InitInputType
! =======================
! ========= Grid3D_InitInputType =======
Expand Down Expand Up @@ -281,8 +280,6 @@ subroutine InflowWind_IO_CopyUniform_InitInputType(SrcUniform_InitInputTypeData,
integer(IntKi), intent(in ) :: CtrlCode
integer(IntKi), intent( out) :: ErrStat
character(*), intent( out) :: ErrMsg
integer(IntKi) :: ErrStat2
character(ErrMsgLen) :: ErrMsg2
character(*), parameter :: RoutineName = 'InflowWind_IO_CopyUniform_InitInputType'
ErrStat = ErrID_None
ErrMsg = ''
Expand All @@ -291,22 +288,15 @@ subroutine InflowWind_IO_CopyUniform_InitInputType(SrcUniform_InitInputTypeData,
DstUniform_InitInputTypeData%RefLength = SrcUniform_InitInputTypeData%RefLength
DstUniform_InitInputTypeData%PropagationDir = SrcUniform_InitInputTypeData%PropagationDir
DstUniform_InitInputTypeData%UseInputFile = SrcUniform_InitInputTypeData%UseInputFile
call NWTC_Library_CopyFileInfoType(SrcUniform_InitInputTypeData%PassedFileInfo, DstUniform_InitInputTypeData%PassedFileInfo, CtrlCode, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
if (ErrStat >= AbortErrLev) return
end subroutine

subroutine InflowWind_IO_DestroyUniform_InitInputType(Uniform_InitInputTypeData, ErrStat, ErrMsg)
type(Uniform_InitInputType), intent(inout) :: Uniform_InitInputTypeData
integer(IntKi), intent( out) :: ErrStat
character(*), intent( out) :: ErrMsg
integer(IntKi) :: ErrStat2
character(ErrMsgLen) :: ErrMsg2
character(*), parameter :: RoutineName = 'InflowWind_IO_DestroyUniform_InitInputType'
ErrStat = ErrID_None
ErrMsg = ''
call NWTC_Library_DestroyFileInfoType(Uniform_InitInputTypeData%PassedFileInfo, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
end subroutine

subroutine InflowWind_IO_PackUniform_InitInputType(RF, Indata)
Expand All @@ -319,7 +309,6 @@ subroutine InflowWind_IO_PackUniform_InitInputType(RF, Indata)
call RegPack(RF, InData%RefLength)
call RegPack(RF, InData%PropagationDir)
call RegPack(RF, InData%UseInputFile)
call NWTC_Library_PackFileInfoType(RF, InData%PassedFileInfo)
if (RegCheckErr(RF, RoutineName)) return
end subroutine

Expand All @@ -333,7 +322,6 @@ subroutine InflowWind_IO_UnPackUniform_InitInputType(RF, OutData)
call RegUnpack(RF, OutData%RefLength); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%PropagationDir); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%UseInputFile); if (RegCheckErr(RF, RoutineName)) return
call NWTC_Library_UnpackFileInfoType(RF, OutData%PassedFileInfo) ! PassedFileInfo
end subroutine

subroutine InflowWind_IO_CopyGrid3D_InitInputType(SrcGrid3D_InitInputTypeData, DstGrid3D_InitInputTypeData, CtrlCode, ErrStat, ErrMsg)
Expand Down
2 changes: 1 addition & 1 deletion modules/inflowwind/src/InflowWind_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -699,7 +699,7 @@ SUBROUTINE InflowWind_ValidateInput( InitInp, InputFileData, ErrStat, ErrMsg )
CALL Steady_ValidateInput()

CASE ( Uniform_WindNumber )
IF ( InitInp%WindType2UseInputFile ) CALL Uniform_ValidateInput()
CALL Uniform_ValidateInput()

CASE ( TSFF_WindNumber )
CALL TSFF_ValidateInput()
Expand Down
12 changes: 0 additions & 12 deletions modules/inflowwind/src/InflowWind_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -110,8 +110,6 @@ MODULE InflowWind_Types
INTEGER(IntKi) :: FilePassingMethod = 0 !< Method for file passing {0: None (read from file), 1: as FileInfoType to parse, 2: as InputFileType already parsed} [-]
TYPE(FileInfoType) :: PassedFileInfo !< If we don't use the input file, pass everything through this [FilePassingMethod = 1] [-]
TYPE(InflowWind_InputFile) :: PassedFileData !< If we don't use the input file, pass everything through this [FilePassingMethod = 2] [-]
LOGICAL :: WindType2UseInputFile = .TRUE. !< Flag for toggling file based IO in wind type 2. [-]
TYPE(FileInfoType) :: WindType2Info !< Optional slot for wind type 2 data if file IO is not used. [-]
LOGICAL :: OutputAccel = .FALSE. !< Flag to output wind acceleration [-]
TYPE(Lidar_InitInputType) :: lidar !< InitInput for lidar data [-]
TYPE(Grid4D_InitInputType) :: FDext !< InitInput for 4D external wind data [-]
Expand Down Expand Up @@ -511,10 +509,6 @@ subroutine InflowWind_CopyInitInput(SrcInitInputData, DstInitInputData, CtrlCode
call InflowWind_CopyInputFile(SrcInitInputData%PassedFileData, DstInitInputData%PassedFileData, CtrlCode, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
if (ErrStat >= AbortErrLev) return
DstInitInputData%WindType2UseInputFile = SrcInitInputData%WindType2UseInputFile
call NWTC_Library_CopyFileInfoType(SrcInitInputData%WindType2Info, DstInitInputData%WindType2Info, CtrlCode, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
if (ErrStat >= AbortErrLev) return
DstInitInputData%OutputAccel = SrcInitInputData%OutputAccel
call Lidar_CopyInitInput(SrcInitInputData%lidar, DstInitInputData%lidar, CtrlCode, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
Expand Down Expand Up @@ -542,8 +536,6 @@ subroutine InflowWind_DestroyInitInput(InitInputData, ErrStat, ErrMsg)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
call InflowWind_DestroyInputFile(InitInputData%PassedFileData, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
call NWTC_Library_DestroyFileInfoType(InitInputData%WindType2Info, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
call Lidar_DestroyInitInput(InitInputData%lidar, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
call InflowWind_IO_DestroyGrid4D_InitInputType(InitInputData%FDext, ErrStat2, ErrMsg2)
Expand All @@ -565,8 +557,6 @@ subroutine InflowWind_PackInitInput(RF, Indata)
call RegPack(RF, InData%FilePassingMethod)
call NWTC_Library_PackFileInfoType(RF, InData%PassedFileInfo)
call InflowWind_PackInputFile(RF, InData%PassedFileData)
call RegPack(RF, InData%WindType2UseInputFile)
call NWTC_Library_PackFileInfoType(RF, InData%WindType2Info)
call RegPack(RF, InData%OutputAccel)
call Lidar_PackInitInput(RF, InData%lidar)
call InflowWind_IO_PackGrid4D_InitInputType(RF, InData%FDext)
Expand All @@ -593,8 +583,6 @@ subroutine InflowWind_UnPackInitInput(RF, OutData)
call RegUnpack(RF, OutData%FilePassingMethod); if (RegCheckErr(RF, RoutineName)) return
call NWTC_Library_UnpackFileInfoType(RF, OutData%PassedFileInfo) ! PassedFileInfo
call InflowWind_UnpackInputFile(RF, OutData%PassedFileData) ! PassedFileData
call RegUnpack(RF, OutData%WindType2UseInputFile); if (RegCheckErr(RF, RoutineName)) return
call NWTC_Library_UnpackFileInfoType(RF, OutData%WindType2Info) ! WindType2Info
call RegUnpack(RF, OutData%OutputAccel); if (RegCheckErr(RF, RoutineName)) return
call Lidar_UnpackInitInput(RF, OutData%lidar) ! lidar
call InflowWind_IO_UnpackGrid4D_InitInputType(RF, OutData%FDext) ! FDext
Expand Down
68 changes: 1 addition & 67 deletions modules/inflowwind/tests/test_uniform_wind.F90
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,7 @@ module test_uniform_wind
subroutine test_uniform_wind_suite(testsuite)
type(unittest_type), allocatable, intent(out) :: testsuite(:)
testsuite = [ &
new_unittest("test_uniform_wind_input", test_uniform_wind_input), &
new_unittest("test_uniform_wind_direct_data", test_uniform_wind_direct_data) &
new_unittest("test_uniform_wind_input", test_uniform_wind_input) &
]
end subroutine

Expand All @@ -44,70 +43,5 @@ subroutine test_uniform_wind_input(error)

end subroutine

subroutine test_uniform_wind_direct_data(error)
type(error_type), allocatable, intent(out) :: error

! Types for setting up module
type(InflowWind_InitInputType) :: InitInp !< Input data for initialization
type(InflowWind_InputType) :: InputGuess !< An initial guess for the input; the input mesh must be defined
type(InflowWind_ParameterType) :: p !< Parameters
type(InflowWind_ContinuousStateType) :: ContStates !< Initial continuous states
type(InflowWind_DiscreteStateType) :: DiscStates !< Initial discrete states
type(InflowWind_ConstraintStateType) :: ConstrStateGuess !< Initial guess of the constraint states
type(InflowWind_OtherStateType) :: OtherStates !< Initial other/optimization states
type(InflowWind_OutputType) :: y !< Initial output (outputs are not calculated; only the output mesh is initialized)
type(InflowWind_MiscVarType) :: m !< Misc variables for optimization (not copied in glue code)
real(DbKi) :: TimeInterval !< Coupling time interval in seconds: InflowWind does not change this.
type(InflowWind_InitOutputType) :: InitOutData

! Variables for testing
integer :: ErrStat
character(ErrMsgLen) :: ErrMsg
type(FileInfoType) :: InFileInfo
type(FileInfoType) :: WindType2Info
character(1024), dimension(6) :: data = [ &
'! Wind file for sheared 18 m/s wind with 30 degree direction. ', &
'! Time Wind Wind Vert. Horiz. Vert. LinV Gust ', &
'! Speed Dir Speed Shear Shear Shear Speed ', &
' 0.0 12.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 ', &
' 0.1 12.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 ', &
' 999.9 12.0 0.0 0.0 0.0 0.0 0.0 0.0 0.0 ' &
]

! Error handling
integer(IntKi) :: TmpErrStat
character(ErrMsgLen) :: TmpErrMsg !< temporary error message

InFileInfo = getInputFileDataWindType2()
call InitFileInfo(data, WindType2Info, ErrStat, ErrMsg)

! For diagnostic purposes, the following can be used to display the contents
! of the InFileInfo data structure.
! call Print_FileInfo_Struct( CU, InFileInfo ) ! CU is the screen -- different number on different systems.

! Variable definitions
InitInp%InputFileName = ""
InitInp%NumWindPoints = 5
InitInp%FilePassingMethod = 1_IntKi
InitInp%RootName = ""
InitInp%PassedFileInfo = InFileInfo
InitInp%WindType2UseInputFile = .false.
InitInp%WindType2Info = WindType2Info

call InflowWind_Init(InitInp, InputGuess, p, ContStates, DiscStates, &
ConstrStateGuess, OtherStates, y, m, TimeInterval, &
InitOutData, TmpErrStat, TmpErrMsg)

! Results
call check(error, TmpErrStat, ErrID_None, message='Error message: '//trim(TmpErrMsg)//NewLine//'ErrStat: '); if (allocated(error)) return
call check(error, p%FlowField%Uniform%Time(1), 0.0_ReKi); if (allocated(error)) return
call check(error, p%FlowField%Uniform%Time(2), 0.1_ReKi); if (allocated(error)) return
call check(error, p%FlowField%Uniform%Time(3), 999.9_ReKi); if (allocated(error)) return

call check(error, p%FlowField%Uniform%VelH(1), 12.0_ReKi); if (allocated(error)) return
call check(error, p%FlowField%Uniform%VelH(2), 12.0_ReKi); if (allocated(error)) return
call check(error, p%FlowField%Uniform%VelH(3), 12.0_ReKi); if (allocated(error)) return

end subroutine

end module

0 comments on commit 24e2e50

Please sign in to comment.