GCC Code Coverage Report


Directory: ./
File: phys/ener_conserv.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 75 134 56.0%
Branches: 131 350 37.4%

Line Branch Exec Source
1 2880 subroutine ener_conserv(klon,klev,pdtphys, &
2 & puo,pvo,pto,pqo,pql0,pqs0, &
3 480 & pun,pvn,ptn,pqn,pqln,pqsn,dtke,masse,exner,d_t_ec)
4
5 !=============================================================
6 ! Energy conservation
7 ! Based on the TKE equation
8 ! The M2 and N2 terms at the origin of TKE production are
9 ! concerted into heating in the d_t_ec term
10 ! Option 1 is the standard
11 ! 101 is for M2 term only
12 ! 101 for N2 term only
13 ! -1 is a previours treatment for kinetic energy only
14 ! FH (hourdin@lmd.jussieu.fr), 2013/04/25
15 !=============================================================
16
17 !=============================================================
18 ! Declarations
19 !=============================================================
20
21 ! From module
22 USE phys_local_var_mod, ONLY : d_u_vdf,d_v_vdf,d_t_vdf,d_u_ajs,d_v_ajs,d_t_ajs, &
23 & d_u_con,d_v_con,d_t_con,d_t_diss
24 USE phys_local_var_mod, ONLY : d_t_eva,d_t_lsc,d_q_eva,d_q_lsc
25 USE phys_local_var_mod, ONLY : d_u_oro,d_v_oro,d_u_lif,d_v_lif
26 USE phys_local_var_mod, ONLY : du_gwd_hines,dv_gwd_hines,dv_gwd_front,dv_gwd_rando
27 USE phys_state_var_mod, ONLY : du_gwd_front,du_gwd_rando
28 USE phys_output_var_mod, ONLY : bils_ec,bils_ech,bils_tke,bils_kinetic,bils_enthalp,bils_latent,bils_diss
29 USE add_phys_tend_mod, ONLY : fl_cor_ebil
30
31
32 IMPLICIT none
33 !
34 ! $Header$
35 !
36 ! ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
37 ! veillez � n'utiliser que des ! pour les commentaires
38 ! et � bien positionner les & des lignes de continuation
39 ! (les placer en colonne 6 et en colonne 73)
40 !
41 !
42 ! A1.0 Fundamental constants
43 REAL RPI,RCLUM,RHPLA,RKBOL,RNAVO
44 ! A1.1 Astronomical constants
45 REAL RDAY,REA,REPSM,RSIYEA,RSIDAY,ROMEGA
46 ! A1.1.bis Constantes concernant l'orbite de la Terre:
47 REAL R_ecc, R_peri, R_incl
48 ! A1.2 Geoide
49 REAL RA,RG,R1SA
50 ! A1.3 Radiation
51 ! REAL RSIGMA,RI0
52 REAL RSIGMA
53 ! A1.4 Thermodynamic gas phase
54 REAL RMO3,RMCO2,RMC,RMCH4,RMN2O,RMCFC11,RMCFC12
55 REAL R,RMD,RMV,RD,RV,RCPD,RCPV,RCVD,RCVV
56 REAL RKAPPA,RETV, eps_w
57 ! A1.5,6 Thermodynamic liquid,solid phases
58 REAL RCW,RCS
59 ! A1.7 Thermodynamic transition of phase
60 REAL RLVTT,RLSTT,RLMLT,RTT,RATM
61 ! A1.8 Curve of saturation
62 REAL RESTT,RALPW,RBETW,RGAMW,RALPS,RBETS,RGAMS
63 REAL RALPD,RBETD,RGAMD
64 !
65 COMMON/YOMCST/RPI ,RCLUM ,RHPLA ,RKBOL ,RNAVO &
66 & ,RDAY ,REA ,REPSM ,RSIYEA,RSIDAY,ROMEGA &
67 & ,R_ecc, R_peri, R_incl &
68 & ,RA ,RG ,R1SA &
69 & ,RSIGMA &
70 & ,R ,RMD ,RMV ,RD ,RV ,RCPD &
71 & ,RMO3 ,RMCO2 ,RMC ,RMCH4 ,RMN2O ,RMCFC11 ,RMCFC12 &
72 & ,RCPV ,RCVD ,RCVV ,RKAPPA,RETV, eps_w &
73 & ,RCW ,RCS &
74 & ,RLVTT ,RLSTT ,RLMLT ,RTT ,RATM &
75 & ,RESTT ,RALPW ,RBETW ,RGAMW ,RALPS ,RBETS ,RGAMS &
76 & ,RALPD ,RBETD ,RGAMD
77 ! ------------------------------------------------------------------
78 !$OMP THREADPRIVATE(/YOMCST/)
79 !
80 ! $Id: YOETHF.h 2799 2017-02-24 18:50:33Z jyg $
81 !
82 ! ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
83 ! veillez n'utiliser que des ! pour les commentaires
84 ! et bien positionner les & des lignes de continuation
85 ! (les placer en colonne 6 et en colonne 73)
86 !
87 !* COMMON *YOETHF* DERIVED CONSTANTS SPECIFIC TO ECMWF THERMODYNAMICS
88 !
89 ! *R__ES* *CONSTANTS USED FOR COMPUTATION OF SATURATION
90 ! MIXING RATIO OVER LIQUID WATER(*R_LES*) OR
91 ! ICE(*R_IES*).
92 ! *RVTMP2* *RVTMP2=RCPV/RCPD-1.
93 ! *RHOH2O* *DENSITY OF LIQUID WATER. (RATM/100.)
94 !
95 REAL R2ES, R3LES, R3IES, R4LES, R4IES, R5LES, R5IES
96 REAL RVTMP2, RHOH2O
97 REAL R5ALVCP,R5ALSCP,RALVDCP,RALSDCP,RALFDCP,RTWAT,RTBER,RTBERCU
98 REAL RTICE,RTICECU,RTWAT_RTICE_R,RTWAT_RTICECU_R,RKOOP1,RKOOP2
99 LOGICAL OK_BAD_ECMWF_THERMO ! If TRUE, then variables set by rrtm/suphec.F90
100 ! If FALSE, then variables set by suphel.F90
101 COMMON /YOETHF/R2ES, R3LES, R3IES, R4LES, R4IES, R5LES, R5IES, &
102 & RVTMP2, RHOH2O, &
103 & R5ALVCP,R5ALSCP,RALVDCP,RALSDCP, &
104 & RALFDCP,RTWAT,RTBER,RTBERCU, &
105 & RTICE,RTICECU,RTWAT_RTICE_R,RTWAT_RTICECU_R,RKOOP1,&
106 & RKOOP2, &
107 & OK_BAD_ECMWF_THERMO
108
109 !$OMP THREADPRIVATE(/YOETHF/)
110 ! $Id: clesphys.h 3435 2019-01-22 15:21:59Z fairhead $
111 !
112 ! ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
113 ! veillez \`a n'utiliser que des ! pour les commentaires
114 ! et \`a bien positionner les & des lignes de continuation
115 ! (les placer en colonne 6 et en colonne 73)
116 !
117 !..include cles_phys.h
118 !
119 INTEGER iflag_cycle_diurne
120 LOGICAL soil_model,new_oliq,ok_orodr,ok_orolf
121 LOGICAL ok_limitvrai
122 LOGICAL ok_all_xml
123 LOGICAL ok_lwoff
124 INTEGER nbapp_rad, iflag_con, nbapp_cv, nbapp_wk, iflag_ener_conserv
125 REAL co2_ppm, co2_ppm0, solaire
126 !FC
127 REAL Cd_frein
128 LOGICAL ok_suntime_rrtm
129 REAL(kind=8) RCO2, RCH4, RN2O, RCFC11, RCFC12
130 REAL(kind=8) RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act
131 REAL(kind=8) CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt
132 !IM ajout CFMIP2/CMIP5
133 REAL(kind=8) RCO2_per,RCH4_per,RN2O_per,RCFC11_per,RCFC12_per
134 REAL(kind=8) CH4_ppb_per,N2O_ppb_per,CFC11_ppt_per,CFC12_ppt_per
135
136 !OM ---> correction du bilan d'eau global
137 !OM Correction sur precip KE
138 REAL cvl_corr
139 !OM Fonte calotte dans bilan eau
140 LOGICAL ok_lic_melt
141 !OB Depot de vapeur d eau sur la calotte pour le bilan eau
142 LOGICAL ok_lic_cond
143
144 !IM simulateur ISCCP
145 INTEGER top_height, overlap
146 !IM seuils cdrm, cdrh
147 REAL cdmmax, cdhmax
148 !IM param. stabilite s/ terres et en dehors
149 REAL ksta, ksta_ter, f_ri_cd_min
150 !IM ok_kzmin : clef calcul Kzmin dans la CL de surface cf FH
151 LOGICAL ok_kzmin
152 !IM, MAFo fmagic, pmagic : parametres - additionnel et multiplicatif -
153 ! pour regler l albedo sur ocean
154 REAL pbl_lmixmin_alpha
155 REAL fmagic, pmagic
156 ! Hauteur (imposee) du contenu en eau du sol
157 REAL qsol0,albsno0,evap0
158 ! Frottement au sol (Cdrag)
159 Real f_cdrag_ter,f_cdrag_oce
160 REAL min_wind_speed,f_gust_wk,f_gust_bl,f_qsat_oce,f_z0qh_oce
161 REAL z0m_seaice,z0h_seaice
162 INTEGER iflag_gusts,iflag_z0_oce
163
164 ! Rugoro
165 Real f_rugoro,z0min
166
167 ! tau_gl : constante de rappel de la temperature a la surface de la glace
168 REAL tau_gl
169
170 !IM lev_histhf : niveau sorties 6h
171 !IM lev_histday : niveau sorties journalieres
172 !IM lev_histmth : niveau sorties mensuelles
173 !IM lev_histdayNMC : on peut sortir soit sur 8 (comme AR5) ou bien
174 ! sur 17 niveaux de pression
175 INTEGER lev_histhf, lev_histday, lev_histmth
176 INTEGER lev_histdayNMC
177 Integer lev_histins, lev_histLES
178 !IM ok_histNMC : sortie fichiers niveaux de pression (histmthNMC, histdayNMC, histhfNMC)
179 !IM freq_outNMC : frequences de sortie fichiers niveaux de pression (histmthNMC, histdayNMC, histhfNMC)
180 !IM freq_calNMC : frequences de calcul fis. hist*NMC.nc
181 LOGICAL ok_histNMC(3)
182 INTEGER levout_histNMC(3)
183 REAL freq_outNMC(3) , freq_calNMC(3)
184 CHARACTER(len=4) type_run
185 ! aer_type: pour utiliser un fichier constant dans readaerosol
186 CHARACTER(len=8) :: aer_type
187 LOGICAL ok_regdyn
188 REAL lonmin_ins, lonmax_ins, latmin_ins, latmax_ins
189 REAL ecrit_ins, ecrit_hf, ecrit_day
190 REAL ecrit_mth, ecrit_tra, ecrit_reg
191 REAL ecrit_LES
192 REAL freq_ISCCP, ecrit_ISCCP
193 REAL freq_COSP, freq_AIRS
194 LOGICAL :: ok_cosp,ok_mensuelCOSP,ok_journeCOSP,ok_hfCOSP
195 LOGICAL :: ok_airs
196 INTEGER :: ip_ebil_phy, iflag_rrtm, iflag_ice_thermo, NSW, iflag_albedo
197 LOGICAL :: ok_chlorophyll
198 LOGICAL :: ok_strato
199 LOGICAL :: ok_hines, ok_gwd_rando
200 LOGICAL :: ok_qch4
201 LOGICAL :: ok_conserv_q
202 LOGICAL :: adjust_tropopause
203 LOGICAL :: ok_daily_climoz
204 ! flag to bypass or not the phytrac module
205 INTEGER :: iflag_phytrac
206
207 COMMON/clesphys/ &
208 ! REAL FIRST
209 & co2_ppm, solaire &
210 & , RCO2, RCH4, RN2O, RCFC11, RCFC12 &
211 & , RCO2_act, RCH4_act, RN2O_act, RCFC11_act, RCFC12_act &
212 & , RCO2_per, RCH4_per, RN2O_per, RCFC11_per, RCFC12_per &
213 & , CH4_ppb, N2O_ppb, CFC11_ppt, CFC12_ppt &
214 & , CH4_ppb_per, N2O_ppb_per, CFC11_ppt_per, CFC12_ppt_per &
215 & , cdmmax,cdhmax,ksta,ksta_ter,f_ri_cd_min,pbl_lmixmin_alpha &
216 & , fmagic, pmagic &
217 & , f_cdrag_ter,f_cdrag_oce,f_rugoro,z0min,tau_gl &
218 & , min_wind_speed,f_gust_wk,f_gust_bl,f_qsat_oce,f_z0qh_oce &
219 & , z0m_seaice,z0h_seaice &
220 & , freq_outNMC, freq_calNMC &
221 & , lonmin_ins, lonmax_ins, latmin_ins, latmax_ins &
222 & , freq_ISCCP, ecrit_ISCCP, freq_COSP, freq_AIRS &
223 & , cvl_corr &
224 & , qsol0,albsno0,evap0 &
225 & , co2_ppm0 &
226 !FC
227 & , Cd_frein &
228 & , ecrit_LES &
229 & , ecrit_ins, ecrit_hf, ecrit_day &
230 & , ecrit_mth, ecrit_tra, ecrit_reg &
231 ! THEN INTEGER AND LOGICALS
232 & , top_height &
233 & , iflag_cycle_diurne, soil_model, new_oliq &
234 & , ok_orodr, ok_orolf, ok_limitvrai, nbapp_rad &
235 & , iflag_con, nbapp_cv, nbapp_wk &
236 & , iflag_ener_conserv &
237 & , ok_suntime_rrtm &
238 & , overlap &
239 & , ok_kzmin &
240 & , lev_histhf, lev_histday, lev_histmth &
241 & , lev_histins, lev_histLES, lev_histdayNMC, levout_histNMC &
242 & , ok_histNMC &
243 & , type_run, ok_regdyn, ok_cosp, ok_airs &
244 & , ok_mensuelCOSP,ok_journeCOSP,ok_hfCOSP &
245 & , ip_ebil_phy &
246 & , iflag_gusts ,iflag_z0_oce &
247 & , ok_lic_melt, ok_lic_cond, aer_type &
248 & , iflag_rrtm, ok_strato,ok_hines, ok_qch4 &
249 & , iflag_ice_thermo, ok_gwd_rando, NSW, iflag_albedo &
250 & , ok_chlorophyll,ok_conserv_q, adjust_tropopause &
251 & , ok_daily_climoz, ok_all_xml, ok_lwoff &
252 & , iflag_phytrac
253
254 save /clesphys/
255 !$OMP THREADPRIVATE(/clesphys/)
256 !
257 ! $Header$
258 !
259 !jyg+al1<
260 !! integer iflag_pbl,iflag_pbl_split
261 !! common/compbl/iflag_pbl,iflag_pbl_split
262 !!FC integer iflag_pbl, iflag_pbl_split, iflag_order2_sollw
263 !FC common/compbl/iflag_pbl, iflag_pbl_split, iflag_order2_sollw
264 integer iflag_pbl, iflag_pbl_split, iflag_order2_sollw, ifl_pbltree
265 common/compbl/iflag_pbl, iflag_pbl_split, iflag_order2_sollw, ifl_pbltree
266 !>jyg+al1
267 !$OMP THREADPRIVATE(/compbl/)
268
269 ! Arguments
270 INTEGER, INTENT(IN) :: klon,klev
271 REAL, INTENT(IN) :: pdtphys
272 REAL, DIMENSION(klon,klev), INTENT(IN) :: puo,pvo,pto,pqo,pql0,pqs0
273 REAL, DIMENSION(klon,klev), INTENT(IN) :: pun,pvn,ptn,pqn,pqln,pqsn
274 REAL, DIMENSION(klon,klev), INTENT(IN) :: masse,exner
275 REAL, DIMENSION(klon,klev+1), INTENT(IN) :: dtke
276 !
277 REAL, DIMENSION(klon,klev), INTENT(OUT) :: d_t_ec
278
279 ! Local
280 integer k,i
281 960 REAL, DIMENSION(klon,klev+1) :: fluxu,fluxv,fluxt
282 960 REAL, DIMENSION(klon,klev+1) :: dddu,dddv,dddt
283 960 REAL, DIMENSION(klon,klev) :: d_u,d_v,d_t,zv,zu,d_t_ech
284 REAL ZRCPD
285
286 character*80 abort_message
287 character*20 :: modname
288
289
290 480 modname='ener_conser'
291
4/4
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 18607680 times.
✓ Branch 3 taken 18720 times.
18626880 d_t_ec(:,:)=0.
292
293
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 IF (iflag_ener_conserv==-1) THEN
294 !+jld ec_conser
295 DO k = 1, klev
296 DO i = 1, klon
297 IF (fl_cor_ebil .GT. 0) then
298 ZRCPD = RCPD*(1.0+RVTMP2*(pqn(i,k)+pqln(i,k)+pqsn(i,k)))
299 ELSE
300 ZRCPD = RCPD*(1.0+RVTMP2*pqn(i,k))
301 ENDIF
302 d_t_ec(i,k)=0.5/ZRCPD &
303 & *(puo(i,k)**2+pvo(i,k)**2-pun(i,k)**2-pvn(i,k)**2)
304 ENDDO
305 ENDDO
306 !-jld ec_conser
307
308
309
310
1/2
✓ Branch 0 taken 480 times.
✗ Branch 1 not taken.
480 ELSEIF (iflag_ener_conserv>=1) THEN
311
312
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 IF (iflag_ener_conserv<=2) THEN
313 ! print*,'ener_conserv pbl=',iflag_pbl
314 IF (iflag_pbl>=20 .AND. iflag_pbl<=27) THEN !d_t_diss accounts for conserv
315 d_t(:,:)=d_t_ajs(:,:) ! d_t_ajs = adjust + thermals
316 d_u(:,:)=d_u_ajs(:,:)+d_u_con(:,:)
317 d_v(:,:)=d_v_ajs(:,:)+d_v_con(:,:)
318 ELSE
319 d_t(:,:)=d_t_vdf(:,:)+d_t_ajs(:,:) ! d_t_ajs = adjust + thermals
320 d_u(:,:)=d_u_vdf(:,:)+d_u_ajs(:,:)+d_u_con(:,:)
321 d_v(:,:)=d_v_vdf(:,:)+d_v_ajs(:,:)+d_v_con(:,:)
322 ENDIF
323
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 ELSEIF (iflag_ener_conserv==101) THEN
324 d_t(:,:)=0.
325 d_u(:,:)=d_u_vdf(:,:)+d_u_ajs(:,:)+d_u_con(:,:)
326 d_v(:,:)=d_v_vdf(:,:)+d_v_ajs(:,:)+d_v_con(:,:)
327
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 ELSEIF (iflag_ener_conserv==110) THEN
328 d_t(:,:)=d_t_vdf(:,:)+d_t_ajs(:,:)
329 d_u(:,:)=0.
330 d_v(:,:)=0.
331
332
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 ELSEIF (iflag_ener_conserv==3) THEN
333 d_t(:,:)=0.
334 d_u(:,:)=0.
335 d_v(:,:)=0.
336
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 ELSEIF (iflag_ener_conserv==4) THEN
337 d_t(:,:)=0.
338 d_u(:,:)=d_u_vdf(:,:)
339 d_v(:,:)=d_v_vdf(:,:)
340
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 ELSEIF (iflag_ener_conserv==5) THEN
341 d_t(:,:)=d_t_vdf(:,:)
342 d_u(:,:)=d_u_vdf(:,:)
343 d_v(:,:)=d_v_vdf(:,:)
344
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 ELSEIF (iflag_ener_conserv==6) THEN
345 d_t(:,:)=d_t_vdf(:,:)
346 d_u(:,:)=d_u_vdf(:,:)+d_u_ajs(:,:)
347 d_v(:,:)=d_v_vdf(:,:)+d_v_ajs(:,:)
348
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 ELSEIF (iflag_ener_conserv==7) THEN
349 d_t(:,:)=d_t_vdf(:,:)+d_t_ajs(:,:)
350 d_u(:,:)=d_u_vdf(:,:)+d_u_ajs(:,:)
351 d_v(:,:)=d_v_vdf(:,:)+d_v_ajs(:,:)
352
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 ELSEIF (iflag_ener_conserv==8) THEN
353 d_t(:,:)=d_t_vdf(:,:)
354 d_u(:,:)=d_u_vdf(:,:)+d_u_ajs(:,:)+d_u_con(:,:)
355 d_v(:,:)=d_v_vdf(:,:)+d_v_ajs(:,:)+d_v_con(:,:)
356
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 ELSEIF (iflag_ener_conserv==9) THEN
357 d_t(:,:)=d_t_vdf(:,:)
358 d_u(:,:)=d_u_vdf(:,:)+d_u_ajs(:,:)+d_u_con(:,:)+d_u_oro(:,:)
359 d_v(:,:)=d_v_vdf(:,:)+d_v_ajs(:,:)+d_v_con(:,:)+d_v_oro(:,:)
360
1/2
✓ Branch 0 taken 480 times.
✗ Branch 1 not taken.
480 ELSEIF (iflag_ener_conserv==10) THEN
361
4/4
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 18607680 times.
✓ Branch 3 taken 18720 times.
18626880 d_t(:,:)=d_t_vdf(:,:)
362
4/4
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 18607680 times.
✓ Branch 3 taken 18720 times.
18626880 d_u(:,:)=d_u_vdf(:,:)+d_u_ajs(:,:)+d_u_con(:,:)+d_u_oro(:,:)+d_u_lif(:,:)
363
4/4
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 18607680 times.
✓ Branch 3 taken 18720 times.
18626880 d_v(:,:)=d_v_vdf(:,:)+d_v_ajs(:,:)+d_v_con(:,:)+d_v_oro(:,:)+d_v_lif(:,:)
364 ELSEIF (iflag_ener_conserv==11) THEN
365 d_t(:,:)=d_t_vdf(:,:)
366 d_u(:,:)=d_u_vdf(:,:)+d_u_ajs(:,:)+d_u_con(:,:)+d_u_oro(:,:)+d_u_lif(:,:)
367 d_v(:,:)=d_v_vdf(:,:)+d_v_ajs(:,:)+d_v_con(:,:)+d_v_oro(:,:)+d_v_lif(:,:)
368 IF (ok_hines) THEN
369 d_u_vdf(:,:)=d_u_vdf(:,:)+du_gwd_hines(:,:)
370 d_v_vdf(:,:)=d_v_vdf(:,:)+dv_gwd_hines(:,:)
371 ENDIF
372 IF (.not. ok_hines .and. ok_gwd_rando) THEN
373 d_u_vdf(:,:)=d_u_vdf(:,:)+du_gwd_front(:,:)
374 d_v_vdf(:,:)=d_v_vdf(:,:)+dv_gwd_front(:,:)
375 ENDIF
376 IF (ok_gwd_rando) THEN
377 d_u_vdf(:,:)=d_u_vdf(:,:)+du_gwd_rando(:,:)
378 d_v_vdf(:,:)=d_v_vdf(:,:)+dv_gwd_rando(:,:)
379 ENDIF
380 ELSE
381 abort_message = 'iflag_ener_conserv non prevu'
382 CALL abort_physic (modname,abort_message,1)
383 ENDIF
384
385 !----------------------------------------------------------------------------
386 ! Two options wether we consider time integration in the energy conservation
387 !----------------------------------------------------------------------------
388
389
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 480 times.
480 if (iflag_ener_conserv==2) then
390 zu(:,:)=puo(:,:)
391 zv(:,:)=pvo(:,:)
392 else
393
1/2
✓ Branch 0 taken 480 times.
✗ Branch 1 not taken.
480 IF (iflag_pbl>=20 .AND. iflag_pbl<=27) THEN
394 zu(:,:)=puo(:,:)+d_u_vdf(:,:)+0.5*d_u(:,:)
395 zv(:,:)=pvo(:,:)+d_v_vdf(:,:)+0.5*d_v(:,:)
396 ELSE
397
4/4
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 18720 times.
✓ Branch 2 taken 18607680 times.
✓ Branch 3 taken 18720 times.
18626880 zu(:,:)=puo(:,:)+0.5*d_u(:,:)
398
4/4
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
✓ Branch 2 taken 18607680 times.
✓ Branch 3 taken 18720 times.
18626880 zv(:,:)=pvo(:,:)+0.5*d_v(:,:)
399 ENDIF
400 endif
401
402
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 fluxu(:,klev+1)=0.
403
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 fluxv(:,klev+1)=0.
404
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 fluxt(:,klev+1)=0.
405
406
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 18720 times.
19200 do k=klev,1,-1
407
2/2
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 18607680 times.
18626400 fluxu(:,k)=fluxu(:,k+1)+masse(:,k)*d_u(:,k)
408
2/2
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 18607680 times.
18626400 fluxv(:,k)=fluxv(:,k+1)+masse(:,k)*d_v(:,k)
409
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626880 fluxt(:,k)=fluxt(:,k+1)+masse(:,k)*d_t(:,k)/exner(:,k)
410 enddo
411
412
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 dddu(:,1)=2*zu(:,1)*fluxu(:,1)
413
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 dddv(:,1)=2*zv(:,1)*fluxv(:,1)
414
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 dddt(:,1)=(exner(:,1)-1.)*fluxt(:,1)
415
416
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 18240 times.
18720 do k=2,klev
417
2/2
✓ Branch 0 taken 18240 times.
✓ Branch 1 taken 18130560 times.
18148800 dddu(:,k)=(zu(:,k)-zu(:,k-1))*fluxu(:,k)
418
2/2
✓ Branch 0 taken 18240 times.
✓ Branch 1 taken 18130560 times.
18148800 dddv(:,k)=(zv(:,k)-zv(:,k-1))*fluxv(:,k)
419
2/2
✓ Branch 0 taken 18130560 times.
✓ Branch 1 taken 18240 times.
18149280 dddt(:,k)=(exner(:,k)-exner(:,k-1))*fluxt(:,k)
420 enddo
421
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 dddu(:,klev+1)=0.
422
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 dddv(:,klev+1)=0.
423
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 dddt(:,klev+1)=0.
424
425
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 18720 times.
19200 do k=1,klev
426
2/2
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 18607680 times.
18626400 d_t_ech(:,k)=-(rcpd*(dddt(:,k)+dddt(:,k+1)))/(2.*rcpd*masse(:,k))
427
2/2
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 18607680 times.
18626880 d_t_ec(:,k)=-(dddu(:,k)+dddu(:,k+1)+dddv(:,k)+dddv(:,k+1))/(2.*rcpd*masse(:,k))+d_t_ech(:,k)
428 enddo
429
430 ENDIF
431
432 !================================================================
433 ! Computation of integrated enthalpie and kinetic energy variation
434 ! FH (hourdin@lmd.jussieu.fr), 2013/04/25
435 ! bils_ec : energie conservation term
436 ! bils_ech : part of this term linked to temperature
437 ! bils_tke : change of TKE
438 ! bils_diss : dissipation of TKE (when activated)
439 ! bils_kinetic : change of kinetic energie of the column
440 ! bils_enthalp : change of enthalpie
441 ! bils_latent : change of latent heat. Computed between
442 ! after reevaporation (at the beginning of the physics)
443 ! and before large scale condensation (fisrtilp)
444 !================================================================
445
446
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 bils_ec(:)=0.
447
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 bils_ech(:)=0.
448
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 bils_tke(:)=0.
449
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 bils_diss(:)=0.
450
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 bils_kinetic(:)=0.
451
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 bils_enthalp(:)=0.
452
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 bils_latent(:)=0.
453
2/2
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 480 times.
19200 DO k=1,klev
454
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626400 bils_ec(:)=bils_ec(:)-d_t_ec(:,k)*masse(:,k)
455
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626400 bils_diss(:)=bils_diss(:)-d_t_diss(:,k)*masse(:,k)
456 bils_kinetic(:)=bils_kinetic(:)+masse(:,k)* &
457 & (pun(:,k)*pun(:,k)+pvn(:,k)*pvn(:,k) &
458
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626400 & -puo(:,k)*puo(:,k)-pvo(:,k)*pvo(:,k))
459 bils_enthalp(:)= &
460
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626400 & bils_enthalp(:)+masse(:,k)*(ptn(:,k)-pto(:,k)+d_t_ec(:,k)-d_t_eva(:,k)-d_t_lsc(:,k))
461 ! & bils_enthalp(:)+masse(:,k)*(ptn(:,k)-pto(:,k)+d_t_ec(:,k))
462 bils_latent(:)=bils_latent(:)+masse(:,k)* &
463 ! & (pqn(:,k)-pqo(:,k))
464
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626880 & (pqn(:,k)-pqo(:,k)-d_q_eva(:,k)-d_q_lsc(:,k))
465 ENDDO
466
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 bils_ec(:)=rcpd*bils_ec(:)/pdtphys
467
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 bils_diss(:)=rcpd*bils_diss(:)/pdtphys
468
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 bils_kinetic(:)= 0.5*bils_kinetic(:)/pdtphys
469
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 bils_enthalp(:)=rcpd*bils_enthalp(:)/pdtphys
470
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 bils_latent(:)=rlvtt*bils_latent(:)/pdtphys
471 !jyg<
472
1/2
✓ Branch 0 taken 480 times.
✗ Branch 1 not taken.
480 IF (iflag_pbl > 1) THEN
473
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 18720 times.
19200 DO k=1,klev
474
2/2
✓ Branch 0 taken 18720 times.
✓ Branch 1 taken 18607680 times.
18626880 bils_tke(:)=bils_tke(:)+0.5*(dtke(:,k)+dtke(:,k+1))*masse(:,k)
475 ENDDO
476
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 bils_tke(:)=bils_tke(:)/pdtphys
477 ENDIF ! (iflag_pbl > 1)
478 !>jyg
479
480
1/2
✓ Branch 0 taken 480 times.
✗ Branch 1 not taken.
480 IF (iflag_ener_conserv>=1) THEN
481
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 477120 times.
477600 bils_ech(:)=0.
482
2/2
✓ Branch 0 taken 480 times.
✓ Branch 1 taken 18720 times.
19200 DO k=1,klev
483
2/2
✓ Branch 0 taken 18607680 times.
✓ Branch 1 taken 18720 times.
18626880 bils_ech(:)=bils_ech(:)-d_t_ech(:,k)*masse(:,k)
484 ENDDO
485
2/2
✓ Branch 0 taken 477120 times.
✓ Branch 1 taken 480 times.
477600 bils_ech(:)=rcpd*bils_ech(:)/pdtphys
486 ENDIF
487
488 480 RETURN
489
490 END
491