GCC Code Coverage Report


Directory: ./
File: phys/phyetat0.f90
Date: 2022-01-11 19:19:34
Exec Total Coverage
Lines: 179 262 68.3%
Branches: 225 468 48.1%

Line Branch Exec Source
1 ! $Id: phyetat0.F90 3956 2021-07-06 07:16:14Z jyg $
2
3 15 SUBROUTINE phyetat0 (fichnom, clesphy0, tabcntr0)
4
5 USE dimphy, only: klon, zmasq, klev
6 USE iophy, ONLY : init_iophy_new
7 USE ocean_cpl_mod, ONLY : ocean_cpl_init
8 USE fonte_neige_mod, ONLY : fonte_neige_init
9 USE pbl_surface_mod, ONLY : pbl_surface_init
10 USE surface_data, ONLY : type_ocean, version_ocean
11 USE phys_state_var_mod, ONLY : ancien_ok, clwcon, detr_therm, phys_tstep, &
12 qsol, fevap, z0m, z0h, agesno, &
13 du_gwd_rando, du_gwd_front, entr_therm, f0, fm_therm, &
14 falb_dir, falb_dif, prw_ancien, prlw_ancien, prsw_ancien, &
15 ftsol, pbl_tke, pctsrf, q_ancien, ql_ancien, qs_ancien, radpas, radsol, rain_fall, ratqs, &
16 rnebcon, rugoro, sig1, snow_fall, solaire_etat0, sollw, sollwdown, &
17 solsw, solswfdiff, t_ancien, u_ancien, v_ancien, w01, wake_cstar, wake_deltaq, &
18 wake_deltat, wake_delta_pbl_TKE, delta_tsurf, beta_aridity, wake_fip, wake_pe, &
19 wake_s, wake_dens, awake_dens, cv_gen, zgam, zmax0, zmea, zpic, zsig, &
20 zstd, zthe, zval, ale_bl, ale_bl_trig, alp_bl, u10m, v10m, treedrg, &
21 ale_wake, ale_bl_stat, ds_ns, dt_ns, delta_sst, delta_sal, ratqs_inter
22 !FC
23 USE geometry_mod, ONLY : longitude_deg, latitude_deg
24 USE iostart, ONLY : close_startphy, get_field, get_var, open_startphy
25 USE infotrac_phy, only: nbtr, nqo, type_trac, tname, niadv
26 USE traclmdz_mod, ONLY : traclmdz_from_restart
27 USE carbon_cycle_mod, ONLY : carbon_cycle_tr, carbon_cycle_cpl, co2_send
28 USE indice_sol_mod, only: nbsrf, is_ter, epsfra, is_lic, is_oce, is_sic
29 USE ocean_slab_mod, ONLY: nslay, tslab, seaice, tice, ocean_slab_init
30 USE time_phylmdz_mod, ONLY: init_iteration, pdtphys, itau_phy
31 use netcdf, only: missing_val => nf90_fill_real
32 use config_ocean_skin_m, only: activate_ocean_skin
33
34 IMPLICIT none
35 !======================================================================
36 ! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
37 ! Objet: Lecture de l'etat initial pour la physique
38 !======================================================================
39 include "dimsoil.h"
40 include "clesphys.h"
41 include "thermcell.h"
42 include "compbl.h"
43 include "YOMCST.h"
44 !======================================================================
45 CHARACTER*(*) fichnom
46
47 ! les variables globales lues dans le fichier restart
48
49 2 REAL tsoil(klon, nsoilmx, nbsrf)
50 2 REAL qsurf(klon, nbsrf)
51 2 REAL snow(klon, nbsrf)
52 2 real fder(klon)
53 2 REAL run_off_lic_0(klon)
54 2 REAL fractint(klon)
55 2 REAL trs(klon, nbtr)
56 2 REAL zts(klon)
57 ! pour drag arbres FC
58 2 REAL drg_ter(klon,klev)
59
60 CHARACTER*6 ocean_in
61 LOGICAL ok_veget_in
62
63 INTEGER longcles
64 PARAMETER ( longcles = 20 )
65 REAL clesphy0( longcles )
66
67 REAL xmin, xmax
68
69 INTEGER nid, nvarid
70 INTEGER ierr, i, nsrf, isoil , k
71 INTEGER length
72 PARAMETER (length=100)
73 INTEGER it, iiq, isw
74 REAL tab_cntrl(length), tabcntr0(length)
75 CHARACTER*7 str7
76 CHARACTER*2 str2
77 LOGICAL :: found,phyetat0_get,phyetat0_srf
78 2 REAL :: lon_startphy(klon), lat_startphy(klon)
79
80 ! FH1D
81 ! real iolat(jjm+1)
82 !real iolat(jjm+1-1/(iim*jjm))
83
84 ! Ouvrir le fichier contenant l'etat initial:
85
86 1 CALL open_startphy(fichnom)
87
88 ! Lecture des parametres de controle:
89
90 1 CALL get_var("controle", tab_cntrl)
91
92 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
93 ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
94 ! Les constantes de la physiques sont lues dans la physique seulement.
95 ! Les egalites du type
96 ! tab_cntrl( 5 )=clesphy0(1)
97 ! sont remplacees par
98 ! clesphy0(1)=tab_cntrl( 5 )
99 ! On inverse aussi la logique.
100 ! On remplit les tab_cntrl avec les parametres lus dans les .def
101 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
102
103
2/2
✓ Branch 0 taken 100 times.
✓ Branch 1 taken 1 times.
101 DO i = 1, length
104 101 tabcntr0( i ) = tab_cntrl( i )
105 ENDDO
106
107 1 tab_cntrl(1)=pdtphys
108 1 tab_cntrl(2)=radpas
109
110 ! co2_ppm : value from the previous time step
111
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
1 IF (carbon_cycle_tr .OR. carbon_cycle_cpl) THEN
112 co2_ppm = tab_cntrl(3)
113 RCO2 = co2_ppm * 1.0e-06 * RMCO2 / RMD
114 ! ELSE : keep value from .def
115 ENDIF
116
117 ! co2_ppm0 : initial value of atmospheric CO2 (from create_etat0_limit.e .def)
118 ! co2_ppm0 = tab_cntrl(16)
119 ! initial value for interactive CO2 run when there is no tracer field for CO2 in restart
120 1 co2_ppm0=284.32
121
122 1 solaire_etat0 = tab_cntrl(4)
123 1 tab_cntrl(5)=iflag_con
124 1 tab_cntrl(6)=nbapp_rad
125
126
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (iflag_cycle_diurne.GE.1) tab_cntrl( 7) = iflag_cycle_diurne
127
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (soil_model) tab_cntrl( 8) =1.
128
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (new_oliq) tab_cntrl( 9) =1.
129
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ok_orodr) tab_cntrl(10) =1.
130
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ok_orolf) tab_cntrl(11) =1.
131
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ok_limitvrai) tab_cntrl(12) =1.
132
133 1 itau_phy = tab_cntrl(15)
134
135 1 clesphy0(1)=tab_cntrl( 5 )
136 1 clesphy0(2)=tab_cntrl( 6 )
137 1 clesphy0(3)=tab_cntrl( 7 )
138 1 clesphy0(4)=tab_cntrl( 8 )
139 1 clesphy0(5)=tab_cntrl( 9 )
140 1 clesphy0(6)=tab_cntrl( 10 )
141 1 clesphy0(7)=tab_cntrl( 11 )
142 1 clesphy0(8)=tab_cntrl( 12 )
143
144 ! set time iteration
145 1 CALL init_iteration(itau_phy)
146
147 ! read latitudes and make a sanity check (because already known from dyn)
148 1 CALL get_field("latitude",lat_startphy)
149
2/2
✓ Branch 0 taken 994 times.
✓ Branch 1 taken 1 times.
995 DO i=1,klon
150
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 994 times.
994 IF (ABS(lat_startphy(i)-latitude_deg(i))>=1) THEN
151 WRITE(*,*) "phyetat0: Error! Latitude discrepancy wrt startphy file:",&
152 " i=",i," lat_startphy(i)=",lat_startphy(i),&
153 " latitude_deg(i)=",latitude_deg(i)
154 ! This is presumably serious enough to abort run
155 CALL abort_physic("phyetat0","discrepancy in latitudes!",1)
156 ENDIF
157
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 994 times.
995 IF (ABS(lat_startphy(i)-latitude_deg(i))>=0.0001) THEN
158 WRITE(*,*) "phyetat0: Warning! Latitude discrepancy wrt startphy file:",&
159 " i=",i," lat_startphy(i)=",lat_startphy(i),&
160 " latitude_deg(i)=",latitude_deg(i)
161 ENDIF
162 ENDDO
163
164 ! read longitudes and make a sanity check (because already known from dyn)
165 1 CALL get_field("longitude",lon_startphy)
166
2/2
✓ Branch 0 taken 994 times.
✓ Branch 1 taken 1 times.
995 DO i=1,klon
167
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 994 times.
994 IF (ABS(lon_startphy(i)-longitude_deg(i))>=1) THEN
168 IF (ABS(360-ABS(lon_startphy(i)-longitude_deg(i)))>=1) THEN
169 WRITE(*,*) "phyetat0: Error! Longitude discrepancy wrt startphy file:",&
170 " i=",i," lon_startphy(i)=",lon_startphy(i),&
171 " longitude_deg(i)=",longitude_deg(i)
172 ! This is presumably serious enough to abort run
173 CALL abort_physic("phyetat0","discrepancy in longitudes!",1)
174 ENDIF
175 ENDIF
176
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 994 times.
995 IF (ABS(lon_startphy(i)-longitude_deg(i))>=1) THEN
177 IF (ABS(360-ABS(lon_startphy(i)-longitude_deg(i))) > 0.0001) THEN
178 WRITE(*,*) "phyetat0: Warning! Longitude discrepancy wrt startphy file:",&
179 " i=",i," lon_startphy(i)=",lon_startphy(i),&
180 " longitude_deg(i)=",longitude_deg(i)
181 ENDIF
182 ENDIF
183 ENDDO
184
185 ! Lecture du masque terre mer
186
187 1 CALL get_field("masque", zmasq, found)
188
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (.NOT. found) THEN
189 PRINT*, 'phyetat0: Le champ <masque> est absent'
190 PRINT *, 'fichier startphy non compatible avec phyetat0'
191 ENDIF
192
193 ! Lecture des fractions pour chaque sous-surface
194
195 ! initialisation des sous-surfaces
196
197
4/4
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 3976 times.
✓ Branch 3 taken 4 times.
3981 pctsrf = 0.
198
199 ! fraction de terre
200
201 1 CALL get_field("FTER", pctsrf(:, is_ter), found)
202
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FTER> est absent'
203
204 ! fraction de glace de terre
205
206 1 CALL get_field("FLIC", pctsrf(:, is_lic), found)
207
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FLIC> est absent'
208
209 ! fraction d'ocean
210
211 1 CALL get_field("FOCE", pctsrf(:, is_oce), found)
212
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FOCE> est absent'
213
214 ! fraction glace de mer
215
216 1 CALL get_field("FSIC", pctsrf(:, is_sic), found)
217
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (.NOT. found) PRINT*, 'phyetat0: Le champ <FSIC> est absent'
218
219 ! Verification de l'adequation entre le masque et les sous-surfaces
220
221 fractint( 1 : klon) = pctsrf(1 : klon, is_ter) &
222
2/2
✓ Branch 0 taken 994 times.
✓ Branch 1 taken 1 times.
995 + pctsrf(1 : klon, is_lic)
223
2/2
✓ Branch 0 taken 994 times.
✓ Branch 1 taken 1 times.
995 DO i = 1 , klon
224
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 994 times.
995 IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN
225 WRITE(*, *) 'phyetat0: attention fraction terre pas ', &
226 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
227 , pctsrf(i, is_lic)
228 WRITE(*, *) 'Je force la coherence zmasq=fractint'
229 zmasq(i) = fractint(i)
230 ENDIF
231 ENDDO
232 fractint (1 : klon) = pctsrf(1 : klon, is_oce) &
233
2/2
✓ Branch 0 taken 994 times.
✓ Branch 1 taken 1 times.
995 + pctsrf(1 : klon, is_sic)
234
2/2
✓ Branch 0 taken 994 times.
✓ Branch 1 taken 1 times.
995 DO i = 1 , klon
235
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 994 times.
995 IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN
236 WRITE(*, *) 'phyetat0 attention fraction ocean pas ', &
237 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
238 , pctsrf(i, is_sic)
239 WRITE(*, *) 'Je force la coherence zmasq=1.-fractint'
240 zmasq(i) = 1. - fractint(i)
241 ENDIF
242 ENDDO
243
244 !===================================================================
245 ! Lecture des temperatures du sol:
246 !===================================================================
247
248 1 found=phyetat0_get(1,ftsol(:,1),"TS","Surface temperature",283.)
249
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (found) THEN
250 DO nsrf=2,nbsrf
251 ftsol(:,nsrf)=ftsol(:,1)
252 ENDDO
253 ELSE
254 1 found=phyetat0_srf(1,ftsol,"TS","Surface temperature",283.)
255 ENDIF
256
257 !===================================================================
258 ! Lecture des albedo difus et direct
259 !===================================================================
260
261
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 1 times.
5 DO nsrf = 1, nbsrf
262
2/2
✓ Branch 0 taken 24 times.
✓ Branch 1 taken 4 times.
29 DO isw=1, nsw
263
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 24 times.
24 IF (isw.GT.99) THEN
264 PRINT*, "Trop de bandes SW"
265 call abort_physic("phyetat0", "", 1)
266 ENDIF
267 24 WRITE(str2, '(i2.2)') isw
268
1/2
✓ Branch 4 taken 24 times.
✗ Branch 5 not taken.
24 found=phyetat0_srf(1,falb_dir(:, isw,:),"A_dir_SW"//str2//"srf","Direct Albedo",0.2)
269
1/2
✓ Branch 4 taken 24 times.
✗ Branch 5 not taken.
28 found=phyetat0_srf(1,falb_dif(:, isw,:),"A_dif_SW"//str2//"srf","Direct Albedo",0.2)
270 ENDDO
271 ENDDO
272
273 1 found=phyetat0_srf(1,u10m,"U10M","u a 10m",0.)
274 1 found=phyetat0_srf(1,v10m,"V10M","v a 10m",0.)
275
276 !===================================================================
277 ! Lecture des temperatures du sol profond:
278 !===================================================================
279
280
2/2
✓ Branch 0 taken 11 times.
✓ Branch 1 taken 1 times.
12 DO isoil=1, nsoilmx
281 IF (isoil.GT.99) THEN
282 PRINT*, "Trop de couches "
283 call abort_physic("phyetat0", "", 1)
284 ENDIF
285 11 WRITE(str2,'(i2.2)') isoil
286
1/2
✓ Branch 4 taken 11 times.
✗ Branch 5 not taken.
11 found=phyetat0_srf(1,tsoil(:, isoil,:),"Tsoil"//str2//"srf","Temp soil",0.)
287
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 11 times.
12 IF (.NOT. found) THEN
288 PRINT*, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
289 PRINT*, " Il prend donc la valeur de surface"
290 tsoil(:, isoil, :)=ftsol(:, :)
291 ENDIF
292 ENDDO
293
294 !=======================================================================
295 ! Lecture precipitation/evaporation
296 !=======================================================================
297
298 1 found=phyetat0_srf(1,qsurf,"QS","Near surface hmidity",0.)
299 1 found=phyetat0_get(1,qsol,"QSOL","Surface hmidity / bucket",0.)
300 1 found=phyetat0_srf(1,snow,"SNOW","Surface snow",0.)
301 1 found=phyetat0_srf(1,fevap,"EVAP","evaporation",0.)
302 1 found=phyetat0_get(1,snow_fall,"snow_f","snow fall",0.)
303 1 found=phyetat0_get(1,rain_fall,"rain_f","rain fall",0.)
304
305 !=======================================================================
306 ! Radiation
307 !=======================================================================
308
309 1 found=phyetat0_get(1,solsw,"solsw","net SW radiation surf",0.)
310 1 found=phyetat0_get(1,solswfdiff,"solswfdiff","fraction of SW radiation surf that is diffuse",1.)
311 1 found=phyetat0_get(1,sollw,"sollw","net LW radiation surf",0.)
312 1 found=phyetat0_get(1,sollwdown,"sollwdown","down LW radiation surf",0.)
313
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (.NOT. found) THEN
314 sollwdown(:) = 0. ; zts(:)=0.
315 DO nsrf=1,nbsrf
316 zts(:)=zts(:)+ftsol(:,nsrf)*pctsrf(:,nsrf)
317 ENDDO
318 sollwdown(:)=sollw(:)+RSIGMA*zts(:)**4
319 ENDIF
320
321 1 found=phyetat0_get(1,radsol,"RADS","Solar radiation",0.)
322 1 found=phyetat0_get(1,fder,"fder","Flux derivative",0.)
323
324
325 ! Lecture de la longueur de rugosite
326 1 found=phyetat0_srf(1,z0m,"RUG","Z0m ancien",0.001)
327
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (found) THEN
328 z0h(:,1:nbsrf)=z0m(:,1:nbsrf)
329 ELSE
330 1 found=phyetat0_srf(1,z0m,"Z0m","Roughness length, momentum ",0.001)
331 1 found=phyetat0_srf(1,z0h,"Z0h","Roughness length, enthalpy ",0.001)
332 ENDIF
333 !FC
334
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF (ifl_pbltree>0) THEN
335 !CALL get_field("FTER", pctsrf(:, is_ter), found)
336 treedrg(:,1:klev,1:nbsrf)= 0.0
337 CALL get_field("treedrg_ter", drg_ter(:,:), found)
338 ! found=phyetat0_srf(1,treedrg,"treedrg","drag from vegetation" , 0.)
339 !lecture du profile de freinage des arbres
340 IF (.not. found ) THEN
341 treedrg(:,1:klev,1:nbsrf)= 0.0
342 ELSE
343 treedrg(:,1:klev,is_ter)= drg_ter(:,:)
344 ! found=phyetat0_srf(klev,treedrg,"treedrg","freinage arbres",0.)
345 ENDIF
346 ELSE
347 ! initialize treedrg(), because it will be written in restartphy.nc
348
6/6
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 156 times.
✓ Branch 3 taken 4 times.
✓ Branch 4 taken 155064 times.
✓ Branch 5 taken 156 times.
155225 treedrg(:,:,:) = 0.0
349 ENDIF
350
351 ! Lecture de l'age de la neige:
352 1 found=phyetat0_srf(1,agesno,"AGESNO","SNOW AGE",0.001)
353
354 1 ancien_ok=.true.
355
1/2
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
1 ancien_ok=ancien_ok.AND.phyetat0_get(klev,t_ancien,"TANCIEN","TANCIEN",0.)
356
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
1 ancien_ok=ancien_ok.AND.phyetat0_get(klev,q_ancien,"QANCIEN","QANCIEN",0.)
357
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 4 not taken.
1 ancien_ok=ancien_ok.AND.phyetat0_get(klev,ql_ancien,"QLANCIEN","QLANCIEN",0.)
358
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
1 ancien_ok=ancien_ok.AND.phyetat0_get(klev,qs_ancien,"QSANCIEN","QSANCIEN",0.)
359
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
1 ancien_ok=ancien_ok.AND.phyetat0_get(klev,u_ancien,"UANCIEN","UANCIEN",0.)
360
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
1 ancien_ok=ancien_ok.AND.phyetat0_get(klev,v_ancien,"VANCIEN","VANCIEN",0.)
361
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
1 ancien_ok=ancien_ok.AND.phyetat0_get(1,prw_ancien,"PRWANCIEN","PRWANCIEN",0.)
362
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
1 ancien_ok=ancien_ok.AND.phyetat0_get(1,prlw_ancien,"PRLWANCIEN","PRLWANCIEN",0.)
363
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
1 ancien_ok=ancien_ok.AND.phyetat0_get(1,prsw_ancien,"PRSWANCIEN","PRSWANCIEN",0.)
364
365 ! Ehouarn: addtional tests to check if t_ancien, q_ancien contain
366 ! dummy values (as is the case when generated by ce0l,
367 ! or by iniaqua)
368 IF ( (maxval(q_ancien).EQ.minval(q_ancien)) .OR. &
369 (maxval(ql_ancien).EQ.minval(ql_ancien)) .OR. &
370 (maxval(qs_ancien).EQ.minval(qs_ancien)) .OR. &
371 (maxval(prw_ancien).EQ.minval(prw_ancien)) .OR. &
372 (maxval(prlw_ancien).EQ.minval(prlw_ancien)) .OR. &
373
113/180
✓ Branch 0 taken 39 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 38766 times.
✓ Branch 3 taken 39 times.
✓ Branch 4 taken 38765 times.
✓ Branch 5 taken 1 times.
✓ Branch 6 taken 33 times.
✓ Branch 7 taken 38732 times.
✓ Branch 8 taken 1 times.
✗ Branch 9 not taken.
✗ Branch 10 not taken.
✓ Branch 11 taken 1 times.
✗ Branch 12 not taken.
✗ Branch 13 not taken.
✓ Branch 14 taken 39 times.
✓ Branch 15 taken 1 times.
✓ Branch 16 taken 38766 times.
✓ Branch 17 taken 39 times.
✓ Branch 18 taken 38765 times.
✓ Branch 19 taken 1 times.
✓ Branch 20 taken 108 times.
✓ Branch 21 taken 38657 times.
✓ Branch 22 taken 1 times.
✗ Branch 23 not taken.
✗ Branch 24 not taken.
✓ Branch 25 taken 1 times.
✗ Branch 26 not taken.
✗ Branch 27 not taken.
✓ Branch 28 taken 39 times.
✓ Branch 29 taken 1 times.
✓ Branch 30 taken 38766 times.
✓ Branch 31 taken 39 times.
✓ Branch 32 taken 38765 times.
✓ Branch 33 taken 1 times.
✗ Branch 34 not taken.
✓ Branch 35 taken 38765 times.
✓ Branch 36 taken 1 times.
✗ Branch 37 not taken.
✗ Branch 38 not taken.
✓ Branch 39 taken 1 times.
✗ Branch 40 not taken.
✗ Branch 41 not taken.
✓ Branch 42 taken 39 times.
✓ Branch 43 taken 1 times.
✓ Branch 44 taken 38766 times.
✓ Branch 45 taken 39 times.
✓ Branch 46 taken 38765 times.
✓ Branch 47 taken 1 times.
✗ Branch 48 not taken.
✓ Branch 49 taken 38765 times.
✓ Branch 50 taken 1 times.
✗ Branch 51 not taken.
✗ Branch 52 not taken.
✓ Branch 53 taken 1 times.
✗ Branch 54 not taken.
✗ Branch 55 not taken.
✓ Branch 56 taken 39 times.
✓ Branch 57 taken 1 times.
✓ Branch 58 taken 38766 times.
✓ Branch 59 taken 39 times.
✓ Branch 60 taken 38765 times.
✓ Branch 61 taken 1 times.
✗ Branch 62 not taken.
✓ Branch 63 taken 38765 times.
✓ Branch 64 taken 1 times.
✗ Branch 65 not taken.
✗ Branch 66 not taken.
✓ Branch 67 taken 1 times.
✗ Branch 68 not taken.
✗ Branch 69 not taken.
✓ Branch 70 taken 39 times.
✓ Branch 71 taken 1 times.
✓ Branch 72 taken 38766 times.
✓ Branch 73 taken 39 times.
✓ Branch 74 taken 38765 times.
✓ Branch 75 taken 1 times.
✗ Branch 76 not taken.
✓ Branch 77 taken 38765 times.
✓ Branch 78 taken 1 times.
✗ Branch 79 not taken.
✗ Branch 80 not taken.
✓ Branch 81 taken 1 times.
✗ Branch 82 not taken.
✗ Branch 83 not taken.
✓ Branch 84 taken 1 times.
✗ Branch 85 not taken.
✗ Branch 86 not taken.
✓ Branch 87 taken 1 times.
✗ Branch 88 not taken.
✗ Branch 89 not taken.
✓ Branch 90 taken 1 times.
✓ Branch 91 taken 994 times.
✓ Branch 92 taken 1 times.
✓ Branch 93 taken 993 times.
✓ Branch 94 taken 1 times.
✗ Branch 95 not taken.
✗ Branch 96 not taken.
✓ Branch 97 taken 1 times.
✗ Branch 98 not taken.
✗ Branch 99 not taken.
✓ Branch 100 taken 994 times.
✓ Branch 101 taken 1 times.
✓ Branch 102 taken 1 times.
✓ Branch 103 taken 993 times.
✓ Branch 104 taken 1 times.
✗ Branch 105 not taken.
✗ Branch 106 not taken.
✓ Branch 107 taken 1 times.
✗ Branch 108 not taken.
✗ Branch 109 not taken.
✓ Branch 110 taken 1 times.
✓ Branch 111 taken 994 times.
✓ Branch 112 taken 1 times.
✓ Branch 113 taken 993 times.
✓ Branch 114 taken 1 times.
✗ Branch 115 not taken.
✗ Branch 116 not taken.
✓ Branch 117 taken 1 times.
✗ Branch 118 not taken.
✗ Branch 119 not taken.
✓ Branch 120 taken 994 times.
✓ Branch 121 taken 1 times.
✓ Branch 122 taken 1 times.
✓ Branch 123 taken 993 times.
✓ Branch 124 taken 1 times.
✗ Branch 125 not taken.
✗ Branch 126 not taken.
✓ Branch 127 taken 1 times.
✗ Branch 128 not taken.
✗ Branch 129 not taken.
✓ Branch 130 taken 1 times.
✓ Branch 131 taken 994 times.
✓ Branch 132 taken 1 times.
✓ Branch 133 taken 993 times.
✓ Branch 134 taken 1 times.
✗ Branch 135 not taken.
✗ Branch 136 not taken.
✓ Branch 137 taken 1 times.
✗ Branch 138 not taken.
✗ Branch 139 not taken.
✓ Branch 140 taken 994 times.
✓ Branch 141 taken 1 times.
✓ Branch 142 taken 1 times.
✓ Branch 143 taken 993 times.
✓ Branch 144 taken 39 times.
✓ Branch 145 taken 1 times.
✓ Branch 146 taken 38766 times.
✓ Branch 147 taken 39 times.
✓ Branch 148 taken 38765 times.
✓ Branch 149 taken 1 times.
✓ Branch 150 taken 44 times.
✓ Branch 151 taken 38721 times.
✓ Branch 152 taken 1 times.
✗ Branch 153 not taken.
✗ Branch 154 not taken.
✓ Branch 155 taken 1 times.
✗ Branch 156 not taken.
✗ Branch 157 not taken.
✓ Branch 158 taken 39 times.
✓ Branch 159 taken 1 times.
✓ Branch 160 taken 38766 times.
✓ Branch 161 taken 39 times.
✓ Branch 162 taken 38765 times.
✓ Branch 163 taken 1 times.
✓ Branch 164 taken 73 times.
✓ Branch 165 taken 38692 times.
✓ Branch 166 taken 1 times.
✗ Branch 167 not taken.
✗ Branch 168 not taken.
✓ Branch 169 taken 1 times.
✗ Branch 170 not taken.
✗ Branch 171 not taken.
✗ Branch 172 not taken.
✓ Branch 173 taken 1 times.
✗ Branch 174 not taken.
✗ Branch 175 not taken.
✗ Branch 176 not taken.
✗ Branch 177 not taken.
✗ Branch 178 not taken.
✗ Branch 179 not taken.
316418 (maxval(prsw_ancien).EQ.minval(prsw_ancien)) .OR. &
374 (maxval(t_ancien).EQ.minval(t_ancien)) ) THEN
375 1 ancien_ok=.false.
376 ENDIF
377
378 1 found=phyetat0_get(klev,clwcon,"CLWCON","CLWCON",0.)
379 1 found=phyetat0_get(klev,rnebcon,"RNEBCON","RNEBCON",0.)
380 1 found=phyetat0_get(klev,ratqs,"RATQS","RATQS",0.)
381
382 1 found=phyetat0_get(1,run_off_lic_0,"RUNOFFLIC0","RUNOFFLIC0",0.)
383
384 !==================================
385 ! TKE
386 !==================================
387 !
388
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (iflag_pbl>1) then
389 1 found=phyetat0_srf(klev+1,pbl_tke,"TKE","Turb. Kinetic. Energ. ",1.e-8)
390 ENDIF
391
392
3/6
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
1 IF (iflag_pbl>1 .AND. iflag_wake>=1 .AND. iflag_pbl_split >=1 ) then
393 1 found=phyetat0_srf(klev+1,wake_delta_pbl_tke,"DELTATKE","Del TKE wk/env",0.)
394 !! found=phyetat0_srf(1,delta_tsurf,"DELTA_TSURF","Delta Ts wk/env ",0.)
395 1 found=phyetat0_srf(1,delta_tsurf,"DELTATS","Delta Ts wk/env ",0.)
396 !! found=phyetat0_srf(1,beta_aridity,"BETA_S","Aridity factor ",1.)
397 1 found=phyetat0_srf(1,beta_aridity,"BETAS","Aridity factor ",1.)
398 ENDIF !(iflag_pbl>1 .AND. iflag_wake>=1 .AND. iflag_pbl_split >=1 )
399
400 !==================================
401 ! thermiques, poches, convection
402 !==================================
403
404 ! Emanuel
405 1 found=phyetat0_get(klev,sig1,"sig1","sig1",0.)
406 1 found=phyetat0_get(klev,w01,"w01","w01",0.)
407
408 ! Wake
409 1 found=phyetat0_get(klev,wake_deltat,"WAKE_DELTAT","Delta T wake/env",0.)
410 1 found=phyetat0_get(klev,wake_deltaq,"WAKE_DELTAQ","Delta hum. wake/env",0.)
411 1 found=phyetat0_get(1,wake_s,"WAKE_S","Wake frac. area",0.)
412 !jyg<
413 ! Set wake_dens to -1000. when there is no restart so that the actual
414 ! initialization is made in calwake.
415 !! found=phyetat0_get(1,wake_dens,"WAKE_DENS","Wake num. /unit area",0.)
416 1 found=phyetat0_get(1,wake_dens,"WAKE_DENS","Wake num. /unit area",-1000.)
417 1 found=phyetat0_get(1,awake_dens,"AWAKE_DENS","Active Wake num. /unit area",0.)
418 1 found=phyetat0_get(1,cv_gen,"CV_GEN","CB birth rate",0.)
419 !>jyg
420 1 found=phyetat0_get(1,wake_cstar,"WAKE_CSTAR","WAKE_CSTAR",0.)
421 1 found=phyetat0_get(1,wake_pe,"WAKE_PE","WAKE_PE",0.)
422 1 found=phyetat0_get(1,wake_fip,"WAKE_FIP","WAKE_FIP",0.)
423
424 ! Thermiques
425 1 found=phyetat0_get(1,zmax0,"ZMAX0","ZMAX0",40.)
426 1 found=phyetat0_get(1,f0,"F0","F0",1.e-5)
427 1 found=phyetat0_get(klev+1,fm_therm,"FM_THERM","Thermals mass flux",0.)
428 1 found=phyetat0_get(klev,entr_therm,"ENTR_THERM","Thermals Entrain.",0.)
429 1 found=phyetat0_get(klev,detr_therm,"DETR_THERM","Thermals Detrain.",0.)
430
431 ! ALE/ALP
432 1 found=phyetat0_get(1,ale_bl,"ALE_BL","ALE BL",0.)
433 1 found=phyetat0_get(1,ale_bl_trig,"ALE_BL_TRIG","ALE BL_TRIG",0.)
434 1 found=phyetat0_get(1,alp_bl,"ALP_BL","ALP BL",0.)
435 1 found=phyetat0_get(1,ale_wake,"ALE_WAKE","ALE_WAKE",0.)
436 1 found=phyetat0_get(1,ale_bl_stat,"ALE_BL_STAT","ALE_BL_STAT",0.)
437
438 ! fisrtilp/Clouds 0.002 could be ratqsbas. But can stay like this as well
439 1 found=phyetat0_get(klev,ratqs_inter,"RATQS_INTER","Relative width of the lsc sugrid scale water",0.002)
440
441 !===========================================
442 ! Read and send field trs to traclmdz
443 !===========================================
444
445
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (type_trac == 'lmdz') THEN
446
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 DO it=1, nbtr
447 !! iiq=niadv(it+2) ! jyg
448 2 iiq=niadv(it+nqo) ! jyg
449 found=phyetat0_get(1,trs(:,it),"trs_"//tname(iiq), &
450 3 "Surf trac"//tname(iiq),0.)
451 ENDDO
452 1 CALL traclmdz_from_restart(trs)
453 ENDIF
454
455
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
1 IF (type_trac == 'co2i' .OR. type_trac == 'inco') THEN
456 IF (carbon_cycle_cpl) THEN
457 ALLOCATE(co2_send(klon), stat=ierr)
458 IF (ierr /= 0) CALL abort_physic('phyetat0', 'pb allocation co2_send', 1)
459 found=phyetat0_get(1,co2_send,"co2_send","co2 send",co2_ppm)
460 ENDIF
461 ENDIF
462
463 !===========================================
464 ! ondes de gravite / relief
465 !===========================================
466
467 ! ondes de gravite non orographiques
468
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 IF (ok_gwd_rando) found = &
469 1 phyetat0_get(klev,du_gwd_rando,"du_gwd_rando","du_gwd_rando",0.)
470
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
1 IF (.NOT. ok_hines .AND. ok_gwd_rando) found &
471 1 = phyetat0_get(klev,du_gwd_front,"du_gwd_front","du_gwd_front",0.)
472
473 ! prise en compte du relief sous-maille
474 1 found=phyetat0_get(1,zmea,"ZMEA","sub grid orography",0.)
475 1 found=phyetat0_get(1,zstd,"ZSTD","sub grid orography",0.)
476 1 found=phyetat0_get(1,zsig,"ZSIG","sub grid orography",0.)
477 1 found=phyetat0_get(1,zgam,"ZGAM","sub grid orography",0.)
478 1 found=phyetat0_get(1,zthe,"ZTHE","sub grid orography",0.)
479 1 found=phyetat0_get(1,zpic,"ZPIC","sub grid orography",0.)
480 1 found=phyetat0_get(1,zval,"ZVAL","sub grid orography",0.)
481 1 found=phyetat0_get(1,zmea,"ZMEA","sub grid orography",0.)
482 1 found=phyetat0_get(1,rugoro,"RUGSREL","sub grid orography",0.)
483
484 !===========================================
485 ! Initialize ocean
486 !===========================================
487
488
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF ( type_ocean == 'slab' ) THEN
489 CALL ocean_slab_init(phys_tstep, pctsrf)
490 IF (nslay.EQ.1) THEN
491 found=phyetat0_get(1,tslab,"tslab01","tslab",0.)
492 IF (.NOT. found) THEN
493 found=phyetat0_get(1,tslab,"tslab","tslab",0.)
494 ENDIF
495 ELSE
496 DO i=1,nslay
497 WRITE(str2,'(i2.2)') i
498 found=phyetat0_get(1,tslab(:,i),"tslab"//str2,"tslab",0.)
499 ENDDO
500 ENDIF
501 IF (.NOT. found) THEN
502 PRINT*, "phyetat0: Le champ <tslab> est absent"
503 PRINT*, "Initialisation a tsol_oce"
504 DO i=1,nslay
505 tslab(:,i)=MAX(ftsol(:,is_oce),271.35)
506 ENDDO
507 ENDIF
508
509 ! Sea ice variables
510 IF (version_ocean == 'sicINT') THEN
511 found=phyetat0_get(1,tice,"slab_tice","slab_tice",0.)
512 IF (.NOT. found) THEN
513 PRINT*, "phyetat0: Le champ <tice> est absent"
514 PRINT*, "Initialisation a tsol_sic"
515 tice(:)=ftsol(:,is_sic)
516 ENDIF
517 found=phyetat0_get(1,seaice,"seaice","seaice",0.)
518 IF (.NOT. found) THEN
519 PRINT*, "phyetat0: Le champ <seaice> est absent"
520 PRINT*, "Initialisation a 0/1m suivant fraction glace"
521 seaice(:)=0.
522 WHERE (pctsrf(:,is_sic).GT.EPSFRA)
523 seaice=917.
524 ENDWHERE
525 ENDIF
526 ENDIF !sea ice INT
527 ENDIF ! Slab
528
529
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if (activate_ocean_skin >= 1) then
530 if (activate_ocean_skin == 2 .and. type_ocean == 'couple') then
531 found = phyetat0_get(1, delta_sal, "delta_sal", &
532 "ocean-air interface salinity minus bulk salinity", 0.)
533 found = phyetat0_get(1, delta_sst, "delta_SST", &
534 "ocean-air interface temperature minus bulk SST", 0.)
535 end if
536
537 found = phyetat0_get(1, ds_ns, "dS_ns", "delta salinity near surface", 0.)
538 found = phyetat0_get(1, dt_ns, "dT_ns", "delta temperature near surface", &
539 0.)
540
541 where (pctsrf(:, is_oce) == 0.)
542 ds_ns = missing_val
543 dt_ns = missing_val
544 delta_sst = missing_val
545 delta_sal = missing_val
546 end where
547 end if
548
549 ! on ferme le fichier
550 1 CALL close_startphy
551
552 ! Initialize module pbl_surface_mod
553
554 1 CALL pbl_surface_init(fder, snow, qsurf, tsoil)
555
556 ! Initialize module ocean_cpl_mod for the case of coupled ocean
557
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 IF ( type_ocean == 'couple' ) THEN
558 CALL ocean_cpl_init(phys_tstep, longitude_deg, latitude_deg)
559 ENDIF
560
561 ! CALL init_iophy_new(latitude_deg, longitude_deg)
562
563 ! Initilialize module fonte_neige_mod
564 1 CALL fonte_neige_init(run_off_lic_0)
565
566 1 END SUBROUTINE phyetat0
567
568 !===================================================================
569 344 FUNCTION phyetat0_get(nlev,field,name,descr,default)
570 !===================================================================
571 ! Lecture d'un champ avec contrôle
572 ! Function logique dont le resultat indique si la lecture
573 ! s'est bien passée
574 ! On donne une valeur par defaut dans le cas contraire
575 !===================================================================
576
577 USE iostart, ONLY : get_field
578 USE dimphy, only: klon
579 USE print_control_mod, ONLY: lunout
580
581 IMPLICIT NONE
582
583 LOGICAL phyetat0_get
584
585 ! arguments
586 INTEGER,INTENT(IN) :: nlev
587 CHARACTER*(*),INTENT(IN) :: name,descr
588 REAL,INTENT(IN) :: default
589 REAL,DIMENSION(klon,nlev),INTENT(INOUT) :: field
590
591 ! Local variables
592 LOGICAL found
593
594 344 CALL get_field(name, field, found)
595
2/2
✓ Branch 0 taken 29 times.
✓ Branch 1 taken 315 times.
344 IF (.NOT. found) THEN
596 29 WRITE(lunout,*) "phyetat0: Le champ <",name,"> est absent"
597 29 WRITE(lunout,*) "Depart legerement fausse. Mais je continue"
598
4/4
✓ Branch 0 taken 105 times.
✓ Branch 1 taken 29 times.
✓ Branch 2 taken 104370 times.
✓ Branch 3 taken 105 times.
104504 field(:,:)=default
599 ENDIF
600
20/28
✓ Branch 3 taken 1265 times.
✓ Branch 4 taken 344 times.
✓ Branch 5 taken 1257410 times.
✓ Branch 6 taken 1265 times.
✓ Branch 7 taken 1257066 times.
✓ Branch 8 taken 344 times.
✓ Branch 9 taken 2089 times.
✓ Branch 10 taken 1254977 times.
✓ Branch 11 taken 344 times.
✗ Branch 12 not taken.
✗ Branch 13 not taken.
✓ Branch 14 taken 344 times.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✓ Branch 18 taken 1265 times.
✓ Branch 19 taken 344 times.
✓ Branch 20 taken 1257410 times.
✓ Branch 21 taken 1265 times.
✓ Branch 22 taken 1257066 times.
✓ Branch 23 taken 344 times.
✓ Branch 24 taken 4458 times.
✓ Branch 25 taken 1252608 times.
✓ Branch 26 taken 344 times.
✗ Branch 27 not taken.
✗ Branch 28 not taken.
✓ Branch 29 taken 344 times.
✗ Branch 30 not taken.
✗ Branch 31 not taken.
2518038 WRITE(lunout,*) name, descr, MINval(field),MAXval(field)
601 phyetat0_get=found
602
603 RETURN
604 END FUNCTION phyetat0_get
605
606 !================================================================
607 73 FUNCTION phyetat0_srf(nlev,field,name,descr,default)
608 !===================================================================
609 ! Lecture d'un champ par sous-surface avec contrôle
610 ! Function logique dont le resultat indique si la lecture
611 ! s'est bien passée
612 ! On donne une valeur par defaut dans le cas contraire
613 !===================================================================
614
615 USE iostart, ONLY : get_field
616 USE dimphy, only: klon
617 USE indice_sol_mod, only: nbsrf
618 USE print_control_mod, ONLY: lunout
619
620 IMPLICIT NONE
621
622 LOGICAL phyetat0_srf
623 ! arguments
624 INTEGER,INTENT(IN) :: nlev
625 CHARACTER*(*),INTENT(IN) :: name,descr
626 REAL,INTENT(IN) :: default
627 REAL,DIMENSION(klon,nlev,nbsrf),INTENT(INOUT) :: field
628
629 ! Local variables
630 LOGICAL found,phyetat0_get
631 INTEGER nsrf
632 CHARACTER*2 str2
633
634 IF (nbsrf.GT.99) THEN
635 WRITE(lunout,*) "Trop de sous-mailles"
636 call abort_physic("phyetat0", "", 1)
637 ENDIF
638
639
2/2
✓ Branch 0 taken 292 times.
✓ Branch 1 taken 73 times.
365 DO nsrf = 1, nbsrf
640 292 WRITE(str2, '(i2.2)') nsrf
641 found= phyetat0_get(nlev,field(:,:, nsrf), &
642 365 name//str2,descr//" srf:"//str2,default)
643 ENDDO
644
645 phyetat0_srf=found
646
647 RETURN
648 END FUNCTION phyetat0_srf
649
650