Skip to content

Commit

Permalink
Flap actuator control - initial commit
Browse files Browse the repository at this point in the history
  • Loading branch information
nikhar-abbas committed Nov 7, 2019
1 parent 2f0f2fb commit ace2cff
Show file tree
Hide file tree
Showing 3 changed files with 56 additions and 16 deletions.
21 changes: 21 additions & 0 deletions src/Controllers.f90
Original file line number Diff line number Diff line change
Expand Up @@ -305,4 +305,25 @@ SUBROUTINE ForeAftDamping(CntrPar, LocalVar, objInst)
END DO

END SUBROUTINE ForeAftDamping
!-------------------------------------------------------------------------------------------------------------------------------
REAL FUNCTION FlapActuator(LocalVar, CntrPar, objInst)
! FlapActuator defines a steady state collective blade flap angle
! Flp_Mode = 0, Nothing
! Flp_Mode = 1, Steady State flap angle
USE ROSCO_Types, ONLY : LocalVariables, ControlParameters, ObjectInstances
IMPLICIT NONE
! Inputs
TYPE(ControlParameters), INTENT(IN) :: CntrPar
TYPE(LocalVariables), INTENT(INOUT) :: LocalVar
TYPE(ObjectInstances), INTENT(INOUT) :: objInst
! Allocate Variables
REAL(4) :: V_towertop ! Estimated velocity of tower top (m/s)
REAL(4) :: Vhat ! Estimated wind speed without towertop motion [m/s]
REAL(4) :: Vhatf ! 30 second low pass filtered Estimated wind speed without towertop motion [m/s]

! Steady flap angle
! avrSWAP() = CntrPar%Flp_Angle
print *,CntrPar%Flp_Angle

END FUNCTION FlapActuator
END MODULE Controllers
26 changes: 16 additions & 10 deletions src/ROSCO_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -94,6 +94,9 @@ MODULE ROSCO_Types
REAL(4), DIMENSION(:), ALLOCATABLE :: PS_WindSpeeds ! Wind speeds corresponding to minimum blade pitch angles [m/s]
REAL(4), DIMENSION(:), ALLOCATABLE :: PS_BldPitchMin ! Minimum blade pitch angles [rad]

INTEGER(4) :: Flp_Mode ! Flap actuator mode {0: off, 1: fixed flap position}
REAL(4) :: Flp_Angle ! Flp_Angle - Blade flap angle (degrees)

REAL(4) :: PC_RtTq99 ! 99% of the rated torque value, using for switching between pitch and torque control, [Nm].
REAL(4) :: VS_MaxOMTq ! Maximum torque at the end of the below-rated region 2, [Nm]
REAL(4) :: VS_MinOMTq ! Minimum torque at the beginning of the below-rated region 2, [Nm]
Expand All @@ -103,16 +106,17 @@ MODULE ROSCO_Types
TYPE, PUBLIC :: LocalVariables
! ---------- From avrSWAP ----------
INTEGER(4) :: iStatus
REAL(4) :: Time
REAL(4) :: DT
REAL(4) :: VS_GenPwr
REAL(4) :: GenSpeed
REAL(4) :: RotSpeed
REAL(4) :: Y_M
REAL(4) :: HorWindV
REAL(4) :: rootMOOP(3)
REAL(4) :: BlPitch(3)
REAL(4) :: Azimuth
REAL(4) :: Time
REAL(4) :: DT
REAL(4) :: VS_GenPwr
REAL(4) :: GenSpeed
REAL(4) :: RotSpeed
REAL(4) :: Y_M
REAL(4) :: HorWindV
REAL(4) :: rootMOOP(3)
REAL(4) :: BlPitch(3)
REAL(4) :: Azimuth
REAL(4) :: BlFlap(3)
INTEGER(4) :: NumBl

! ---------- -Internal controller variables ----------
Expand Down Expand Up @@ -156,6 +160,8 @@ MODULE ROSCO_Types
REAL(4) :: Y_ErrLPFSlow ! Filtered yaw error by slow low pass filter [rad].
REAL(4) :: Y_MErr ! Measured yaw error, measured + setpoint [rad].
REAL(4) :: Y_YawEndT ! Yaw end time [s]. Indicates the time up until which yaw is active with a fixed rate


END TYPE LocalVariables

TYPE, PUBLIC :: ObjectInstances
Expand Down
25 changes: 19 additions & 6 deletions src/ReadSetParameters.f90
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ SUBROUTINE ReadControlParameterFileSub(CntrPar)
READ(UnControllerParameters, *) CntrPar%SS_Mode
READ(UnControllerParameters, *) CntrPar%WE_Mode
READ(UnControllerParameters, *) CntrPar%PS_Mode
READ(UnControllerParameters, *) CntrPar%Flp_Mode
READ(UnControllerParameters, *)

!----------------- FILTER CONSTANTS ---------------------
Expand Down Expand Up @@ -165,6 +166,11 @@ SUBROUTINE ReadControlParameterFileSub(CntrPar)
READ(UnControllerParameters, *) CntrPar%PS_WindSpeeds
ALLOCATE(CntrPar%PS_BldPitchMin(CntrPar%PS_BldPitchMin_N))
READ(UnControllerParameters, *) CntrPar%PS_BldPitchMin
READ(UnControllerParameters, *)

!------------ FLAP ACTUATOR ------------
READ(UnControllerParameters, *)
READ(UnControllerParameters, *) CntrPar%Flp_Angle
! END OF INPUT FILE

!------------------- CALCULATED CONSTANTS -----------------------
Expand Down Expand Up @@ -262,13 +268,20 @@ SUBROUTINE ReadAvrSWAP(avrSWAP, LocalVar)
LocalVar%FA_Acc = avrSWAP(53)
LocalVar%Azimuth = avrSWAP(60)
LocalVar%NumBl = NINT(avrSWAP(61))
LocalVar%BlPitch(1) = avrSWAP(4)
LocalVar%BlPitch(2) = avrSWAP(33)
LocalVar%BlPitch(3) = avrSWAP(34)
! LocalVar%BlPitch(1) = avrSWAP(4)
! LocalVar%BlPitch(2) = avrSWAP(33)
! LocalVar%BlPitch(3) = avrSWAP(34)

! BLADE FLAPS - zero for now
LocalVar%BlFlap(1) = 0 !avrSWAP(4)
LocalVar%BlFlap(2) = 0 !avrSWAP(33)
LocalVar%BlFlap(3) = 0 !avrSWAP(34)


! --- NJA: sometimes feedback bath the previous pitch command helps for numerical stability, sometimes it does not...
! LocalVar%BlPitch(1) = LocalVar%PitCom(1)
! LocalVar%BlPitch(2) = LocalVar%PitCom(2)
! LocalVar%BlPitch(3) = LocalVar%PitCom(3)
LocalVar%BlPitch(1) = LocalVar%PitCom(1)
LocalVar%BlPitch(2) = LocalVar%PitCom(2)
LocalVar%BlPitch(3) = LocalVar%PitCom(3)

END SUBROUTINE ReadAvrSWAP
! -----------------------------------------------------------------------------------
Expand Down

0 comments on commit ace2cff

Please sign in to comment.