The POMPES method
This control method mimics the operation of a pumping station comprising a number of identical pumps which start or stop depending on a low or high water level and a time delay.
SUBROUTINE CPOMPES(U,Y,YT,PARA) USE D_GLOBAL, ONLY : REPSI USE SIRENE_parametres, ONLY : LONG USE TEMPS, ONLY : T,TDEB,TFIN USE IFICH, ONLY : JREGS USE P1, ONLY : INURE USE P2, ONLY : INU,INY,DTU IMPLICIT NONE REAL(KIND=LONG), INTENT(IN) :: Y,YT REAL(KIND=LONG), INTENT(INOUT) :: PARA, U INTEGER :: NBMIN,NBINI,NBMAX,NBNOW REAL(KIND=LONG) :: ZH,ZB,Z1,Z2,Q,TLASTON,TLASTOF REAL(KIND=LONG) :: TEMPOonoff,TEMPOoffon,TEMPOonon,TEMPOoffoff REAL(KIND=LONG) :: RHO,P,H,PMAX,ETOT LOGICAL :: Bon,Boff DIMENSION U(*),Y(*),YT(*),PARA(*) !-----Affectations ZH=PARA(1) ZB=PARA(2) NBMIN=INT(PARA(3)) NBINI=INT(PARA(4)) NBMAX=INT(PARA(5)) Q=PARA(6) TEMPOonoff=PARA(7) TEMPOoffon=PARA(8) TEMPOonon=PARA(9) TEMPOoffoff=PARA(10) TLASTON=PARA(11) TLASTOF=PARA(12) PMAX=PARA(13) ETOT=PARA(14) NBNOW=PARA(15) !-----Protection IF (Q.EQ.0.) RETURN !-----Calcul des booléens pour savoir si on peut faire un on et/ou un off !-----en tenant compte des tempos. Par défaut on ne peut pas (=FALSE) Bon=.FALSE. Boff=.FALSE. IF(TLASTON<=TDEB.AND.TLASTOF<=TDEB) THEN !--On n'a rien fait encore donc on peut tout faire (on ou off) Bon=.TRUE. Boff=.TRUE. ELSEIF(TLASTON<=TDEB) THEN !--On a déjà fait un off mais pas encore un on IF((T-TLASTOF).GE.TEMPOoffon) Bon=.TRUE. IF((T-TLASTOF).GE.TEMPOoffoff) Boff=.TRUE. ELSEIF(TLASTOF<=TDEB) THEN !--On a déjà fait un on mais pas encore un off IF((T-TLASTON).GE.TEMPOonon) Bon=.TRUE. IF((T-TLASTON).GE.TEMPOonoff) Boff=.TRUE. ELSE !--On a déjà fait un on et un off IF(TLASTON<TLASTOF) THEN !--Le dernier réalisé est un off IF((T-TLASTOF).GE.TEMPOoffon) Bon=.TRUE. IF((T-TLASTOF).GE.TEMPOoffoff) Boff=.TRUE. ELSE !--Le dernier réalisé est un on (ou les 2 en mm temps mais pas possible) IF((T-TLASTON).GE.TEMPOonon) Bon=.TRUE. IF((T-TLASTON).GE.TEMPOonoff) Boff=.TRUE. ENDIF ENDIF IF (Y(1).GT.ZH) THEN IF (Q.GT.0) THEN !--------Arret d'une pompe (alimentation) si possible si Q>0 (N>NBMIN et TEMPO) IF(NBNOW.GT.NBMIN.AND.Boff) THEN NBNOW=NBNOW-1 TLASTOF=T WRITE(JREGS,830) 'POMPE ',INURE,' - Arret d''une pompe (alimentation) à T=',T,' : ',Y(1),' > ',ZH & ,' . U=',U(1),' -> ',NBNOW*Q ENDIF ELSE !--------Démarrage d'une pompe (extraction) si possible si Q<0 (N<NBMAX et TEMPO) IF(NBNOW.LT.NBMAX.AND.Bon) THEN NBNOW=NBNOW+1 TLASTON=T WRITE(JREGS,830) 'POMPE ',INURE,' - Démarrage d''une pompe (extraction) à T=',T,' : ',Y(1),' > ',ZH & ,' . U=',U(1),' -> ',NBNOW*Q ENDIF ENDIF ELSEIF (Y(1).LT.ZB) THEN IF (Q.GT.0) THEN !--------Démarrage d'une pompe (alimentation) si possible si Q>0 (N<NBMAX et TEMPO) IF(NBNOW.LT.NBMAX.AND.Bon) THEN NBNOW=NBNOW+1 TLASTON=T WRITE(JREGS,830) 'POMPE ',INURE,' - Démarrage d''une pompe (alimentation) à T=',T,' : ',Y(1),' < ',ZB & ,' . U=',U(1),' -> ',NBNOW*Q ENDIF ELSE !--------Arret d'une pompe (extraction) si possible si Q<0 (N>NBMIN et TEMPO) IF(NBNOW.GT.NBMIN.AND.Boff) THEN NBNOW=NBNOW-1 TLASTOF=T WRITE(JREGS,830) 'POMPE ',INURE,' - Arret d''une pompe (extraction) à T=',T,' : ',Y(1),' < ',ZB & ,' . U=',U(1),' -> ',NBNOW*Q ENDIF ENDIF ENDIF !-----Affectation du débit dans la commande U U(1)=NBNOW*Q !-----Vérification des cotes de l'eau IF (Q.LT.0) THEN !-----Vérification de la cote de l'eau à l'aspiration (Q<0) !-----Récupération de la cote d'aspiration Z1 pour le calcul du gain de charge IF(Y(1).LT.YT(1)) THEN WRITE(JREGS,800) 'POMPE ',INURE,' - Cote de l''eau trop basse à l''aspiration au temps T=',T,' : ',Y(1),' < ',YT(1) Z1=YT(1) ELSE Z1=Y(1) ENDIF !-----Récupération de la cote de refoulement Z2 pour le calcul du gain de charge !-----Si on a un Y2, en option on prend YT(2), sinon on prend YT(1)+10m IF(INY.LT.2) THEN Z2=YT(1)+10.0 ELSE !-----Si on a un U2 on regarde alors la valeur de Y(2) % YT(2) sinon on prend YT(2) IF(INU.GT.1) THEN IF(Y(2).LT.YT(2)) THEN !---------------Le refoulement est dénoyé Z2=YT(2) ELSE !---------------Le refoulement est noyé Z2=Y(2) ENDIF ELSE Z2=YT(2) ENDIF ENDIF ELSE !-----Vérification de la cote de l'eau au refoulement (Q>0) !-----Récupération de la cote de refoulement Z2 pour le calcul du gain de charge IF(Y(1).GT.YT(1)) THEN WRITE(JREGS,800) 'POMPE ',INURE,' - Cote de l''eau plus haute au refoulement au temps T= ',T,' : ',Y(1),' > ',YT(1) Z2=Y(1) ELSE Z2=YT(1) ENDIF !-----Récupération de la cote d'aspiration Z1 pour le calcul du gain de charge !-----Si on a un Y2, en option on prend YT(2), sinon on prend YT(1)-10m IF(INY.LT.2) THEN Z1=YT(1)-10.0 ELSE !-----Si on a un U2 on regarde alors la valeur de Y(2) % YT(2) sinon on prend YT(2) IF(INU.GT.1) THEN IF(Y(2).LT.YT(2)) THEN !---------------L'aspiration est dénoyé (pb mais on doit qd mm faire le calcul) Z1=YT(2) ELSE !---------------L'aspiration est noyé (ok cas normal) Z1=Y(2) ENDIF ELSE Z1=YT(2) ENDIF ENDIF ENDIF !-----Calcul de la hauteur de refoulement - hauteur d'aspiration !-----On néglige les V^2/2g à l'amont et à l'aval ainsi que les pertes de charges dans le dispositif H=Z2-Z1 !-----Calcul de la puissance hydraulique nécessaire au refoulement RHO=1 P=RHO*9.81*ABS(U(1))*H !-----Stockage de la puissance max dans PMAX IF(P.GT.PMAX) THEN PMAX=P WRITE(JREGS,810) 'POMPE ',INURE,' - Puissance maximum au temps T=',T,' : ',P,' Watts' ENDIF !-----Calcul de l'énergie totale consommée dans ETOT ETOT=ETOT+P*DTU IF(T.GE.TFIN) THEN WRITE(JREGS,820) 'POMPE ',INURE,' - Energie totale consommée jusqu''au au temps T=',T,' : ',ETOT,' Joules' ENDIF !-----Possibilité de faire communiquer la pompe avec un autre emplacement (si INU>1) IF(INU.GT.1) THEN U(2)=-U(1) ENDIF !-----Sauvegarde des variables PARA(11)=TLASTON PARA(12)=TLASTOF PARA(13)=PMAX PARA(14)=ETOT PARA(15)=NBNOW 800 FORMAT(A6,I2,A55,F12.2,A3,F14.3,A3,F14.3) 810 FORMAT(A6,I2,A55,F12.2,A3,F12.1,A6) 820 FORMAT(A6,I2,A55,F12.2,A3,E20.1,A7) 830 FORMAT(A6,I2,A55,F12.2,A3,F14.3,A3,F14.3,A5,F10.3,A4,F10.3) END SUBROUTINE CPOMPES
If you want a different pumping station control module you can always copy this routine into a USER module and modify it as you wish (in this case, do this for the LPOMPES -> LUSER routine for parameter reading).
SUBROUTINE LPOMPES(CHAINE,Reg) USE D_REGULATION, ONLY : Regulateur_t USE SIRENE_parametres, ONLY : LONG USE F1 , ONLY : IERROR,IWARN,CWARN USE TEMPS , ONLY : TDEB IMPLICIT NONE CHARACTER, INTENT(IN) :: CHAINE*(*) TYPE(Regulateur_t), INTENT(INOUT) :: Reg REAL(KIND=LONG) :: TEMPOonoff,TEMPOoffon,TEMPOonon,TEMPOoffoff INTEGER :: I !-----Debut de la routine !-----Lecture des parametres specifiques pour cette methode !-----Debut de la routine !-----En V 5.31e on passe à 10 paramètres READ(CHAINE,'(9(F8.3,1X),F8.3)',ERR=10) (Reg%tPara(I),I=1,10) TEMPOonoff=Reg%tPara(7) TEMPOoffon=Reg%tPara(8) TEMPOonon=Reg%tPara(9) TEMPOoffoff=Reg%tPara(10) Reg%tPara(11)=TDEB-MAX(TEMPOonoff,TEMPOonon) ! TLASTON Reg%tPara(12)=TDEB-MAX(TEMPOoffon,TEMPOoffoff) ! TLASTOF Reg%tPara(13)=0 ! Puissance Reg%tPara(14)=0 ! Energie Reg%tPara(15)=Reg%tPara(4) ! Nb de pompes actives en temps réel (NBNOW=NBINI) RETURN 10 CONTINUE IERROR=2 END SUBROUTINE LPOMPES