GCC Code Coverage Report


Directory: ./
File: phys/thermcell_env.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 26 26 100.0%
Branches: 17 18 94.4%

Line Branch Exec Source
1 18608640 SUBROUTINE thermcell_env(ngrid,nlay,po,pt,pu,pv,pplay, &
2 480 & pplev,zo,zh,zl,ztv,zthl,zu,zv,zpspsk,pqsat,lev_out)
3
4 !--------------------------------------------------------------
5 !thermcell_env: calcule les caracteristiques de l environnement
6 !necessaires au calcul des proprietes dans le thermique
7 !--------------------------------------------------------------
8
9 USE print_control_mod, ONLY: prt_level
10 IMPLICIT NONE
11
12 !
13 ! $Header$
14 !
15 ! ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
16 ! veillez � n'utiliser que des ! pour les commentaires
17 ! et � bien positionner les & des lignes de continuation
18 ! (les placer en colonne 6 et en colonne 73)
19 !
20 !
21 ! A1.0 Fundamental constants
22 REAL RPI,RCLUM,RHPLA,RKBOL,RNAVO
23 ! A1.1 Astronomical constants
24 REAL RDAY,REA,REPSM,RSIYEA,RSIDAY,ROMEGA
25 ! A1.1.bis Constantes concernant l'orbite de la Terre:
26 REAL R_ecc, R_peri, R_incl
27 ! A1.2 Geoide
28 REAL RA,RG,R1SA
29 ! A1.3 Radiation
30 ! REAL RSIGMA,RI0
31 REAL RSIGMA
32 ! A1.4 Thermodynamic gas phase
33 REAL RMO3,RMCO2,RMC,RMCH4,RMN2O,RMCFC11,RMCFC12
34 REAL R,RMD,RMV,RD,RV,RCPD,RCPV,RCVD,RCVV
35 REAL RKAPPA,RETV, eps_w
36 ! A1.5,6 Thermodynamic liquid,solid phases
37 REAL RCW,RCS
38 ! A1.7 Thermodynamic transition of phase
39 REAL RLVTT,RLSTT,RLMLT,RTT,RATM
40 ! A1.8 Curve of saturation
41 REAL RESTT,RALPW,RBETW,RGAMW,RALPS,RBETS,RGAMS
42 REAL RALPD,RBETD,RGAMD
43 !
44 COMMON/YOMCST/RPI ,RCLUM ,RHPLA ,RKBOL ,RNAVO &
45 & ,RDAY ,REA ,REPSM ,RSIYEA,RSIDAY,ROMEGA &
46 & ,R_ecc, R_peri, R_incl &
47 & ,RA ,RG ,R1SA &
48 & ,RSIGMA &
49 & ,R ,RMD ,RMV ,RD ,RV ,RCPD &
50 & ,RMO3 ,RMCO2 ,RMC ,RMCH4 ,RMN2O ,RMCFC11 ,RMCFC12 &
51 & ,RCPV ,RCVD ,RCVV ,RKAPPA,RETV, eps_w &
52 & ,RCW ,RCS &
53 & ,RLVTT ,RLSTT ,RLMLT ,RTT ,RATM &
54 & ,RESTT ,RALPW ,RBETW ,RGAMW ,RALPS ,RBETS ,RGAMS &
55 & ,RALPD ,RBETD ,RGAMD
56 ! ------------------------------------------------------------------
57 !$OMP THREADPRIVATE(/YOMCST/)
58 !
59 ! $Id: YOETHF.h 2799 2017-02-24 18:50:33Z jyg $
60 !
61 ! ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
62 ! veillez n'utiliser que des ! pour les commentaires
63 ! et bien positionner les & des lignes de continuation
64 ! (les placer en colonne 6 et en colonne 73)
65 !
66 !* COMMON *YOETHF* DERIVED CONSTANTS SPECIFIC TO ECMWF THERMODYNAMICS
67 !
68 ! *R__ES* *CONSTANTS USED FOR COMPUTATION OF SATURATION
69 ! MIXING RATIO OVER LIQUID WATER(*R_LES*) OR
70 ! ICE(*R_IES*).
71 ! *RVTMP2* *RVTMP2=RCPV/RCPD-1.
72 ! *RHOH2O* *DENSITY OF LIQUID WATER. (RATM/100.)
73 !
74 REAL R2ES, R3LES, R3IES, R4LES, R4IES, R5LES, R5IES
75 REAL RVTMP2, RHOH2O
76 REAL R5ALVCP,R5ALSCP,RALVDCP,RALSDCP,RALFDCP,RTWAT,RTBER,RTBERCU
77 REAL RTICE,RTICECU,RTWAT_RTICE_R,RTWAT_RTICECU_R,RKOOP1,RKOOP2
78 LOGICAL OK_BAD_ECMWF_THERMO ! If TRUE, then variables set by rrtm/suphec.F90
79 ! If FALSE, then variables set by suphel.F90
80 COMMON /YOETHF/R2ES, R3LES, R3IES, R4LES, R4IES, R5LES, R5IES, &
81 & RVTMP2, RHOH2O, &
82 & R5ALVCP,R5ALSCP,RALVDCP,RALSDCP, &
83 & RALFDCP,RTWAT,RTBER,RTBERCU, &
84 & RTICE,RTICECU,RTWAT_RTICE_R,RTWAT_RTICECU_R,RKOOP1,&
85 & RKOOP2, &
86 & OK_BAD_ECMWF_THERMO
87
88 !$OMP THREADPRIVATE(/YOETHF/)
89 !
90 ! $Header$
91 !
92 !
93 ! ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
94 ! veillez n'utiliser que des ! pour les commentaires
95 ! et bien positionner les & des lignes de continuation
96 ! (les placer en colonne 6 et en colonne 73)
97 !
98 ! ------------------------------------------------------------------
99 ! This COMDECK includes the Thermodynamical functions for the cy39
100 ! ECMWF Physics package.
101 ! Consistent with YOMCST Basic physics constants, assuming the
102 ! partial pressure of water vapour is given by a first order
103 ! Taylor expansion of Qs(T) w.r.t. to Temperature, using constants
104 ! in YOETHF
105 ! ------------------------------------------------------------------
106 REAL PTARG, PDELARG, P5ARG, PQSARG, PCOARG
107 REAL FOEEW, FOEDE, qsats, qsatl, dqsats, dqsatl
108 LOGICAL thermcep
109 PARAMETER (thermcep=.TRUE.)
110 !
111 FOEEW ( PTARG,PDELARG ) = EXP ( &
112 & (R3LES*(1.-PDELARG)+R3IES*PDELARG) * (PTARG-RTT) &
113 & / (PTARG-(R4LES*(1.-PDELARG)+R4IES*PDELARG)) )
114 !
115 FOEDE ( PTARG,PDELARG,P5ARG,PQSARG,PCOARG ) = PQSARG*PCOARG*P5ARG &
116 & / (PTARG-(R4LES*(1.-PDELARG)+R4IES*PDELARG))**2
117 !
118 qsats(ptarg) = 100.0 * 0.622 * 10.0 &
119 & ** (2.07023 - 0.00320991 * ptarg &
120 & - 2484.896 / ptarg + 3.56654 * LOG10(ptarg))
121 qsatl(ptarg) = 100.0 * 0.622 * 10.0 &
122 & ** (23.8319 - 2948.964 / ptarg &
123 & - 5.028 * LOG10(ptarg) &
124 & - 29810.16 * EXP( - 0.0699382 * ptarg) &
125 & + 25.21935 * EXP( - 2999.924 / ptarg))
126 !
127 dqsats(ptarg,pqsarg) = RLVTT/RCPD*pqsarg * (3.56654/ptarg &
128 & +2484.896*LOG(10.)/ptarg**2 &
129 & -0.00320991*LOG(10.))
130 dqsatl(ptarg,pqsarg) = RLVTT/RCPD*pqsarg*LOG(10.)* &
131 & (2948.964/ptarg**2-5.028/LOG(10.)/ptarg &
132 & +25.21935*2999.924/ptarg**2*EXP(-2999.924/ptarg) &
133 & +29810.16*0.0699382*EXP(-0.0699382*ptarg))
134
135 INTEGER ngrid,nlay
136 REAL po(ngrid,nlay)
137 REAL pt(ngrid,nlay)
138 REAL pu(ngrid,nlay)
139 REAL pv(ngrid,nlay)
140 REAL pplay(ngrid,nlay)
141 REAL pplev(ngrid,nlay+1)
142 integer lev_out ! niveau pour les print
143
144 REAL zo(ngrid,nlay)
145 REAL zl(ngrid,nlay)
146 REAL zh(ngrid,nlay)
147 REAL ztv(ngrid,nlay)
148 REAL zthl(ngrid,nlay)
149 REAL zpspsk(ngrid,nlay)
150 REAL zu(ngrid,nlay)
151 REAL zv(ngrid,nlay)
152 REAL pqsat(ngrid,nlay)
153
154 INTEGER ig,ll
155
156 real dqsat_dT
157 real RLvCp
158
159 480 logical mask(ngrid,nlay)
160
161
162 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
163 ! Initialisations :
164 !------------------
165
166
4/4
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 18607680 times.
✓ Branch 3 taken 18720 times.
18626880 mask(:,:)=.true.
167 480 RLvCp = RLVTT/RCPD
168
169 !
170 ! calcul des caracteristiques de l environnement
171
2/2
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
19200 DO ll=1,nlay
172
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626880 DO ig=1,ngrid
173 18607680 zo(ig,ll)=po(ig,ll)
174 18607680 zl(ig,ll)=0.
175 18626400 zh(ig,ll)=pt(ig,ll)
176 EndDO
177 EndDO
178 !
179 !
180 ! Condensation :
181 !---------------
182 ! Calcul de l'humidite a saturation et de la condensation
183
184 480 call thermcell_qsat(ngrid*nlay,mask,pplev,pt,po,pqsat)
185
2/2
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
19200 DO ll=1,nlay
186
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626880 DO ig=1,ngrid
187 18607680 zl(ig,ll) = max(0.,po(ig,ll)-pqsat(ig,ll))
188 18607680 zh(ig,ll) = pt(ig,ll)+RLvCp*zl(ig,ll) ! T = Tl + Lv/Cp ql
189 18626400 zo(ig,ll) = po(ig,ll)-zl(ig,ll)
190 ENDDO
191 ENDDO
192 !
193 !
194 !-----------------------------------------------------------------------
195
196
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 if (prt_level.ge.1) print*,'0 OK convect8'
197
198
2/2
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
19200 DO ll=1,nlay
199
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626880 DO ig=1,ngrid
200 18607680 zpspsk(ig,ll)=(pplay(ig,ll)/100000.)**RKAPPA
201 18607680 zu(ig,ll)=pu(ig,ll)
202 18607680 zv(ig,ll)=pv(ig,ll)
203 !attention zh est maintenant le profil de T et plus le profil de theta !
204 ! Quelle horreur ! A eviter.
205 !
206 ! T-> Theta
207 18607680 ztv(ig,ll)=zh(ig,ll)/zpspsk(ig,ll)
208 !Theta_v
209 18607680 ztv(ig,ll)=ztv(ig,ll)*(1.+RETV*(zo(ig,ll))-zl(ig,ll))
210 !Thetal
211 18626400 zthl(ig,ll)=pt(ig,ll)/zpspsk(ig,ll)
212 !
213 ENDDO
214 ENDDO
215
216 480 RETURN
217 END
218