Example of calculation routine CPID
The PID method corresponding to a classic PID controller is programmed as explained below. It includes an optionnal filter term of the derivative term, an antiwindup and deadband zone:
SUBROUTINE CPID(Reg,U,Y,YT,PARA,ISIMO) USE SIRENE_parametres, ONLY : LONG USE IFICH , ONLY : JREGS USE TEMPS , ONLY : T USE D_REGULATION, ONLY : Regulateur_t USE D_GLOBAL, ONLY : sProgActif IMPLICIT NONE TYPE(Regulateur_t), INTENT(INOUT) :: Reg INTEGER, INTENT(IN) :: ISIMO REAL(KIND=LONG), INTENT(IN) :: Y,YT REAL(KIND=LONG), INTENT(INOUT) :: U,PARA INTEGER :: IU,IY REAL(KIND=LONG) :: KP,N,TI,TD,AWU,EOLD,SE,DE,E,STI,A1,A2,U2 !-----Si ISIMO=0 c'est un PID monovariable, si ISIMO=1 et s'il y a plusieurs U on duplique U !-----Si ISIMO=I<0 il est appelé à partir d'ATVPID et c'est l'indice du U et du Y qu'on doit !----- utiliser pour décaller le U et Y global pour DYMAX et les variables de l'antiwindup INTEGER, PARAMETER :: NMES=$NSIRE,LMES=$LSIRE !-----On gère l'antiwindup LOGICAL SATURE CHARACTER MESP*(LMES) !-----On utilise DTU et non plus DT (POM 2/6/99) COMMON/SIRE/MESP(NMES) DIMENSION Y(:),YT(:),U(:),PARA(:) !-----Affectations KP=PARA(1) TI=PARA(2) TD=PARA(3) N=PARA(4) AWU=PARA(5) EOLD=PARA(6) SE=PARA(7) DE=PARA(8) !-----Calcul pour cette methode !-----Nouvel ecart (e = y* - y) E=YT(1)-Y(1) !-----Recherche de l'indice global pour Y et pour U (POM 14/3/5) IF(ISIMO.LT.0) THEN IY=ABS(ISIMO) IU=ABS(ISIMO) ELSE IY=1 IU=1 ENDIF !-----On gère une bande morte (POM 21/07/04) IF(ABS(E).LT.Reg%tY(IY)%DYMax) THEN IF(sProgActif=='SIRENE') THEN WRITE(JREGS,MESP(87)) T,'DYMax',Reg%num,IY,Reg%tY(IY)%DYMax,E,0. ELSEIF(sProgActif=='FLUVIA') THEN WRITE(JREGS,MESP(76)) T,'DYMax',Reg%num,IY,Reg%tY(IY)%DYMax,E,0. ENDIF E=0. ENDIF !-----Terme integral (approximation de Tustin) !-----On gère l'antiwindup (POM 16/07/04) IF(TI.NE.0.) THEN STI=KP*Reg%tU(IU)%VarU%DT/TI*(EOLD+E)/2 ELSE STI=0. ENDIF IF(AWU.EQ.1.) THEN SATURE=Reg%tU(IU)%FiltreU%iFlagBloc>=3 .AND. Reg%tU(IU)%FiltreU%iFlagBloc/=5 IF(.NOT.SATURE) THEN SE=SE+STI ENDIF ELSE SE=SE+STI ENDIF !-----Terme derive IF(TD.NE.0.) THEN IF(N.EQ.0.) THEN !-----------Terme derive sans filtre (backward difference) !-----------Avec une consigne y* constante DE=KP/Reg%tU(IU)%VarU%DT*TD*(E-EOLD) ELSE !-----------Terme derive avec filtre (backward difference) !-----------Avec une consigne y* constante A1=1/(1+N*Reg%tU(IU)%VarU%DT/TD) A2=KP*N*A1 DE=A1*DE+A2*(E-EOLD) ENDIF ENDIF !-----Calcul de la commande U(1)=KP*E+SE+DE !-----Ancien ecart EOLD=E !-----Affectations PARA(6)=EOLD PARA(7)=SE PARA(8)=DE !-----Si plusieurs U (SIMO) on duplique la meme ouverture !-----(interessant dans le cas de plusieurs vannes identiques en parallele, en mode V par exemple) IF(ISIMO.GT.0) THEN U2=U(1) U(:)=U2 ENDIF END SUBROUTINE CPID
If you want another PID equation, you can always copy and paste this subroutine into a USER regulation module and modify it as you want (do the same with the LPID -> LUSER subroutine to read the parameters).