Skip to content

Commit

Permalink
Pass pointer into AD15 during init.
Browse files Browse the repository at this point in the history
Also modify call order in the ADI library
  • Loading branch information
andrew-platt committed Jan 29, 2024
1 parent fd168cb commit 85365c4
Show file tree
Hide file tree
Showing 6 changed files with 49 additions and 12 deletions.
Binary file added modules/aerodyn/src/.AeroDyn_Inflow.f90.swp
Binary file not shown.
3 changes: 3 additions & 0 deletions modules/aerodyn/src/AeroDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -393,6 +393,9 @@ subroutine AD_Init( InitInp, u, p, x, xd, z, OtherState, y, m, Interval, InitOut
p%rotors(iR)%TFin%TFinAFID = InputFileData%rotors(iR)%TFin%TFinAFID
enddo

! Set pointer to FlowField data
if (associated(InitInp%FlowField)) p%FlowField => InitInp%FlowField


!............................................................................................
! Define and initialize inputs here
Expand Down
20 changes: 11 additions & 9 deletions modules/aerodyn/src/AeroDyn_Inflow.f90
Original file line number Diff line number Diff line change
Expand Up @@ -62,30 +62,32 @@ subroutine ADI_Init(InitInp, u, p, x, xd, z, OtherState, y, m, Interval, InitOut
! Display the module information
call DispNVD( ADI_Ver )

! Clear writeoutputs
if (allocated(InitOut%WriteOutputHdr)) deallocate(InitOut%WriteOutputHdr)
if (allocated(InitOut%WriteOutputUnt)) deallocate(InitOut%WriteOutputUnt)

! Set parameters
p%dt = interval
p%storeHHVel = InitInp%storeHHVel
p%WrVTK = InitInp%WrVTK
p%MHK = InitInp%AD%MHK
p%WtrDpth = InitInp%AD%WtrDpth

! --- Initialize Inflow Wind
call ADI_InitInflowWind(InitInp%RootName, InitInp%IW_InitInp, u%AD, OtherState%AD, m%IW, Interval, InitOut_IW, errStat2, errMsg2); if (Failed()) return
! Concatenate AD outputs to IW outputs
call concatOutputHeaders(InitOut%WriteOutputHdr, InitOut%WriteOutputUnt, InitOut_IW%WriteOutputHdr, InitOut_IW%WriteOutputUnt, errStat2, errMsg2); if(Failed()) return

! --- Initialize AeroDyn
if (allocated(InitOut%WriteOutputHdr)) deallocate(InitOut%WriteOutputHdr)
if (allocated(InitOut%WriteOutputUnt)) deallocate(InitOut%WriteOutputUnt)
! Link InflowWind's FlowField to AeroDyn's FlowField
InitInp%AD%FlowField => InitOut_IW%FlowField

call AD_Init(InitInp%AD, u%AD, p%AD, x%AD, xd%AD, z%AD, OtherState%AD, y%AD, m%AD, Interval, InitOut_AD, errStat2, errMsg2); if (Failed()) return
InitOut%Ver = InitOut_AD%ver
! Add writeoutput units and headers to driver, same for all cases and rotors!
!TODO: this header is too short if we add more rotors. Should also add a rotor identifier
call concatOutputHeaders(InitOut%WriteOutputHdr, InitOut%WriteOutputUnt, InitOut_AD%rotors(1)%WriteOutputHdr, InitOut_AD%rotors(1)%WriteOutputUnt, errStat2, errMsg2); if(Failed()) return

! --- Initialize Inflow Wind
call ADI_InitInflowWind(InitInp%RootName, InitInp%IW_InitInp, u%AD, OtherState%AD, m%IW, Interval, InitOut_IW, errStat2, errMsg2); if (Failed()) return
! Concatenate AD outputs to IW outputs
call concatOutputHeaders(InitOut%WriteOutputHdr, InitOut%WriteOutputUnt, InitOut_IW%WriteOutputHdr, InitOut_IW%WriteOutputUnt, errStat2, errMsg2); if(Failed()) return
! Link InflowWind's FlowField to AeroDyn's FlowField
p%AD%FlowField => InitOut_IW%FlowField

! --- Initialize grouped outputs
!TODO: assumes one rotor
p%NumOuts = p%AD%rotors(1)%NumOuts + p%AD%rotors(1)%BldNd_TotNumOuts + m%IW%p%NumOuts
Expand Down
1 change: 1 addition & 0 deletions modules/aerodyn/src/AeroDyn_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -104,6 +104,7 @@ typedef ^ InitInputType ReKi defPatm - - - "Default atmospheric
typedef ^ InitInputType ReKi defPvap - - - "Default vapor pressure from the driver; may be overwritten" Pa
typedef ^ InitInputType ReKi WtrDpth - - - "Water depth" m
typedef ^ InitInputType ReKi MSL2SWL - - - "Offset between still-water level and mean sea level" m
typedef ^ InitInputType FlowFieldType *FlowField - - - "Pointer of InflowWinds flow field data type" -

# This is data defined in the Input File for this module (or could otherwise be passed in)
# ..... Blade Input file data .....................................................................................................
Expand Down
31 changes: 31 additions & 0 deletions modules/aerodyn/src/AeroDyn_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,7 @@ MODULE AeroDyn_Types
REAL(ReKi) :: defPvap = 0.0_ReKi !< Default vapor pressure from the driver; may be overwritten [Pa]
REAL(ReKi) :: WtrDpth = 0.0_ReKi !< Water depth [m]
REAL(ReKi) :: MSL2SWL = 0.0_ReKi !< Offset between still-water level and mean sea level [m]
TYPE(FlowFieldType) , POINTER :: FlowField => NULL() !< Pointer of InflowWinds flow field data type [-]
END TYPE AD_InitInputType
! =======================
! ========= AD_BladePropsType =======
Expand Down Expand Up @@ -946,6 +947,7 @@ subroutine AD_CopyInitInput(SrcInitInputData, DstInitInputData, CtrlCode, ErrSta
DstInitInputData%defPvap = SrcInitInputData%defPvap
DstInitInputData%WtrDpth = SrcInitInputData%WtrDpth
DstInitInputData%MSL2SWL = SrcInitInputData%MSL2SWL
DstInitInputData%FlowField => SrcInitInputData%FlowField
end subroutine

subroutine AD_DestroyInitInput(InitInputData, ErrStat, ErrMsg)
Expand All @@ -970,6 +972,7 @@ subroutine AD_DestroyInitInput(InitInputData, ErrStat, ErrMsg)
end if
call NWTC_Library_DestroyFileInfoType(InitInputData%PassedPrimaryInputData, ErrStat2, ErrMsg2)
call SetErrStat(ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName)
nullify(InitInputData%FlowField)
end subroutine

subroutine AD_PackInitInput(RF, Indata)
Expand All @@ -978,6 +981,7 @@ subroutine AD_PackInitInput(RF, Indata)
character(*), parameter :: RoutineName = 'AD_PackInitInput'
integer(B8Ki) :: i1
integer(B8Ki) :: LB(1), UB(1)
logical :: PtrInIndex
if (RF%ErrStat >= AbortErrLev) return
call RegPack(RF, allocated(InData%rotors))
if (allocated(InData%rotors)) then
Expand All @@ -1003,6 +1007,13 @@ subroutine AD_PackInitInput(RF, Indata)
call RegPack(RF, InData%defPvap)
call RegPack(RF, InData%WtrDpth)
call RegPack(RF, InData%MSL2SWL)
call RegPack(RF, associated(InData%FlowField))
if (associated(InData%FlowField)) then
call RegPackPointer(RF, c_loc(InData%FlowField), PtrInIndex)
if (.not. PtrInIndex) then
call IfW_FlowField_PackFlowFieldType(RF, InData%FlowField)
end if
end if
if (RegCheckErr(RF, RoutineName)) return
end subroutine

Expand All @@ -1014,6 +1025,8 @@ subroutine AD_UnPackInitInput(RF, OutData)
integer(B8Ki) :: LB(1), UB(1)
integer(IntKi) :: stat
logical :: IsAllocAssoc
integer(B8Ki) :: PtrIdx
type(c_ptr) :: Ptr
if (RF%ErrStat /= ErrID_None) return
if (allocated(OutData%rotors)) deallocate(OutData%rotors)
call RegUnpack(RF, IsAllocAssoc); if (RegCheckErr(RF, RoutineName)) return
Expand Down Expand Up @@ -1043,6 +1056,24 @@ subroutine AD_UnPackInitInput(RF, OutData)
call RegUnpack(RF, OutData%defPvap); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%WtrDpth); if (RegCheckErr(RF, RoutineName)) return
call RegUnpack(RF, OutData%MSL2SWL); if (RegCheckErr(RF, RoutineName)) return
if (associated(OutData%FlowField)) deallocate(OutData%FlowField)
call RegUnpack(RF, IsAllocAssoc); if (RegCheckErr(RF, RoutineName)) return
if (IsAllocAssoc) then
call RegUnpackPointer(RF, Ptr, PtrIdx); if (RegCheckErr(RF, RoutineName)) return
if (c_associated(Ptr)) then
call c_f_pointer(Ptr, OutData%FlowField)
else
allocate(OutData%FlowField,stat=stat)
if (stat /= 0) then
call SetErrStat(ErrID_Fatal, 'Error allocating OutData%FlowField.', RF%ErrStat, RF%ErrMsg, RoutineName)
return
end if
RF%Pointers(PtrIdx) = c_loc(OutData%FlowField)
call IfW_FlowField_UnpackFlowFieldType(RF, OutData%FlowField) ! FlowField
end if
else
OutData%FlowField => null()
end if
end subroutine

subroutine AD_CopyBladePropsType(SrcBladePropsTypeData, DstBladePropsTypeData, CtrlCode, ErrStat, ErrMsg)
Expand Down
6 changes: 3 additions & 3 deletions modules/openfast-library/src/FAST_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -555,9 +555,6 @@ SUBROUTINE FAST_InitializeAll( t_initial, p_FAST, y_FAST, m_FAST, ED, BD, SrvD,
CALL SetModuleSubstepTime(Module_IfW, p_FAST, y_FAST, ErrStat2, ErrMsg2)
CALL SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)

! Set pointers to flowfield
IF (p_FAST%CompAero == Module_AD) AD%p%FlowField => Init%OutData_IfW%FlowField

allocate( y_FAST%Lin%Modules(MODULE_IfW)%Instance(1), stat=ErrStat2)
if (ErrStat2 /= 0 ) then
call SetErrStat(ErrID_Fatal, "Error allocating Lin%Modules(IfW).", ErrStat, ErrMsg, RoutineName )
Expand Down Expand Up @@ -820,6 +817,9 @@ SUBROUTINE FAST_InitializeAll( t_initial, p_FAST, y_FAST, m_FAST, ED, BD, SrvD,
Init%InData_AD%rotors(1)%BladeRootOrientation(:,:,k) = ED%y%BladeRootMotion(k)%RefOrientation(:,:,1)
end do

! Set pointers to flowfield
IF (p_FAST%CompInflow == Module_IfW) Init%InData_AD%FlowField => Init%OutData_IfW%FlowField

CALL AD_Init( Init%InData_AD, AD%Input(1), AD%p, AD%x(STATE_CURR), AD%xd(STATE_CURR), AD%z(STATE_CURR), &
AD%OtherSt(STATE_CURR), AD%y, AD%m, p_FAST%dt_module( MODULE_AD ), Init%OutData_AD, ErrStat2, ErrMsg2 )
CALL SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
Expand Down

0 comments on commit 85365c4

Please sign in to comment.