source: LMDZ6/trunk/libf/phylmd/lmdz_thermcell_qsat.f90 @ 5279

Last change on this file since 5279 was 5274, checked in by abarral, 9 months ago

Replace yomcst.h by existing module

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 3.5 KB
Line 
1MODULE lmdz_thermcell_qsat
2CONTAINS
3
4subroutine thermcell_qsat(klon,active,pplev,ztemp,zqta,zqsat)
5USE yomcst_mod_h, ONLY: RPI, RCLUM, RHPLA, RKBOL, RNAVO                   &
6          , RDAY, REA, REPSM, RSIYEA, RSIDAY, ROMEGA                  &
7          , R_ecc, R_peri, R_incl                                      &
8          , RA, RG, R1SA                                         &
9          , RSIGMA                                                     &
10          , R, RMD, RMV, RD, RV, RCPD                    &
11          , RMO3, RMCO2, RMC, RMCH4, RMN2O, RMCFC11, RMCFC12        &
12          , RCPV, RCVD, RCVV, RKAPPA, RETV, eps_w                    &
13          , RCW, RCS                                                 &
14          , RLVTT, RLSTT, RLMLT, RTT, RATM                           &
15          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
16          , RALPD, RBETD, RGAMD
17implicit none
18
19
20  INCLUDE "YOETHF.h"
21  INCLUDE "FCTTRE.h"
22
23
24!====================================================================
25! DECLARATIONS
26!====================================================================
27
28! Arguments
29INTEGER klon
30REAL zpspsk(klon),pplev(klon)
31REAL ztemp(klon),zqta(klon),zqsat(klon)
32LOGICAL active(klon)
33
34! Variables locales
35INTEGER ig,iter
36REAL Tbef(klon),DT(klon)
37REAL tdelta,qsatbef,zcor,qlbef,zdelta,zcvm5,dqsat,num,denom,dqsat_dT
38logical Zsat
39REAL RLvCp
40
41REAL, SAVE :: DDT0=.01
42!$OMP THREADPRIVATE(DDT0)
43
44LOGICAL afaire(klon),tout_converge
45
46!====================================================================
47! INITIALISATIONS
48!====================================================================
49
50RLvCp = RLVTT/RCPD
51tout_converge=.false.
52afaire(:)=.false.
53DT(:)=0.
54
55
56!====================================================================
57! Routine a vectoriser en copiant active dans converge et en mettant
58! la boucle sur les iterations a l'exterieur est en mettant
59! converge= false des que la convergence est atteinte.
60!====================================================================
61
62do ig=1,klon
63   if (active(ig)) then
64               Tbef(ig)=ztemp(ig)
65               zdelta=MAX(0.,SIGN(1.,RTT-Tbef(ig)))
66               qsatbef= R2ES * FOEEW(Tbef(ig),zdelta)/pplev(ig)
67               qsatbef=MIN(0.5,qsatbef)
68               zcor=1./(1.-retv*qsatbef)
69               qsatbef=qsatbef*zcor
70               qlbef=max(0.,zqta(ig)-qsatbef)
71               DT(ig) = 0.5*RLvCp*qlbef
72               zqsat(ig)=qsatbef
73     endif
74enddo
75
76! Traitement du cas ou il y a condensation mais faible
77! On ne condense pas mais on dit que le qsat est le qta
78do ig=1,klon
79   if (active(ig)) then
80      if (0.<abs(DT(ig)).and.abs(DT(ig))<=DDT0) then
81         zqsat(ig)=zqta(ig)
82      endif
83   endif
84enddo
85
86do iter=1,10
87    afaire(:)=abs(DT(:)).gt.DDT0
88    do ig=1,klon
89               if (afaire(ig)) then
90                 Tbef(ig)=Tbef(ig)+DT(ig)
91                 zdelta=MAX(0.,SIGN(1.,RTT-Tbef(ig)))
92                 qsatbef= R2ES * FOEEW(Tbef(ig),zdelta)/pplev(ig)
93                 qsatbef=MIN(0.5,qsatbef)
94                 zcor=1./(1.-retv*qsatbef)
95                 qsatbef=qsatbef*zcor
96                 qlbef=zqta(ig)-qsatbef
97                 zdelta=MAX(0.,SIGN(1.,RTT-Tbef(ig)))
98                 zcvm5=R5LES*(1.-zdelta) + R5IES*zdelta
99                 zcor=1./(1.-retv*qsatbef)
100                 dqsat_dT=FOEDE(Tbef(ig),zdelta,zcvm5,qsatbef,zcor)
101                 num=-Tbef(ig)+ztemp(ig)+RLvCp*qlbef
102                 denom=1.+RLvCp*dqsat_dT
103                 zqsat(ig) = qsatbef
104                 DT(ig)=num/denom
105               endif
106    enddo
107enddo
108
109return
110end
111END MODULE lmdz_thermcell_qsat
Note: See TracBrowser for help on using the repository browser.