Skip to content

Commit

Permalink
Included a general PI controller with outpur saturations in the Funct…
Browse files Browse the repository at this point in the history
…ionToolbox and implemented generator region 2.5 PI torque control *untested*
  • Loading branch information
Sebastiaan Mulders committed Aug 30, 2017
1 parent 72db4bd commit 585f33a
Show file tree
Hide file tree
Showing 2 changed files with 36 additions and 19 deletions.
33 changes: 18 additions & 15 deletions Source/DISCON.f90
Original file line number Diff line number Diff line change
Expand Up @@ -98,6 +98,7 @@ SUBROUTINE DISCON ( avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG ) BIND (C, N
REAL(4), PARAMETER :: VS_RtGnSp = 121.6805 ! Rated generator speed (HSS side), [rad/s]. -- chosen to be 99% of PC_RefSpd
REAL(4) :: VS_RtTq ! Rated torque, [Nm].
REAL(4), PARAMETER :: VS_RtPwr = 5296610.0 ! Rated generator generator power in Region 3, [W]. -- chosen to be 5MW divided by the electrical generator efficiency of 94.4%
REAL(4) :: VS_RtSpd ! Rated generator speed [rad/s]
REAL(4), SAVE :: VS_Slope15 ! Torque/speed slope of region 1 1/2 cut-in torque ramp , [Nm/(rad/s)].
REAL(4), SAVE :: VS_Slope25 ! Torque/speed slope of region 2 1/2 induction generator, [Nm/(rad/s)].
REAL(4), PARAMETER :: VS_SlPc = 10.0 ! Rated generator slip percentage in Region 2 1/2, [%].
Expand Down Expand Up @@ -135,24 +136,25 @@ SUBROUTINE DISCON ( avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG ) BIND (C, N


! Load variables from calling program (See Appendix A of Bladed User's Guide):

BlPitch (1) = avrSWAP( 4)
BlPitch (2) = avrSWAP(33)
BlPitch (3) = avrSWAP(34)
iStatus = NINT( avrSWAP( 1) )
Time = avrSWAP( 2)
DT = avrSWAP( 3)
BlPitch (1) = avrSWAP( 4)
PC_SetPnt = avrSWAP( 5)
PC_MinPit = avrSWAP( 6)
VS_RtSpd = avrSWAP(19)
GenSpeed = avrSWAP(20)
VS_RtTq = avrSWAP(22)
Y_MErr = avrSWAP(24)
HorWindV = avrSWAP(27)
IPC_aziAngle = avrSWAP(60)
iStatus = NINT( avrSWAP( 1) )
NumBl = NINT( avrSWAP(61) )
PC_MinPit = avrSWAP( 6)
PC_SetPnt = avrSWAP( 5)
rootMOOP (1) = avrSWAP(30)
rootMOOP (2) = avrSWAP(31)
rootMOOP (3) = avrSWAP(32)
Time = avrSWAP( 2)
Y_MErr = avrSWAP(24)
VS_RtTq = avrSWAP(22)
BlPitch (2) = avrSWAP(33)
BlPitch (3) = avrSWAP(34)
IPC_aziAngle = avrSWAP(60)
NumBl = NINT( avrSWAP(61) )


!print *, 'from_sc: ', from_sc(1:4)
!to_sc(1) = 5.0;
Expand Down Expand Up @@ -438,7 +440,7 @@ SUBROUTINE DISCON ( avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG ) BIND (C, N

! Filter the HSS (generator) speed measurement:
! Apply Low-Pass Filter
GenSpeedF = LPFilter( GenSpeed, DT, CornerFreq, iStatus, 1) ! This is the first instance of LPFilter
GenSpeedF = LPFilter(GenSpeed, DT, CornerFreq, iStatus, 1) ! This is the first instance of LPFilter


!..............................................................................................................................
Expand All @@ -461,13 +463,14 @@ SUBROUTINE DISCON ( avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG ) BIND (C, N
ELSEIF ( GenSpeedF < VS_TrGnSp ) THEN ! We are in region 2 - optimal torque is proportional to the square of the generator speed
GenTrq = VS_Rgn2K*GenSpeedF*GenSpeedF
ELSE ! We are in region 2 1/2 - simple induction generator transition region
GenTrq = VS_Slope25*( GenSpeedF - VS_SySp )
GenTrq = PI(VS_RtSpd-GenSpeedF,real(-4200),real(-2100),real(35233.0),VS_RtTq,DT,real(35233.0),1)
!GenTrq = VS_Slope25*( GenSpeedF - VS_SySp )
ENDIF


! Saturate the commanded torque using the maximum torque limit:

GenTrq = MIN( GenTrq , VS_MaxTq ) ! Saturate the command using the maximum torque limit
GenTrq = MIN(GenTrq , VS_MaxTq) ! Saturate the command using the maximum torque limit


! Saturate the commanded torque using the torque rate limit:
Expand Down
22 changes: 18 additions & 4 deletions Source/FunctionToolbox.f90
Original file line number Diff line number Diff line change
Expand Up @@ -32,20 +32,34 @@ REAL FUNCTION PI(error,kp,ki,minValue,maxValue,DT,I0,inst)
REAL(4), INTENT(IN) :: minValue
REAL(4), INTENT(IN) :: maxValue
REAL(4), INTENT(IN) :: DT
REAL(4), INTENT(IN) :: inst
INTEGER(4), INTENT(IN) :: inst
REAL(4), INTENT(IN) :: I0

! Local
REAL(4) :: PTerm ! Proportional term
REAL(4), DIMENSION(99), SAVE :: ITermLast ! Integral term signal the last time this controller was called. Supports 99 separate instances.
INTEGER(4) :: i ! Counter for making arrays
REAL(4) :: PTerm ! Proportional term
REAL(4), DIMENSION(99), SAVE :: ITerm ! Integral term, current.
REAL(4), DIMENSION(99), SAVE :: ITermLast ! Integral term, the last time this controller was called. Supports 99 separate instances.
INTEGER(4), DIMENSION(99), SAVE :: FirstCall = (/ (1, i=1,99) /) ! First call of this function?

! Initialize persistent variables/arrays, and set inital condition for integrator term
IF ( FirstCall(inst) == 1 ) THEN
ITerm(1:99) = (/ (real(9999.9), i = 1,99) /)
ITermLast(1:99) = (/ (real(9999.9), i = 1,99) /)

ITerm(inst) = I0
ITermLast(inst) = I0

FirstCall(inst) = 0
END IF

PTerm = kp*error
ITerm(inst) = ITerm(inst) + DT*ki*error
ITerm(inst) = saturate(ITerm(inst),maxValue,minValue)
PI = PTerm + ITerm(inst)
PI = saturate(PI,maxValue,minValue)

END FUNCTION saturate
ITermLast(inst) = ITerm(inst)
END FUNCTION PI
!-------------------------------------------------------------------------------------------------------------------------------
END MODULE FunctionToolbox

0 comments on commit 585f33a

Please sign in to comment.