Skip to content

Commit 6508efb

Browse files
authored
Merge pull request #2761 from bjonkman/f/Lidar_cleanup
Cleanup LIDAR code
2 parents 4d4f114 + af0d1e4 commit 6508efb

File tree

18 files changed

+231
-843
lines changed

18 files changed

+231
-843
lines changed

modules/aerodyn/src/AeroDyn_Inflow.f90

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -392,6 +392,11 @@ subroutine ADI_InitInflowWind(Root, i_IW, u_AD, o_AD, IW, dt, InitOutData, errSt
392392
! the average values for the entire wind profile must be calculated and stored (we don't know if OLAF
393393
! is used until after AD_Init below).
394394
InitInData%BoxExceedAllow = .true.
395+
396+
!bjj: what about these initialization inputs?
397+
! InitInData%HubPosition
398+
! InitInData%RadAvg
399+
395400
CALL InflowWind_Init( InitInData, IW%u, IW%p, &
396401
IW%x, IW%xd, IW%z, IW%OtherSt, &
397402
IW%y, IW%m, dt, InitOutData, errStat2, errMsg2 )

modules/awae/src/AWAE.f90

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -909,9 +909,7 @@ subroutine AWAE_Init( InitInp, u, p, x, xd, z, OtherState, y, m, Interval, InitO
909909
IfW_InitInp%RootName = TRIM(p%OutFileRoot)//'.IfW'
910910
IfW_InitInp%FilePassingMethod = 0_IntKi ! Read IfW input file from disk
911911
IfW_InitInp%InputFileName = InitInp%InputFileData%InflowFile
912-
IfW_InitInp%lidar%Tmax = 0.0_ReKi
913-
IfW_InitInp%lidar%HubPosition = 0.0_ReKi
914-
IfW_InitInp%lidar%SensorType = SensorType_None
912+
IfW_InitInp%HubPosition = 0.0_ReKi
915913
IfW_InitInp%Use4Dext = .false.
916914
IfW_InitInp%MHK = MHK_None
917915
IfW_InitInp%WtrDpth = 0.0_ReKi

modules/inflowwind/src/InflowWind.f90

Lines changed: 5 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -186,23 +186,8 @@ SUBROUTINE InflowWind_Init( InitInp, InputGuess, p, ContStates, DiscStates, Cons
186186
endif
187187

188188
! initialize sensor data:
189-
p%lidar%SensorType = InputFileData%SensorType
190-
IF (InputFileData%SensorType /= SensorType_None) THEN
191-
p%lidar%NumBeam = InputFileData%NumBeam
192-
p%lidar%RotorApexOffsetPos = InputFileData%RotorApexOffsetPos
193-
p%lidar%LidRadialVel = InputFileData%LidRadialVel
194-
p%lidar%NumPulseGate = InputFileData%NumPulseGate
195-
p%lidar%FocalDistanceX = InputFileData%FocalDistanceX ! these are allocatable. Should allocate then copy
196-
p%lidar%FocalDistanceY = InputFileData%FocalDistanceY
197-
p%lidar%FocalDistanceZ = InputFileData%FocalDistanceZ
198-
p%lidar%MeasurementInterval= InputFileData%MeasurementInterval
199-
p%lidar%PulseSpacing = InputFileData%PulseSpacing
200-
p%lidar%URefLid = InputFileData%URefLid
201-
p%lidar%ConsiderHubMotion = InputFileData%ConsiderHubMotion
202-
203-
CALL Lidar_Init( InitInp, InputGuess, p, ContStates, DiscStates, ConstrStateGuess, OtherStates, &
204-
y, m, TimeInterval, InitOutData, TmpErrStat, TmpErrMsg ); if (Failed()) return
205-
endif
189+
CALL Lidar_Init( InitInp, InputFileData, InputGuess, p, y, m, TimeInterval, TmpErrStat, TmpErrMsg )
190+
if (Failed()) return
206191

207192
! If a summary file was requested, open it.
208193
IF ( InputFileData%SumPrint ) THEN
@@ -216,7 +201,7 @@ SUBROUTINE InflowWind_Init( InitInp, InputGuess, p, ContStates, DiscStates, Cons
216201
! Allocate the array for passing points
217202
CALL AllocAry( InputGuess%PositionXYZ, 3, InitInp%NumWindPoints, "Array of positions at which to find wind velocities", TmpErrStat, TmpErrMsg ); if (Failed()) return
218203
InputGuess%PositionXYZ = 0.0_ReKi
219-
InputGuess%HubPosition = 0.0_ReKi
204+
InputGuess%HubPosition = InitInp%HubPosition
220205
CALL Eye(InputGuess%HubOrientation,TmpErrStat,TmpErrMsg); if (Failed()) return
221206

222207
! Allocate the array for passing velocities out
@@ -619,12 +604,10 @@ SUBROUTINE InflowWind_CalcOutput( Time, InputData, p, &
619604
! return sensor values
620605
IF (p%lidar%SensorType /= SensorType_None) THEN
621606

622-
CALL Lidar_CalcOutput(Time, InputData, p, &
623-
ContStates, DiscStates, ConstrStates, OtherStates, &
624-
OutputData, m, TmpErrStat, TmpErrMsg )
607+
CALL Lidar_CalcOutput(Time, InputData, p, OutputData, m, TmpErrStat, TmpErrMsg )
625608
CALL SetErrStat( TmpErrStat, TmpErrMsg, ErrStat, ErrMsg, RoutineName )
626609

627-
END IF
610+
END IF
628611

629612

630613
!-----------------------------

modules/inflowwind/src/InflowWind.txt

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,7 @@ typedef ^ ^ ReKi PulseSpacin
7676
typedef ^ ^ ReKi MeasurementInterval - - - "Time between each measurement" s
7777
typedef ^ ^ ReKi URefLid - - - "Reference average wind speed for the lidar" m/s
7878
typedef ^ ^ LOGICAL LidRadialVel - - - "TRUE => return radial component, FALSE => return 'x' direction estimate" -
79-
typedef ^ ^ IntKi ConsiderHubMotion - - - "Flag whether or not the hub motion's impact on the Lidar measurement will be considered [0 for no, 1 for yes]" -
79+
typedef ^ ^ IntKi ConsiderHubMotion - - - "whether or not the hub motion's impact on the Lidar measurement will be considered" -
8080
typedef ^ ^ Grid3D_InitInputType FF - - - "scaling data" -
8181

8282

@@ -92,14 +92,14 @@ typedef ^ ^ IntKi FilePassing
9292
typedef ^ ^ FileInfoType PassedFileInfo - - - "If we don't use the input file, pass everything through this [FilePassingMethod = 1]" -
9393
typedef ^ ^ InflowWind_InputFile PassedFileData - - - "If we don't use the input file, pass everything through this [FilePassingMethod = 2]" -
9494
typedef ^ ^ LOGICAL OutputAccel - .FALSE. - "Flag to output wind acceleration" -
95-
typedef ^ ^ Lidar_InitInputType lidar - - - "InitInput for lidar data" -
9695
typedef ^ ^ Grid4D_InitInputType FDext - - - "InitInput for 4D external wind data" -
9796
typedef ^ ^ ReKi RadAvg - - - "Radius (from hub) used for averaging wind speed" -
9897
typedef ^ ^ IntKi MHK - - - "MHK turbine type switch" -
9998
typedef ^ ^ ReKi WtrDpth - - - "Water depth" m
10099
typedef ^ ^ ReKi MSL2SWL - - - "Mean sea level to still water level" m
101100
typedef ^ ^ LOGICAL BoxExceedAllow - .FALSE. - "Flag to allow Extrapolation winds outside box starting at this index (for OLAF wakes and LidarSim)" -
102101
typedef ^ ^ LOGICAL LidarEnabled - .false. - "Enable LiDAR for this instance of InflowWind? (FAST.Farm, ADI, and InflowWind driver/library are not compatible)" -
102+
typedef ^ ^ ReKi HubPosition {3} - - "initial position of the hub (lidar mounted on hub) [0,0,HubHeight]" "m"
103103

104104

105105
# Init Output

modules/inflowwind/src/InflowWind_Subs.f90

Lines changed: 17 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -504,18 +504,14 @@ SUBROUTINE InflowWind_ParseInputFileInfo( InputFileData, InFileInfo, PriPath, In
504504
CALL ParseVar( InFileInfo, CurLine, "NumBeam", InputFileData%NumBeam, TmpErrStat, TmpErrMsg, UnEc )
505505
if (Failed()) return
506506

507-
! Before proceeding, make sure that NumBeam makes sense
508-
IF ((InputFileData%SensorType == 1) .and. (InputFileData%NumBeam < 1 .OR. InputFileData%NumBeam > 5)) THEN
509-
CALL SetErrStat( ErrID_Fatal, 'NumBeam must be greater than or equal to one and less than 6.', &
510-
ErrStat, ErrMsg, RoutineName )
511-
RETURN
512-
ELSE
513-
! Allocate space for the output location arrays:
514-
CALL AllocAry( InputFileData%FocalDistanceX, InputFileData%NumBeam, 'FocalDistanceX', TmpErrStat, TmpErrMsg ); CALL SetErrStat( TmpErrStat, TmpErrMsg, ErrStat, ErrMsg, RoutineName )
515-
CALL AllocAry( InputFileData%FocalDistanceY, InputFileData%NumBeam, 'FocalDistanceY', TmpErrStat, TmpErrMsg ); CALL SetErrStat( TmpErrStat, TmpErrMsg, ErrStat, ErrMsg, RoutineName )
516-
CALL AllocAry( InputFileData%FocalDistanceZ, InputFileData%NumBeam, 'FocalDistanceZ', TmpErrStat, TmpErrMsg ); CALL SetErrStat( TmpErrStat, TmpErrMsg, ErrStat, ErrMsg, RoutineName )
517-
if (Failed()) return
518-
ENDIF
507+
! Before proceeding, make sure that NumBeam makes sense for array allocation
508+
InputFileData%NumBeam = MAX(InputFileData%NumBeam, 1)
509+
510+
! Allocate space for the output location arrays:
511+
CALL AllocAry( InputFileData%FocalDistanceX, InputFileData%NumBeam, 'FocalDistanceX', TmpErrStat, TmpErrMsg ); CALL SetErrStat( TmpErrStat, TmpErrMsg, ErrStat, ErrMsg, RoutineName )
512+
CALL AllocAry( InputFileData%FocalDistanceY, InputFileData%NumBeam, 'FocalDistanceY', TmpErrStat, TmpErrMsg ); CALL SetErrStat( TmpErrStat, TmpErrMsg, ErrStat, ErrMsg, RoutineName )
513+
CALL AllocAry( InputFileData%FocalDistanceZ, InputFileData%NumBeam, 'FocalDistanceZ', TmpErrStat, TmpErrMsg ); CALL SetErrStat( TmpErrStat, TmpErrMsg, ErrStat, ErrMsg, RoutineName )
514+
if (Failed()) return
519515

520516
! Focal Distance X
521517
CALL ParseAry( InFileInfo, CurLine, 'FocalDistanceX', InputFileData%FocalDistanceX, InputFileData%NumBeam, TmpErrStat, TmpErrMsg, UnEc )
@@ -647,7 +643,7 @@ SUBROUTINE InflowWind_ValidateInput( InitInp, InputFileData, ErrStat, ErrMsg )
647643
return
648644
end if
649645

650-
if (InitInp%lidar%SensorType /= SensorType_None) then
646+
if (InputFileData%SensorType /= SensorType_None) then
651647
call SetErrStat(ErrID_Fatal, 'InflowWind can not perform linearization with the lidar module enabled.', ErrStat, ErrMsg, RoutineName)
652648
return
653649
end if
@@ -1177,7 +1173,7 @@ SUBROUTINE SetOutParam(OutList, p, ErrStat, ErrMsg )
11771173
! Passed variables
11781174

11791175
CHARACTER(ChanLen), INTENT(IN) :: OutList(:) !< The list of user-requested outputs
1180-
TYPE(InflowWind_ParameterType), INTENT(INOUT) :: p !< The module parameters
1176+
TYPE(InflowWind_ParameterType), INTENT(INOUT) :: p !< The module parameters
11811177
INTEGER(IntKi), INTENT(OUT) :: ErrStat !< The error status code
11821178
CHARACTER(*), INTENT(OUT) :: ErrMsg !< The error message, if an error occurred
11831179

@@ -1288,17 +1284,9 @@ SUBROUTINE SetOutParam(OutList, p, ErrStat, ErrMsg )
12881284
InvalidOutput(WindAccZ) = .TRUE.
12891285
end if
12901286

1291-
if (p%lidar%SensorType /= SensorType_None) then
1292-
IF (p%lidar%SensorType == SensorType_SinglePoint) THEN
1293-
DO I=p%lidar%NumBeam+1,5
1294-
InvalidOutput( WindMeas(I) ) = .TRUE.
1295-
END DO
1296-
ELSE
1297-
DO I=p%lidar%NumPulseGate+1,5
1298-
InvalidOutput( WindMeas(I) ) = .TRUE.
1299-
END DO
1300-
END IF
1301-
endif
1287+
do I=p%lidar%NumMeasurements+1,SIZE(WindMeas)
1288+
InvalidOutput( WindMeas(I) ) = .TRUE.
1289+
end do
13021290

13031291
! ................. End of validity checking .................
13041292

@@ -1521,16 +1509,10 @@ SUBROUTINE SetAllOuts( p, y, m, ErrStat, ErrMsg )
15211509

15221510

15231511
!FIXME: Add in Wind1Dir etc. -- although those can be derived outside of FAST.
1524-
if (p%lidar%SensorType /= SensorType_None) then
1525-
IF ( p%lidar%SensorType == SensorType_SinglePoint) THEN
1526-
DO I = 1,MIN(5, p%lidar%NumBeam )
1527-
m%AllOuts( WindMeas(I) ) = y%lidar%LidSpeed(I)
1528-
END DO
1529-
ELSE
1530-
DO I = 1,MIN(5, p%lidar%NumPulseGate )
1531-
m%AllOuts( WindMeas(I) ) = y%lidar%LidSpeed(I)
1532-
END DO
1533-
END IF
1512+
if (ALLOCATED(y%lidar%LidSpeed)) then
1513+
DO I = 1,MIN(SIZE(WindMeas), SIZE(y%lidar%LidSpeed) )
1514+
m%AllOuts( WindMeas(I) ) = y%lidar%LidSpeed(I)
1515+
END DO
15341516
endif
15351517

15361518
END SUBROUTINE SetAllOuts

modules/inflowwind/src/InflowWind_Types.f90

Lines changed: 5 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ MODULE InflowWind_Types
9494
REAL(ReKi) :: MeasurementInterval = 0.0_ReKi !< Time between each measurement [s]
9595
REAL(ReKi) :: URefLid = 0.0_ReKi !< Reference average wind speed for the lidar [m/s]
9696
LOGICAL :: LidRadialVel = .false. !< TRUE => return radial component, FALSE => return 'x' direction estimate [-]
97-
INTEGER(IntKi) :: ConsiderHubMotion = 0_IntKi !< Flag whether or not the hub motion's impact on the Lidar measurement will be considered [0 for no, 1 for yes] [-]
97+
INTEGER(IntKi) :: ConsiderHubMotion = 0_IntKi !< whether or not the hub motion's impact on the Lidar measurement will be considered [-]
9898
TYPE(Grid3D_InitInputType) :: FF !< scaling data [-]
9999
END TYPE InflowWind_InputFile
100100
! =======================
@@ -111,14 +111,14 @@ MODULE InflowWind_Types
111111
TYPE(FileInfoType) :: PassedFileInfo !< If we don't use the input file, pass everything through this [FilePassingMethod = 1] [-]
112112
TYPE(InflowWind_InputFile) :: PassedFileData !< If we don't use the input file, pass everything through this [FilePassingMethod = 2] [-]
113113
LOGICAL :: OutputAccel = .FALSE. !< Flag to output wind acceleration [-]
114-
TYPE(Lidar_InitInputType) :: lidar !< InitInput for lidar data [-]
115114
TYPE(Grid4D_InitInputType) :: FDext !< InitInput for 4D external wind data [-]
116115
REAL(ReKi) :: RadAvg = 0.0_ReKi !< Radius (from hub) used for averaging wind speed [-]
117116
INTEGER(IntKi) :: MHK = 0_IntKi !< MHK turbine type switch [-]
118117
REAL(ReKi) :: WtrDpth = 0.0_ReKi !< Water depth [m]
119118
REAL(ReKi) :: MSL2SWL = 0.0_ReKi !< Mean sea level to still water level [m]
120119
LOGICAL :: BoxExceedAllow = .FALSE. !< Flag to allow Extrapolation winds outside box starting at this index (for OLAF wakes and LidarSim) [-]
121120
LOGICAL :: LidarEnabled = .false. !< Enable LiDAR for this instance of InflowWind? (FAST.Farm, ADI, and InflowWind driver/library are not compatible) [-]
121+
REAL(ReKi) , DIMENSION(1:3) :: HubPosition = 0.0_ReKi !< initial position of the hub (lidar mounted on hub) [0,0,HubHeight] [m]
122122
END TYPE InflowWind_InitInputType
123123
! =======================
124124
! ========= InflowWind_InitOutputType =======
@@ -511,9 +511,6 @@ subroutine InflowWind_CopyInitInput(SrcInitInputData, DstInitInputData, CtrlCode
511511
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
512512
if (ErrStat >= AbortErrLev) return
513513
DstInitInputData%OutputAccel = SrcInitInputData%OutputAccel
514-
call Lidar_CopyInitInput(SrcInitInputData%lidar, DstInitInputData%lidar, CtrlCode, ErrStat2, ErrMsg2)
515-
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
516-
if (ErrStat >= AbortErrLev) return
517514
call InflowWind_IO_CopyGrid4D_InitInputType(SrcInitInputData%FDext, DstInitInputData%FDext, CtrlCode, ErrStat2, ErrMsg2)
518515
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
519516
if (ErrStat >= AbortErrLev) return
@@ -523,6 +520,7 @@ subroutine InflowWind_CopyInitInput(SrcInitInputData, DstInitInputData, CtrlCode
523520
DstInitInputData%MSL2SWL = SrcInitInputData%MSL2SWL
524521
DstInitInputData%BoxExceedAllow = SrcInitInputData%BoxExceedAllow
525522
DstInitInputData%LidarEnabled = SrcInitInputData%LidarEnabled
523+
DstInitInputData%HubPosition = SrcInitInputData%HubPosition
526524
end subroutine
527525

528526
subroutine InflowWind_DestroyInitInput(InitInputData, ErrStat, ErrMsg)
@@ -538,8 +536,6 @@ subroutine InflowWind_DestroyInitInput(InitInputData, ErrStat, ErrMsg)
538536
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
539537
call InflowWind_DestroyInputFile(InitInputData%PassedFileData, ErrStat2, ErrMsg2)
540538
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
541-
call Lidar_DestroyInitInput(InitInputData%lidar, ErrStat2, ErrMsg2)
542-
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
543539
call InflowWind_IO_DestroyGrid4D_InitInputType(InitInputData%FDext, ErrStat2, ErrMsg2)
544540
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
545541
end subroutine
@@ -560,14 +556,14 @@ subroutine InflowWind_PackInitInput(RF, Indata)
560556
call NWTC_Library_PackFileInfoType(RF, InData%PassedFileInfo)
561557
call InflowWind_PackInputFile(RF, InData%PassedFileData)
562558
call RegPack(RF, InData%OutputAccel)
563-
call Lidar_PackInitInput(RF, InData%lidar)
564559
call InflowWind_IO_PackGrid4D_InitInputType(RF, InData%FDext)
565560
call RegPack(RF, InData%RadAvg)
566561
call RegPack(RF, InData%MHK)
567562
call RegPack(RF, InData%WtrDpth)
568563
call RegPack(RF, InData%MSL2SWL)
569564
call RegPack(RF, InData%BoxExceedAllow)
570565
call RegPack(RF, InData%LidarEnabled)
566+
call RegPack(RF, InData%HubPosition)
571567
if (RegCheckErr(RF, RoutineName)) return
572568
end subroutine
573569

@@ -587,14 +583,14 @@ subroutine InflowWind_UnPackInitInput(RF, OutData)
587583
call NWTC_Library_UnpackFileInfoType(RF, OutData%PassedFileInfo) ! PassedFileInfo
588584
call InflowWind_UnpackInputFile(RF, OutData%PassedFileData) ! PassedFileData
589585
call RegUnpack(RF, OutData%OutputAccel); if (RegCheckErr(RF, RoutineName)) return
590-
call Lidar_UnpackInitInput(RF, OutData%lidar) ! lidar
591586
call InflowWind_IO_UnpackGrid4D_InitInputType(RF, OutData%FDext) ! FDext
592587
call RegUnpack(RF, OutData%RadAvg); if (RegCheckErr(RF, RoutineName)) return
593588
call RegUnpack(RF, OutData%MHK); if (RegCheckErr(RF, RoutineName)) return
594589
call RegUnpack(RF, OutData%WtrDpth); if (RegCheckErr(RF, RoutineName)) return
595590
call RegUnpack(RF, OutData%MSL2SWL); if (RegCheckErr(RF, RoutineName)) return
596591
call RegUnpack(RF, OutData%BoxExceedAllow); if (RegCheckErr(RF, RoutineName)) return
597592
call RegUnpack(RF, OutData%LidarEnabled); if (RegCheckErr(RF, RoutineName)) return
593+
call RegUnpack(RF, OutData%HubPosition); if (RegCheckErr(RF, RoutineName)) return
598594
end subroutine
599595

600596
subroutine InflowWind_CopyInitOutput(SrcInitOutputData, DstInitOutputData, CtrlCode, ErrStat, ErrMsg)

0 commit comments

Comments
 (0)