Skip to content

Commit

Permalink
Merge pull request #4 from andrew-platt/BMertz/f/flap_control
Browse files Browse the repository at this point in the history
Minor updates to Flap Control
  • Loading branch information
Ben-Mertz authored Mar 9, 2020
2 parents 181e12e + 6233ada commit c4db7dd
Show file tree
Hide file tree
Showing 6 changed files with 103 additions and 82 deletions.
25 changes: 17 additions & 8 deletions modules/openfast-library/src/FAST_Solver.f90
Original file line number Diff line number Diff line change
Expand Up @@ -446,12 +446,11 @@ SUBROUTINE AD_InputSolve_IfW( p_FAST, u_AD, y_IfW, y_OpFM, ErrStat, ErrMsg )
END SUBROUTINE AD_InputSolve_IfW
!----------------------------------------------------------------------------------------------------------------------------------
!> This routine sets all the AeroDyn inputs, except for the wind inflow values.
SUBROUTINE AD_InputSolve_NoIfW( p_FAST, u_AD, p_AD, y_SrvD, y_ED, BD, MeshMapData, ErrStat, ErrMsg )
SUBROUTINE AD_InputSolve_NoIfW( p_FAST, u_AD, y_SrvD, y_ED, BD, MeshMapData, ErrStat, ErrMsg )

! Passed variables
TYPE(FAST_ParameterType), INTENT(IN ) :: p_FAST !< FAST parameter data
TYPE(AD_InputType), INTENT(INOUT) :: u_AD !< The inputs to AeroDyn14
TYPE(AD_ParameterType), INTENT(IN ) :: p_AD !< Parameters from AeroDyne
TYPE(SrvD_OutputType), INTENT(IN ) :: y_SrvD !< ServoDyn outputs
TYPE(ED_OutputType), INTENT(IN) :: y_ED !< The outputs from the structural dynamics module
TYPE(BeamDyn_Data), INTENT(IN) :: BD !< The data from BeamDyn (want the outputs only, but it's in an array)
Expand Down Expand Up @@ -517,12 +516,22 @@ SUBROUTINE AD_InputSolve_NoIfW( p_FAST, u_AD, p_AD, y_SrvD, y_ED, BD, MeshMapDat


END IF
! Set Conrol parameter (i.e. flaps)
DO k_bl=1,p_AD%numBlades
DO k_bn=1,p_AD%NumBlNds
u_AD%UserProp(k_bn , k_bl) = y_SrvD%BlFlapCom(k_bl) !bem: This takes in flap deflection for each blade (only one flap deflection angle per blade) from ServoDyn (which comes from Bladed style DLL controller)


! Set Conrol parameter (i.e. flaps) if using ServoDyn
! bem: This takes in flap deflection for each blade (only one flap deflection angle per blade),
! from ServoDyn (which comes from Bladed style DLL controller)
! Commanded Airfoil UserProp for blade (must be same units as given in AD15 airfoil tables)
! This is passed to AD15 to be interpolated with the airfoil table userprop column
! (might be used for airfoil flap angles for example)
if (p_FAST%CompServo == Module_SrvD) then
DO k_bl=1,size(u_AD%UserProp,DIM=2)
DO k_bn=1,size(u_AD%UserProp,DIM=1)
u_AD%UserProp(k_bn , k_bl) = y_SrvD%BlAirfoilCom(k_bl) ! Must be same units as given in airfoil (no unit conversions handled in code)
END DO
END DO
endif


END SUBROUTINE AD_InputSolve_NoIfW
!----------------------------------------------------------------------------------------------------------------------------------
Expand Down Expand Up @@ -4485,7 +4494,7 @@ SUBROUTINE CalcOutputs_And_SolveForInputs( n_t_global, this_time, this_state, ca

ELSEIF ( p_FAST%CompAero == Module_AD ) THEN

CALL AD_InputSolve_NoIfW( p_FAST, AD%Input(1), AD%p, SrvD%y, ED%Output(1), BD, MeshMapData, ErrStat2, ErrMsg2 )
CALL AD_InputSolve_NoIfW( p_FAST, AD%Input(1), SrvD%y, ED%Output(1), BD, MeshMapData, ErrStat2, ErrMsg2 )
CALL SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName )

! because we're not calling InflowWind_CalcOutput or getting new values from OpenFOAM,
Expand Down Expand Up @@ -4810,7 +4819,7 @@ SUBROUTINE SolveOption2b_Inp2IfW(this_time, this_state, p_FAST, m_FAST, ED, BD,
ELSE IF ( p_FAST%CompAero == Module_AD ) THEN

! note that this uses BD outputs, which are from the previous step (and need to be initialized)
CALL AD_InputSolve_NoIfW( p_FAST, AD%Input(1), AD%p, SrvD%y, ED%Output(1), BD, MeshMapData, ErrStat2, ErrMsg2 )
CALL AD_InputSolve_NoIfW( p_FAST, AD%Input(1), SrvD%y, ED%Output(1), BD, MeshMapData, ErrStat2, ErrMsg2 )
CALL SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName )

END IF
Expand Down
Binary file modified modules/openfast-library/src/OutListParameters.xlsx
Binary file not shown.
10 changes: 7 additions & 3 deletions modules/servodyn/src/BladedInterface.f90
Original file line number Diff line number Diff line change
Expand Up @@ -714,9 +714,13 @@ SUBROUTINE Retrieve_avrSWAP( p, dll_data, ErrStat, ErrMsg )
!> * Record 108: Yaw brake torque demand; ignored in ServoDyn

!> * Records 120-129: User-defined variables 1-10; ignored in ServoDyn
dll_data%BlFlapCom(1) = dll_data%avrSWAP(120)
dll_data%BlFlapCom(2) = dll_data%avrSWAP(121)
dll_data%BlFlapCom(3) = dll_data%avrSWAP(122)
! Commanded Airfoil UserProp for blade (must be same units as given in AD15 airfoil tables)
! This is passed to AD15 to be interpolated with the airfoil table userprop column
! (might be used for airfoil flap angles for example)
dll_data%BlAirfoilCom(1) = dll_data%avrSWAP(120)
dll_data%BlAirfoilCom(2) = dll_data%avrSWAP(121)
dll_data%BlAirFoilCom(3) = dll_data%avrSWAP(122)

!> * Records 130-142: Reserved

!> * L1: variables for logging output; not yet implemented in ServoDyn
Expand Down
56 changes: 32 additions & 24 deletions modules/servodyn/src/ServoDyn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -119,11 +119,11 @@ MODULE ServoDyn
INTEGER(IntKi), PARAMETER :: TTMD_YQ = 14
INTEGER(IntKi), PARAMETER :: TTMD_YQD = 15

! Flap Control:
! Airfoil Control (might be used for flap actuation):

INTEGER(IntKi), PARAMETER :: BlFlap1 = 16
INTEGER(IntKi), PARAMETER :: BlFlap2 = 17
INTEGER(IntKi), PARAMETER :: BlFlap3 = 18
INTEGER(IntKi), PARAMETER :: BlAirFlC1 = 16
INTEGER(IntKi), PARAMETER :: BlAirFlC2 = 17
INTEGER(IntKi), PARAMETER :: BlAirFlC3 = 18

! The maximum number of output channels which can be output by the code.
INTEGER(IntKi), PARAMETER :: MaxOutPts = 18
Expand All @@ -132,7 +132,7 @@ MODULE ServoDyn
! ===================================================================================================

INTEGER(IntKi), PARAMETER :: BlPitchC (3) = (/ BlPitchC1, BlPitchC2, BlPitchC3 /)
INTEGER(IntKi), PARAMETER :: BlFlapC (3) = (/ BlFlap1, BlFlap2, BlFlap3 /)
INTEGER(IntKi), PARAMETER :: BlAirfoilC (3) = (/ BlAirFlC1, BlAirFlC2, BlAirFlC3 /)

!bjj: added parameters here (after the "(/ /)" above) so VS2010 doesn't get so confused with the previous statement.

Expand Down Expand Up @@ -395,11 +395,13 @@ SUBROUTINE SrvD_Init( InitInp, u, p, x, xd, z, OtherState, y, m, Interval, InitO
CALL AllocAry( y%BlPitchCom, p%NumBl, 'BlPitchCom', ErrStat2, ErrMsg2 )
CALL CheckError( ErrStat2, ErrMsg2 )
IF (ErrStat >= AbortErrLev) RETURN

CALL AllocAry( y%BlFlapCom, p%NumBl, 'BlFlapCom', ErrStat2, ErrMsg2 )

! Commanded Airfoil UserProp for blade. Must be same units as given in AD15 airfoil tables
! This is passed to AD15 to be interpolated with the airfoil table userprop column
CALL AllocAry( y%BlAirfoilCom, p%NumBl, 'BlAirfoilCom', ErrStat2, ErrMsg2 )
CALL CheckError( ErrStat2, ErrMsg2 )
IF (ErrStat >= AbortErrLev) RETURN
y%BlFlapCom = 0.0
y%BlAirfoilCom = 0.0_ReKi

! tip brakes - this may be added back, later, so we'll keep these here for now
CALL AllocAry( y%TBDrCon, p%NumBl, 'TBDrCon', ErrStat2, ErrMsg2 )
Expand Down Expand Up @@ -950,8 +952,10 @@ SUBROUTINE SrvD_CalcOutput( t, u, p, x, xd, z, OtherState, y, m, ErrStat, ErrMsg
CALL SetErrStat( ErrStat2, ErrMsg2, ErrStat, ErrMsg, RoutineName )
END IF

! Set ServoDyn output for flap deflection angle
y%BlFlapCom(1:p%NumBl) = m%dll_data%BlFlapCom
! Commanded Airfoil UserProp for blade (must be same units as given in AD15 airfoil tables)
! This is passed to AD15 to be interpolated with the airfoil table userprop column
! (might be used for airfoil flap angles for example)
y%BlAirfoilCom(1:p%NumBl) = m%dll_data%BlAirfoilCom(1:p%NumBl)

IF (ALLOCATED(y%SuperController)) THEN
y%SuperController = m%dll_data%SCoutput
Expand Down Expand Up @@ -993,8 +997,8 @@ SUBROUTINE SrvD_CalcOutput( t, u, p, x, xd, z, OtherState, y, m, ErrStat, ErrMsg
AllOuts(HSSBrTqC)= 0.001*y%HSSBrTrqC

DO K=1,p%NumBl
AllOuts( BlPitchC(K) ) = y%BlPitchCom(K)*R2D
AllOuts( BlFlapC(K) ) = y%BlFlapCom(K)
AllOuts( BlPitchC(K) ) = y%BlPitchCom(K)*R2D
AllOuts( BlAirfoilC(K) ) = y%BlAirfoilCom(K)
END DO

AllOuts(YawMomCom) = -0.001*y%YawMom
Expand Down Expand Up @@ -3170,18 +3174,21 @@ SUBROUTINE SetOutParam(OutList, p, ErrStat, ErrMsg )
CHARACTER(ChanLen) :: OutListTmp ! A string to temporarily hold OutList(I)
CHARACTER(*), PARAMETER :: RoutineName = "SetOutParam"

CHARACTER(OutStrLenM1), PARAMETER :: ValidParamAry(19) = (/ & ! This lists the names of the allowed parameters, which must be sorted alphabetically
"BLFLAP1 ","BLFLAP2 ","BLFLAP3 ","BLPITCHC1","BLPITCHC2","BLPITCHC3","GENPWR ", &
"GENTQ ","HSSBRTQC ","NTMD_XQ ","NTMD_XQD ","NTMD_YQ ","NTMD_YQD ","TTMD_XQ ", &
"TTMD_XQD ","TTMD_YQ ","TTMD_YQD ","YAWMOM ","YAWMOMCOM"/)
INTEGER(IntKi), PARAMETER :: ParamIndxAry(19) = (/ & ! This lists the index into AllOuts(:) of the allowed parameters ValidParamAry(:)
BlFlap1 , BlFlap2 , BlFlap3 , BlPitchC1 , BlPitchC2 , BlPitchC3 , GenPwr , &
GenTq , HSSBrTqC , NTMD_XQ , NTMD_XQD , NTMD_YQ , NTMD_YQD , TTMD_XQ , &
TTMD_XQD , TTMD_YQ , TTMD_YQD , YawMomCom , YawMomCom/)
CHARACTER(ChanLen), PARAMETER :: ParamUnitsAry(19) = (/ & ! This lists the units corresponding to the allowed parameters
"(deg) ","(deg) ","(deg) ","(deg) ","(deg) ","(deg) ","(kW) ", &
"(kN-m) ","(kN-m) ","(m) ","(m/s) ","(m) ","(m/s) ","(m) ", &
"(m/s) ","(m) ","(m/s) ","(kN-m) ","(kN-m) "/)
CHARACTER(OutStrLenM1), PARAMETER :: ValidParamAry(22) = (/ & ! This lists the names of the allowed parameters, which must be sorted alphabetically
"BLAIRFLC1","BLAIRFLC2","BLAIRFLC3","BLFLAP1 ","BLFLAP2 ","BLFLAP3 ","BLPITCHC1", &
"BLPITCHC2","BLPITCHC3","GENPWR ","GENTQ ","HSSBRTQC ","NTMD_XQ ","NTMD_XQD ", &
"NTMD_YQ ","NTMD_YQD ","TTMD_XQ ","TTMD_XQD ","TTMD_YQ ","TTMD_YQD ","YAWMOM ", &
"YAWMOMCOM"/)
INTEGER(IntKi), PARAMETER :: ParamIndxAry(22) = (/ & ! This lists the index into AllOuts(:) of the allowed parameters ValidParamAry(:)
BlAirFlC1 , BlAirFlC2 , BlAirFlC3 , BlAirFlC1 , BlAirFlC2 , BlAirFlC3 , BlPitchC1 , &
BlPitchC2 , BlPitchC3 , GenPwr , GenTq , HSSBrTqC , NTMD_XQ , NTMD_XQD , &
NTMD_YQ , NTMD_YQD , TTMD_XQ , TTMD_XQD , TTMD_YQ , TTMD_YQD , YawMomCom , &
YawMomCom /)
CHARACTER(ChanLen), PARAMETER :: ParamUnitsAry(22) = (/ & ! This lists the units corresponding to the allowed parameters
"(-) ","(-) ","(-) ","(-) ","(-) ","(-) ","(deg) ", &
"(deg) ","(deg) ","(kW) ","(kN-m) ","(kN-m) ","(m) ","(m/s) ", &
"(m) ","(m/s) ","(m) ","(m/s) ","(m) ","(m/s) ","(kN-m) ", &
"(kN-m) "/)


! Initialize values
Expand All @@ -3192,6 +3199,7 @@ SUBROUTINE SetOutParam(OutList, p, ErrStat, ErrMsg )

! Determine which inputs are not valid

InvalidOutput(BlAirFlC3) = ( p%NumBl < 3 )
InvalidOutput(BlPitchC3) = ( p%NumBl < 3 )
InvalidOutput( NTMD_XQ) = ( .not. p%CompNTMD )
InvalidOutput( NTMD_XQD) = ( .not. p%CompNTMD )
Expand Down
4 changes: 2 additions & 2 deletions modules/servodyn/src/ServoDyn_Registry.txt
Original file line number Diff line number Diff line change
Expand Up @@ -133,7 +133,7 @@ typedef ^ BladedDLLType IntKi GenState - - - "Generator state from Bladed DLL" N
#typedef ^ BladedDLLType ReKi ElecPwr - - - "Electrical power sent to Bladed DLL" W
typedef ^ BladedDLLType ReKi BlPitchCom 3 - - "Commanded blade pitch angles" radians
typedef ^ BladedDLLType ReKi PrevBlPitch 3 - - "Previously commanded blade pitch angles" radians
typedef ^ BladedDLLType ReKi BlFlapCom 3 - - "Commanded lap deflection angles" degrees
typedef ^ BladedDLLType ReKi BlAirfoilCom 3 - - "Commanded Airfoil UserProp for blade. Passed to AD15 for airfoil interpolation (must be same units as given in AD15 airfoil tables)" -
typedef ^ BladedDLLType SiKi SCoutput {:} - - "controller output to supercontroller" -

# ..... States ....................................................................................................................
Expand Down Expand Up @@ -330,7 +330,7 @@ typedef ^ InputType SiKi SuperController {:} - - "A swap array: used to pass inp
# Define outputs that are not on this mesh here:
typedef ^ OutputType ReKi WriteOutput {:} - - "Data to be written to an output file: see WriteOutputHdr for names of each variable" "see WriteOutputUnt"
typedef ^ OutputType ReKi BlPitchCom {:} - - "Commanded blade pitch angles" radians
typedef ^ OutputType ReKi BlFlapCom {:} - - "Commanded flap deflection angles" degrees
typedef ^ OutputType ReKi BlAirfoilCom {:} - - "Commanded Airfoil UserProp for blade. Passed to AD15 for airfoil interpolation (must be same units as given in AD15 airfoil tables)" -
typedef ^ OutputType ReKi YawMom - - - "Torque transmitted through the yaw bearing" N-m
typedef ^ OutputType ReKi GenTrq - - - "Electrical generator torque" N-m
typedef ^ OutputType ReKi HSSBrTrqC - - - "Commanded HSS brake torque" N-m
Expand Down
Loading

0 comments on commit c4db7dd

Please sign in to comment.