Skip to content

Commit

Permalink
Added type ObjectInstances, to enable object-oriented-like programmin…
Browse files Browse the repository at this point in the history
…g of filters possible
  • Loading branch information
Sebastiaan Mulders committed Oct 25, 2017
1 parent 096c996 commit 0a86bd3
Show file tree
Hide file tree
Showing 8 changed files with 85 additions and 45 deletions.
3 changes: 2 additions & 1 deletion .gitignore
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
~$README.docx
ControllerSchematic.pptx
Source/Obj_win32
Source/Obj_win32
*.mod
Binary file modified DISCON/DISCON_gwin32.dll
Binary file not shown.
27 changes: 20 additions & 7 deletions Source/DISCON.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ SUBROUTINE DISCON (avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG) BIND (C, NAM
USE :: ReadParameters
USE :: FunctionToolbox
USE :: Filters
USE DRC_Types, ONLY : ObjectInstances

IMPLICIT NONE
#ifndef IMPLICIT_DLLEXPORT
Expand All @@ -38,6 +39,10 @@ SUBROUTINE DISCON (avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG) BIND (C, NAM
CHARACTER(KIND=C_CHAR), INTENT(IN) :: avcOUTNAME(NINT(avrSWAP(51))) ! OUTNAME (Simulation RootName)
CHARACTER(KIND=C_CHAR), INTENT(INOUT) :: avcMSG(NINT(avrSWAP(49))) ! MESSAGE (Message from DLL to simulation code [ErrMsg]) The message which will be displayed by the calling program if aviFAIL <> 0.

! Types

TYPE(ObjectInstances) :: objInst

! Local Variables:

REAL(4), SAVE :: LastGenTrq ! Commanded electrical generator torque the last time the controller was called, [Nm].
Expand All @@ -48,6 +53,7 @@ SUBROUTINE DISCON (avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG) BIND (C, NAM
REAL(4), SAVE :: testValue ! TestValue

INTEGER(4) :: I ! Generic index.
INTEGER(4) :: instLPF ! Instance counter for all first-order low-pass filters
INTEGER(4) :: K ! Loops through blades.
INTEGER(4), PARAMETER :: UnDb = 85 ! I/O unit for the debugging information
INTEGER(4), PARAMETER :: UnDb2 = 86 ! I/O unit for the debugging information
Expand All @@ -68,6 +74,13 @@ SUBROUTINE DISCON (avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG) BIND (C, NAM
! Initialize aviFAIL to 0:
aviFAIL = 0

! Initialize all filter instance counters at 1
objInst%instLPF = 1
objInst%instSecLPF = 1
objInst%instHPF = 1
objInst%instNotchSlopes = 1
objInst%instNotch = 1

! Read any External Controller Parameters specified in the User Interface
! and initialize variables:
IF (LocalVar%iStatus == 0) THEN ! .TRUE. if we're on the first call to the DLL
Expand Down Expand Up @@ -258,7 +271,7 @@ SUBROUTINE DISCON (avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG) BIND (C, NAM

! Filter the HSS (generator) speed measurement:
! Apply Low-Pass Filter
LocalVar%GenSpeedF = SecLPFilter(LocalVar%GenSpeed, LocalVar%DT, CntrPar%CornerFreq, 0.7, LocalVar%iStatus, 1) ! This is the first instance of a second order LPFilter
LocalVar%GenSpeedF = SecLPFilter(LocalVar%GenSpeed, LocalVar%DT, CntrPar%CornerFreq, 0.7, LocalVar%iStatus, .FALSE., objInst%instSecLPF) ! This is the first instance of a second order LPFilter

! Calculate yaw-alignment error
LocalVar%Y_MErr = LocalVar%Y_M + CntrPar%Y_MErrSet
Expand Down Expand Up @@ -347,7 +360,7 @@ SUBROUTINE DISCON (avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG) BIND (C, NAM

! Individual pitch control
IF ((CntrPar%IPC_ControlMode == 1) .OR. (CntrPar%Y_ControlMode == 2)) THEN
CALL IPC(LocalVar%rootMOOP, LocalVar%Azimuth, CntrPar%IPC_phi, LocalVar%Y_MErr, LocalVar%DT, CntrPar%IPC_KI, CntrPar%Y_IPC_KP, CntrPar%Y_IPC_KI, CntrPar%IPC_omegaHP, CntrPar%IPC_omegaLP, CntrPar%IPC_omegaNotch, CntrPar%IPC_zetaHP, CntrPar%IPC_zetaLP, CntrPar%IPC_zetaNotch, LocalVar%iStatus, CntrPar%IPC_ControlMode, CntrPar%Y_ControlMode, LocalVar%NumBl, LocalVar%IPC_PitComF)
CALL IPC(LocalVar%rootMOOP, LocalVar%Azimuth, CntrPar%IPC_phi, LocalVar%Y_MErr, LocalVar%DT, CntrPar%IPC_KI, CntrPar%Y_IPC_KP, CntrPar%Y_IPC_KI, CntrPar%IPC_omegaHP, CntrPar%IPC_omegaLP, CntrPar%IPC_omegaNotch, CntrPar%IPC_zetaHP, CntrPar%IPC_zetaLP, CntrPar%IPC_zetaNotch, LocalVar%iStatus, CntrPar%IPC_ControlMode, CntrPar%Y_ControlMode, LocalVar%NumBl, LocalVar%IPC_PitComF, objInst)
ELSE
LocalVar%IPC_PitComF = 0.0
END IF
Expand All @@ -359,7 +372,7 @@ SUBROUTINE DISCON (avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG) BIND (C, NAM

! PitCom(K) = ratelimit(PitComT_IPC(K), LocalVar%BlPitch(K), PC_MinRat, PC_MaxRat, LocalVar%DT) ! Saturate the overall command of blade K using the pitch rate limit
LocalVar%PitCom(K) = saturate(PitComT_IPC(K), CntrPar%PC_MinPit, CntrPar%PC_MaxPit) ! Saturate the overall command using the pitch angle limits
LocalVar%PitCom(K) = LPFilter(LocalVar%PitCom(K), LocalVar%DT, CntrPar%CornerFreq, LocalVar%iStatus, .FALSE., K+3)
LocalVar%PitCom(K) = LPFilter(LocalVar%PitCom(K), LocalVar%DT, CntrPar%CornerFreq, LocalVar%iStatus, .FALSE., objInst%instLPF)
END DO

! Set the pitch override to yes and command the pitch demanded from the last
Expand All @@ -382,8 +395,8 @@ SUBROUTINE DISCON (avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG) BIND (C, NAM
IF (LocalVar%Time >= Y_YawEndT) THEN ! Check if the turbine is currently yawing
avrSWAP(48) = 0.0 ! Set yaw rate to zero

LocalVar%Y_ErrLPFFast = LPFilter(LocalVar%Y_MErr, LocalVar%DT, CntrPar%Y_omegaLPFast, LocalVar%iStatus, .FALSE., 2) ! Fast low pass filtered yaw error with a frequency of 1
LocalVar%Y_ErrLPFSlow = LPFilter(LocalVar%Y_MErr, LocalVar%DT, CntrPar%Y_omegaLPSlow, LocalVar%iStatus, .FALSE., 3) ! Slow low pass filtered yaw error with a frequency of 1/60
LocalVar%Y_ErrLPFFast = LPFilter(LocalVar%Y_MErr, LocalVar%DT, CntrPar%Y_omegaLPFast, LocalVar%iStatus, .FALSE., objInst%instLPF) ! Fast low pass filtered yaw error with a frequency of 1
LocalVar%Y_ErrLPFSlow = LPFilter(LocalVar%Y_MErr, LocalVar%DT, CntrPar%Y_omegaLPSlow, LocalVar%iStatus, .FALSE., objInst%instLPF) ! Slow low pass filtered yaw error with a frequency of 1/60

Y_AccErr = Y_AccErr + LocalVar%DT*SIGN(LocalVar%Y_ErrLPFFast**2, LocalVar%Y_ErrLPFFast) ! Integral of the fast low pass filtered yaw error

Expand All @@ -392,8 +405,8 @@ SUBROUTINE DISCON (avrSWAP, aviFAIL, accINFILE, avcOUTNAME, avcMSG) BIND (C, NAM
END IF
ELSE
avrSWAP(48) = SIGN(CntrPar%Y_Rate, LocalVar%Y_MErr) ! Set yaw rate to predefined yaw rate, the sign of the error is copied to the rate
LocalVar%Y_ErrLPFFast = LPFilter(LocalVar%Y_MErr, LocalVar%DT, CntrPar%Y_omegaLPFast, LocalVar%iStatus, .TRUE., 2) ! Fast low pass filtered yaw error with a frequency of 1
LocalVar%Y_ErrLPFSlow = LPFilter(LocalVar%Y_MErr, LocalVar%DT, CntrPar%Y_omegaLPSlow, LocalVar%iStatus, .TRUE., 3) ! Slow low pass filtered yaw error with a frequency of 1/60
LocalVar%Y_ErrLPFFast = LPFilter(LocalVar%Y_MErr, LocalVar%DT, CntrPar%Y_omegaLPFast, LocalVar%iStatus, .TRUE., objInst%instLPF) ! Fast low pass filtered yaw error with a frequency of 1
LocalVar%Y_ErrLPFSlow = LPFilter(LocalVar%Y_MErr, LocalVar%DT, CntrPar%Y_omegaLPSlow, LocalVar%iStatus, .TRUE., objInst%instLPF) ! Slow low pass filtered yaw error with a frequency of 1/60
Y_AccErr = 0.0 ! "
END IF
END IF
Expand Down
24 changes: 17 additions & 7 deletions Source/DRC_Types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -10,13 +10,13 @@ MODULE DRC_Types
INTEGER(4) :: LoggingLevel ! 0 = write no debug files, 1 = write standard output .dbg-file, 2 = write standard output .dbg-file and complete avrSWAP-array .dbg2-file
REAL(4) :: IPC_KI ! Integral gain for the individual pitch controller, [-]. 8E-10
INTEGER(4) :: IPC_ControlMode ! Turn Individual Pitch Control (IPC) for fatigue load reductions (pitch contribution) on = 1/off = 0
REAL(4) :: IPC_omegaHP ! High-pass filter cut-in frequency used to separate yaw-by-IPC contribution from blade load reduction contribution, [rad/s]. 0.3141592
REAL(4) :: IPC_omegaLP ! Low-pass filter corner frequency for the individual pitch controller, [rad/s].0.6283185
REAL(4) :: IPC_omegaNotch ! Notch filter corner frequency for the individual pitch controller, [rad/s].1.269330365
REAL(4) :: IPC_phi ! Phase offset added to the azimuth angle for the individual pitch controller, [rad]. 0.436332313
REAL(4) :: IPC_zetaHP ! High-pass filter damping value, [-]. 0.70
REAL(4) :: IPC_zetaLP ! Low-pass filter damping factor for the individual pitch controller, [-].1.0
REAL(4) :: IPC_zetaNotch ! Notch filter damping factor for the individual pitch controller, [-].0.5
REAL(4) :: IPC_omegaHP ! High-pass filter cut-in frequency used to separate yaw-by-IPC contribution from blade load reduction contribution, [rad/s].
REAL(4) :: IPC_omegaLP ! Low-pass filter corner frequency for the individual pitch controller, [rad/s].
REAL(4) :: IPC_omegaNotch ! Notch filter corner frequency for the individual pitch controller, [rad/s].
REAL(4) :: IPC_phi ! Phase offset added to the azimuth angle for the individual pitch controller, [rad].
REAL(4) :: IPC_zetaHP ! High-pass filter damping value, [-].
REAL(4) :: IPC_zetaLP ! Low-pass filter damping factor for the individual pitch controller, [-].
REAL(4) :: IPC_zetaNotch ! Notch filter damping factor for the individual pitch controller, [-].
INTEGER(4) :: PC_GS_n ! Amount of gain-scheduling table entries
REAL(4), DIMENSION(:), ALLOCATABLE :: PC_GS_angles ! Gain-schedule table: pitch angles
REAL(4), DIMENSION(:), ALLOCATABLE :: PC_GS_kp ! Gain-schedule table: pitch controller kp gains
Expand Down Expand Up @@ -62,6 +62,7 @@ MODULE DRC_Types
END TYPE ControlParameters

TYPE, PUBLIC :: LocalVariables
! From avrSWAP
INTEGER(4) :: iStatus
REAL(4) :: Time
REAL(4) :: DT
Expand All @@ -74,6 +75,7 @@ MODULE DRC_Types
REAL(4) :: Azimuth
INTEGER(4) :: NumBl

! Internal controller variables
REAL(4) :: GenSpeedF ! Filtered HSS (generator) speed [rad/s].
REAL(4) :: GenTrq ! Electrical generator torque, [Nm].
REAL(4) :: GenTrqAr ! Electrical generator torque, for above-rated PI-control [Nm].
Expand All @@ -94,6 +96,14 @@ MODULE DRC_Types
REAL(4) :: Y_MErr ! Measured yaw error, measured + setpoint [rad]
END TYPE LocalVariables

TYPE, PUBLIC :: ObjectInstances
INTEGER(4) :: instLPF
INTEGER(4) :: instSecLPF
INTEGER(4) :: instHPF
INTEGER(4) :: instNotchSlopes
INTEGER(4) :: instNotch
END TYPE ObjectInstances

!TYPE, PUBLIC :: PersistentVariables
!END TYPE PersistentVariables

Expand Down
Loading

0 comments on commit 0a86bd3

Please sign in to comment.