Skip to content

Commit

Permalink
Fix low wind speed pitch+torque saturation bug
Browse files Browse the repository at this point in the history
  • Loading branch information
nikhar-abbas committed Jul 22, 2020
1 parent b3df093 commit 5f92876
Show file tree
Hide file tree
Showing 4 changed files with 13 additions and 14 deletions.
14 changes: 6 additions & 8 deletions src/ControllerBlocks.f90
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ SUBROUTINE StateMachine(CntrPar, LocalVar)
! Initialize State machine if first call
IF (LocalVar%iStatus == 0) THEN ! .TRUE. if we're on the first call to the DLL

IF (LocalVar%PitCom(1) >= CntrPar%VS_Rgn3Pitch) THEN ! We are in region 3
IF (LocalVar%PitCom(1) >= LocalVar%VS_Rgn3Pitch) THEN ! We are in region 3
IF (CntrPar%VS_ControlMode == 1) THEN ! Constant power tracking
LocalVar%VS_State = 5
LocalVar%PC_State = 1
Expand All @@ -78,14 +78,12 @@ SUBROUTINE StateMachine(CntrPar, LocalVar)
END IF

! --- Torque control state machine ---
IF (LocalVar%PC_PitComT >= CntrPar%VS_Rgn3Pitch) THEN
IF (LocalVar%PC_PitComT >= LocalVar%VS_Rgn3Pitch) THEN

IF (LocalVar%PC_PitComT >= LocalVar%PC_MinPit + CntrPar%PC_Switch) THEN ! Make sure we aren't implement pitch saturation
IF (CntrPar%VS_ControlMode == 1) THEN ! Region 3
LocalVar%VS_State = 5 ! Constant power tracking
ELSE
LocalVar%VS_State = 4 ! Constant torque tracking
END IF
IF (CntrPar%VS_ControlMode == 1) THEN ! Region 3
LocalVar%VS_State = 5 ! Constant power tracking
ELSE
LocalVar%VS_State = 4 ! Constant torque tracking
END IF
ELSE
IF (LocalVar%GenArTq >= CntrPar%VS_MaxOMTq*1.01) THEN ! Region 2 1/2 - active PI torque control
Expand Down
4 changes: 2 additions & 2 deletions src/Controllers.f90
Original file line number Diff line number Diff line change
Expand Up @@ -88,9 +88,9 @@ SUBROUTINE PitchControl(avrSWAP, CntrPar, LocalVar, objInst)
! Pitch Saturation
IF (CntrPar%PS_Mode == 1) THEN
LocalVar%PC_MinPit = PitchSaturation(LocalVar,CntrPar,objInst)
LocalVar%PC_MinPit = max(LocalVar%PC_MinPit, CntrPar%PC_MinPit)
LocalVar%PC_MinPit = max(LocalVar%PC_MinPit, CntrPar%PC_FinePit)
ELSE
LocalVar%PC_MinPit = CntrPar%PC_MinPit
LocalVar%PC_MinPit = CntrPar%PC_FinePit
ENDIF

! Shutdown
Expand Down
2 changes: 1 addition & 1 deletion src/ROSCO_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,6 @@ MODULE ROSCO_Types
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]
REAL(4) :: VS_Rgn3Pitch ! Pitch angle at which the state machine switches to region 3, [rad].

END TYPE ControlParameters

Expand Down Expand Up @@ -184,6 +183,7 @@ MODULE ROSCO_Types
REAL(4) :: VS_SpdErrBr ! Current speed error for region 1.5 PI controller (generator torque control) [rad/s].
REAL(4) :: VS_SpdErr ! Current speed error for tip-speed-ratio tracking controller (generator torque control) [rad/s].
INTEGER(4) :: VS_State ! State of the torque control system
REAL(4) :: VS_Rgn3Pitch ! Pitch angle at which the state machine switches to region 3, [rad].
REAL(4) :: WE_Vw ! Estimated wind speed [m/s]
REAL(4) :: WE_Vw_F ! Filtered estimated wind speed [m/s]
REAL(4) :: WE_VwI ! Integrated wind speed quantity for estimation [m/s]
Expand Down
7 changes: 4 additions & 3 deletions src/ReadSetParameters.f90
Original file line number Diff line number Diff line change
Expand Up @@ -215,7 +215,6 @@ SUBROUTINE ReadControlParameterFileSub(CntrPar, accINFILE, accINFILE_size)!, acc
CntrPar%PC_RtTq99 = CntrPar%VS_RtTq*0.99
CntrPar%VS_MinOMTq = CntrPar%VS_Rgn2K*CntrPar%VS_MinOMSpd**2
CntrPar%VS_MaxOMTq = CntrPar%VS_Rgn2K*CntrPar%VS_RefSpd**2
CntrPar%VS_Rgn3Pitch = CntrPar%PC_FinePit + CntrPar%PC_Switch

CLOSE(UnControllerParameters)

Expand Down Expand Up @@ -283,8 +282,10 @@ SUBROUTINE ComputeVariablesSetpoints(CntrPar, LocalVar, objInst)
! Define transition region setpoint errors
LocalVar%VS_SpdErrAr = VS_RefSpd - LocalVar%GenSpeedF ! Current speed error - Region 2.5 PI-control (Above Rated)
LocalVar%VS_SpdErrBr = CntrPar%VS_MinOMSpd - LocalVar%GenSpeedF ! Current speed error - Region 1.5 PI-control (Below Rated)



! Region 3 minimum pitch angle for state machine
LocalVar%VS_Rgn3Pitch = LocalVar%PC_MinPit + CntrPar%PC_Switch

END SUBROUTINE ComputeVariablesSetpoints
! -----------------------------------------------------------------------------------
! Read avrSWAP array passed from ServoDyn
Expand Down

0 comments on commit 5f92876

Please sign in to comment.