Skip to content

Commit

Permalink
MultiRot: integration with glue-code
Browse files Browse the repository at this point in the history
  • Loading branch information
ebranlard committed Mar 2, 2021
1 parent 46ebd60 commit 16345c3
Show file tree
Hide file tree
Showing 8 changed files with 263 additions and 237 deletions.
29 changes: 19 additions & 10 deletions modules/aerodyn/src/AeroDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,7 @@ module AeroDyn
! states(z)
PUBLIC :: AD_GetOP !< Routine to pack the operating point values (for linearization) into arrays


contains
!----------------------------------------------------------------------------------------------------------------------------------
!> This subroutine sets the initialization output data structure, which contains data to be returned to the calling program (e.g.,
Expand All @@ -86,6 +87,7 @@ subroutine AD_SetInitOut(p, p_AD, InputFileData, InitOut, errStat, errMsg)
integer(IntKi) :: NumCoords

! Initialize variables for this routine

errStat = ErrID_None
errMsg = ""

Expand All @@ -99,13 +101,13 @@ subroutine AD_SetInitOut(p, p_AD, InputFileData, InitOut, errStat, errMsg)

if (ErrStat >= AbortErrLev) return


do i=1,p%NumOuts
InitOut%WriteOutputHdr(i) = p%OutParam(i)%Name
InitOut%WriteOutputUnt(i) = p%OutParam(i)%Units
end do



! Set the info in WriteOutputHdr and WriteOutputUnt
CALL AllBldNdOuts_InitOut( InitOut, p, p_AD, InputFileData, ErrStat2, ErrMsg2 )
call SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName )
Expand Down Expand Up @@ -190,7 +192,6 @@ subroutine AD_SetInitOut(p, p_AD, InputFileData, InitOut, errStat, errMsg)
END IF

end subroutine AD_SetInitOut

!----------------------------------------------------------------------------------------------------------------------------------
!> This routine is called at the start of the simulation to perform initialization steps.
!! The parameters are set here and not changed during the simulation.
Expand Down Expand Up @@ -469,8 +470,10 @@ logical function Failed()
if (Failed) call Cleanup()
end function Failed
subroutine Cleanup()

CALL AD_DestroyInputFile( InputFileData, ErrStat2, ErrMsg2 )
IF ( UnEcho > 0 ) CLOSE( UnEcho )

end subroutine Cleanup

end subroutine AD_Init
Expand Down Expand Up @@ -1156,6 +1159,7 @@ subroutine AD_End( u, p, x, xd, z, OtherState, y, m, ErrStat, ErrMsg )
ErrMsg = ""


! Place any last minute operations or calculations here:
! End the FVW submodule
if (p%WakeMod == WakeMod_FVW ) then
call FVW_End( m%FVW_u, p%FVW, x%FVW, xd%FVW, z%FVW, OtherState%FVW, m%FVW_y, m%FVW, ErrStat, ErrMsg )
Expand Down Expand Up @@ -1329,7 +1333,6 @@ subroutine AD_CalcOutput( t, u, p, x, xd, z, OtherState, y, m, ErrStat, ErrMsg,
! NOTE: m%BEMT_u(i) indices are set differently from the way OpenFAST typically sets up the u and uTimes arrays
integer, parameter :: indx = 1 ! m%BEMT_u(1) is at t; m%BEMT_u(2) is t+dt
integer(intKi) :: i
integer(intKi) :: j
integer(intKi) :: iR ! Loop on rotors

integer(intKi) :: ErrStat2
Expand Down Expand Up @@ -1516,6 +1519,8 @@ subroutine AD_CalcConstrStateResidual( Time, u, p, p_AD, x, xd, z, OtherState, m
INTEGER(IntKi), INTENT( OUT) :: ErrStat !< Error status of the operation
CHARACTER(*), INTENT( OUT) :: ErrMsg !< Error message if ErrStat /= ErrID_None



! Local variables
integer(intKi) :: iR ! rotor index
integer(intKi) :: ErrStat2
Expand Down Expand Up @@ -2421,7 +2426,6 @@ SUBROUTINE ValidateInputData( InitInp, InputFileData, NumBl, ErrStat, ErrMsg )
end if
end if


END SUBROUTINE ValidateInputData
!----------------------------------------------------------------------------------------------------------------------------------
!> This subroutine sets up the data structures and initializes AirfoilInfo to get the necessary AFI parameters. It then verifies
Expand Down Expand Up @@ -2647,6 +2651,7 @@ SUBROUTINE Init_BEMTmodule( InputFileData, RotInputFileData, u_AD, u, p, p_AD, x
InitInp%numReIterations = 1 ! This is currently not available in the input file and is only for testing
InitInp%maxIndIterations = InputFileData%MaxIter


call AllocAry(InitInp%chord, InitInp%numBladeNodes,InitInp%numBlades,'chord', ErrStat2,ErrMsg2); call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
call AllocAry(InitInp%AFindx,InitInp%numBladeNodes,InitInp%numBlades,'AFindx',ErrStat2,ErrMsg2); call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
call AllocAry(InitInp%zHub, InitInp%numBlades,'zHub', ErrStat2,ErrMsg2); call SetErrStat(ErrStat2,ErrMsg2,ErrStat,ErrMsg,RoutineName)
Expand Down Expand Up @@ -2730,6 +2735,7 @@ subroutine Cleanup()
call BEMT_DestroyInitInput( InitInp, ErrStat2, ErrMsg2 )
call BEMT_DestroyInitOutput( InitOut, ErrStat2, ErrMsg2 )
end subroutine Cleanup

END SUBROUTINE Init_BEMTmodule

!----------------------------------------------------------------------------------------------------------------------------------
Expand All @@ -2745,10 +2751,7 @@ SUBROUTINE Init_FVWmodule( InputFileData, u_AD, u, p, x, xd, z, OtherState, m, E
type(FVW_DiscreteStateType), intent( out) :: xd !< Initial discrete states
type(FVW_ConstraintStateType), intent( out) :: z !< Initial guess of the constraint states
type(FVW_OtherStateType), intent( out) :: OtherState !< Initial other states
! type(FVW_OutputType), intent( out) :: y !< Initial system outputs (outputs are not calculated;
!! only the output mesh is initialized)
! type(FVW_MiscVarType), intent( out) :: m !< Initial misc/optimization variables
type(AD_MiscVarType), intent( out) :: m !< Initial misc/optimization variables
type(AD_MiscVarType), intent(inout) :: m !< Initial misc/optimization variables
integer(IntKi), intent( out) :: errStat !< Error status of the operation
character(*), intent( out) :: errMsg !< Error message if ErrStat /= ErrID_None

Expand Down Expand Up @@ -2868,6 +2871,7 @@ SUBROUTINE Init_FVWmodule( InputFileData, u_AD, u, p, x, xd, z, OtherState, m, E
ALLOCATE( InitInp%WingsMesh(p%rotors(iR)%NumBlades), STAT = ErrStat2 ) ! TODO TODO
IF (ErrStat2 /= 0) THEN
CALL SetErrStat ( ErrID_Fatal, 'Could not allocate InitInp%WingsMesh (meshes)', ErrStat,ErrMsg,RoutineName )
call Cleanup()
RETURN
END IF
DO IB = 1, p%rotors(iR)%NumBlades
Expand All @@ -2880,7 +2884,10 @@ SUBROUTINE Init_FVWmodule( InputFileData, u_AD, u, p, x, xd, z, OtherState, m, E
,ErrStat = ErrStat2 &
,ErrMess = ErrMsg2 )
CALL SetErrStat ( ErrStat2, ErrMsg2, ErrStat,ErrMsg,RoutineName )
IF (ErrStat >= AbortErrLev) RETURN
IF (ErrStat >= AbortErrLev) then
call Cleanup()
RETURN
endif
ENDDO

enddo ! iR, rotors TODO TODO
Expand All @@ -2898,6 +2905,8 @@ SUBROUTINE Init_FVWmodule( InputFileData, u_AD, u, p, x, xd, z, OtherState, m, E
if (.not. equalRealNos(Interval, p%DT) ) &
call SetErrStat( ErrID_Fatal, "DTAero was changed in Init_FVWmodule(); this is not allowed yet.", ErrStat2, ErrMsg2, RoutineName)

call CleanUp()

contains
subroutine Cleanup()
call FVW_DestroyInitInput( InitInp, ErrStat2, ErrMsg2 )
Expand Down Expand Up @@ -3544,6 +3553,7 @@ SUBROUTINE TwrInfl_NearestPoint(p, u, BladeNodePosition, r_TowerBlade, theta_tow

END SUBROUTINE TwrInfl_NearestPoint
!----------------------------------------------------------------------------------------------------------------------------------

!++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
! ###### The following four routines are Jacobian routines for linearization capabilities #######
! If the module does not implement them, set ErrStat = ErrID_Fatal in AD_Init() when InitInp%Linearize is .true.
Expand Down Expand Up @@ -4150,7 +4160,6 @@ subroutine cleanup()
end subroutine cleanup

END SUBROUTINE RotJacobianPContState

!----------------------------------------------------------------------------------------------------------------------------------
!> Routine to compute the Jacobians of the output (Y), continuous- (X), discrete- (Xd), and constraint-state (Z) functions
!! with respect to the discrete states (xd). The partial derivatives dY/dxd, dX/dxd, dXd/dxd, and dZ/dxd are returned.
Expand Down
2 changes: 1 addition & 1 deletion modules/aerodyn/src/AeroDyn_Driver_Subs.f90
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,7 @@ subroutine Init_AeroDyn(iCase, DvrData, AD, dt, errStat, errMsg)
errMsg = ''


allocate(InitInData%rotors(1), InitOutData%rotors(1), stat=errStat)
allocate(InitInData%rotors(1), stat=errStat)
if (errStat/=0) then
call SetErrStat( ErrID_Fatal, 'Allocating rotors', errStat, errMsg, RoutineName )
call Cleanup()
Expand Down
3 changes: 3 additions & 0 deletions modules/aerodyn/src/AeroDyn_IO.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1767,6 +1767,8 @@ subroutine Calc_WriteOutput_BEMT

m%AllOuts( RtAeroPwr ) = m%BEMT_u(indx)%omega * m%AllOuts( RtAeroMxh )



m%AllOuts( RtTSR ) = m%BEMT_u(indx)%TSR

if ( EqualRealNos( m%V_dot_x, 0.0_ReKi ) ) then
Expand Down Expand Up @@ -3270,6 +3272,7 @@ SUBROUTINE SetOutParam(OutList, p, p_AD, ErrStat, ErrMsg )


! ..... Developer must add checking for invalid inputs here: .....

!bjj: do we want to avoid outputting this if we haven't used tower aero?

if ( p%TwrPotent == TwrPotent_none .and. p%TwrShadow == TwrShadow_none ) then
Expand Down
8 changes: 4 additions & 4 deletions modules/openfast-library/src/FAST_Library.f90
Original file line number Diff line number Diff line change
Expand Up @@ -526,8 +526,8 @@ subroutine FAST_OpFM_Init(iTurb, TMax, InputFileName_c, TurbID, NumSC2Ctrl, NumC
NumBl_c = SIZE(Turbine(iTurb)%AD14%Input(1)%InputMarkers)
NumBlElem_c = Turbine(iTurb)%AD14%Input(1)%InputMarkers(1)%Nnodes
ELSEIF (Turbine(iTurb)%p_FAST%CompAero == MODULE_AD) THEN
NumBl_c = SIZE(Turbine(iTurb)%AD%Input(1)%BladeMotion)
NumBlElem_c = Turbine(iTurb)%AD%Input(1)%BladeMotion(1)%Nnodes
NumBl_c = SIZE(Turbine(iTurb)%AD%Input(1)%rotors(1)%BladeMotion)
NumBlElem_c = Turbine(iTurb)%AD%Input(1)%rotors(1)%BladeMotion(1)%Nnodes
ELSE
NumBl_c = 0
NumBlElem_c = 0
Expand Down Expand Up @@ -610,8 +610,8 @@ subroutine FAST_OpFM_Restart(iTurb, CheckpointRootName_c, AbortErrLev_c, dt_c, n
n_t_global_c = n_t_global
AbortErrLev_c = AbortErrLev
NumOuts_c = min(MAXOUTPUTS, 1 + SUM( Turbine(iTurb)%y_FAST%numOuts )) ! includes time
numBlades_c = Turbine(iTurb)%ad%p%numblades
numElementsPerBlade_c = Turbine(iTurb)%ad%p%numblnds ! I'm not sure if FASTv8 can handle different number of blade nodes for each blade.
numBlades_c = Turbine(iTurb)%ad%p%rotors(1)%numblades
numElementsPerBlade_c = Turbine(iTurb)%ad%p%rotors(1)%numblnds ! I'm not sure if FASTv8 can handle different number of blade nodes for each blade.
dt_c = Turbine(iTurb)%p_FAST%dt

ErrStat_c = ErrStat
Expand Down
Loading

0 comments on commit 16345c3

Please sign in to comment.