1 | SUBROUTINE phyredem (fichnom) |
---|
2 | ! |
---|
3 | !------------------------------------------------------------------------------- |
---|
4 | ! Author: Z.X. Li (LMD/CNRS), 1993/08/18 |
---|
5 | !------------------------------------------------------------------------------- |
---|
6 | ! Purpose: Write restart state for physics. |
---|
7 | !------------------------------------------------------------------------------- |
---|
8 | USE dimphy, ONLY: klon, klev |
---|
9 | USE fonte_neige_mod, ONLY : fonte_neige_final |
---|
10 | USE pbl_surface_mod, ONLY : pbl_surface_final |
---|
11 | USE phys_state_var_mod, ONLY: radpas, zmasq, pctsrf, ftsol, falb_dir, & |
---|
12 | falb_dif, qsol, fevap, radsol, solsw, sollw, & |
---|
13 | sollwdown, rain_fall, snow_fall, z0m, z0h, & |
---|
14 | agesno, zmea, zstd, zsig, zgam, zthe, zpic, & |
---|
15 | zval, rugoro, t_ancien, q_ancien, & |
---|
16 | prw_ancien, prlw_ancien, prsw_ancien, & |
---|
17 | ql_ancien, qs_ancien, u_ancien, & |
---|
18 | v_ancien, clwcon, rnebcon, ratqs, pbl_tke, & |
---|
19 | wake_delta_pbl_tke, zmax0, f0, sig1, w01, & |
---|
20 | wake_deltat, wake_deltaq, wake_s, wake_cstar,& |
---|
21 | wake_pe, wake_fip, fm_therm, entr_therm, & |
---|
22 | detr_therm, Ale_bl, Ale_bl_trig, Alp_bl, & |
---|
23 | #ifdef ISO |
---|
24 | xtsol, fxtevap,xtrain_fall, xtsnow_fall, & |
---|
25 | xt_ancien, xtl_ancien, xts_ancien, & |
---|
26 | wake_deltaxt, & |
---|
27 | #endif |
---|
28 | du_gwd_rando, du_gwd_front, u10m, v10m |
---|
29 | USE geometry_mod, ONLY : longitude_deg, latitude_deg |
---|
30 | USE iostart, ONLY: open_restartphy, close_restartphy, put_field, put_var |
---|
31 | USE traclmdz_mod, ONLY : traclmdz_to_restart |
---|
32 | USE infotrac_phy, ONLY: type_trac, niadv, tname, nbtr, nqo |
---|
33 | #ifdef ISO |
---|
34 | USE infotrac_phy, ONLY: itr_indice,niso,ntraciso |
---|
35 | #ifdef ISOVERIF |
---|
36 | USE isotopes_verif_mod |
---|
37 | #endif |
---|
38 | #endif |
---|
39 | USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send |
---|
40 | USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic, epsfra |
---|
41 | USE surface_data, ONLY: type_ocean, version_ocean |
---|
42 | USE ocean_slab_mod, ONLY : tslab, seaice, tice, fsic |
---|
43 | USE time_phylmdz_mod, ONLY: annee_ref, day_end, itau_phy, pdtphys |
---|
44 | |
---|
45 | IMPLICIT none |
---|
46 | |
---|
47 | include "dimsoil.h" |
---|
48 | include "clesphys.h" |
---|
49 | include "thermcell.h" |
---|
50 | include "compbl.h" |
---|
51 | !====================================================================== |
---|
52 | CHARACTER*(*) fichnom |
---|
53 | |
---|
54 | ! les variables globales ecrites dans le fichier restart |
---|
55 | |
---|
56 | REAL tsoil(klon, nsoilmx, nbsrf) |
---|
57 | REAL qsurf(klon, nbsrf) |
---|
58 | REAL snow(klon, nbsrf) |
---|
59 | real fder(klon) |
---|
60 | REAL run_off_lic_0(klon) |
---|
61 | REAL trs(klon, nbtr) |
---|
62 | #ifdef ISO |
---|
63 | REAL xtsnow(niso,klon, nbsrf) |
---|
64 | REAL xtrun_off_lic_0(niso,klon) |
---|
65 | REAL Rland_ice(niso,klon) |
---|
66 | INTEGER iq |
---|
67 | #endif |
---|
68 | |
---|
69 | INTEGER nid, nvarid, idim1, idim2, idim3 |
---|
70 | INTEGER ierr |
---|
71 | INTEGER length |
---|
72 | PARAMETER (length=100) |
---|
73 | REAL tab_cntrl(length) |
---|
74 | |
---|
75 | INTEGER isoil, nsrf,isw |
---|
76 | CHARACTER (len=7) :: str7 |
---|
77 | CHARACTER (len=256) :: nam, lnam |
---|
78 | INTEGER :: it, iiq |
---|
79 | |
---|
80 | !====================================================================== |
---|
81 | |
---|
82 | ! Get variables which will be written to restart file from module |
---|
83 | ! pbl_surface_mod |
---|
84 | CALL pbl_surface_final(fder, snow, qsurf, tsoil & |
---|
85 | #ifdef ISO |
---|
86 | ,xtsnow,Rland_ice & |
---|
87 | #endif |
---|
88 | ) |
---|
89 | |
---|
90 | ! Get a variable calculated in module fonte_neige_mod |
---|
91 | CALL fonte_neige_final(run_off_lic_0 & |
---|
92 | #ifdef ISO |
---|
93 | ,xtrun_off_lic_0 & |
---|
94 | #endif |
---|
95 | ) |
---|
96 | |
---|
97 | !====================================================================== |
---|
98 | |
---|
99 | CALL open_restartphy(fichnom) |
---|
100 | |
---|
101 | DO ierr = 1, length |
---|
102 | tab_cntrl(ierr) = 0.0 |
---|
103 | ENDDO |
---|
104 | tab_cntrl(1) = pdtphys |
---|
105 | tab_cntrl(2) = radpas |
---|
106 | ! co2_ppm : current value of atmospheric CO2 |
---|
107 | tab_cntrl(3) = co2_ppm |
---|
108 | tab_cntrl(4) = solaire |
---|
109 | tab_cntrl(5) = iflag_con |
---|
110 | tab_cntrl(6) = nbapp_rad |
---|
111 | |
---|
112 | IF( cycle_diurne ) tab_cntrl( 7 ) = 1. |
---|
113 | IF( soil_model ) tab_cntrl( 8 ) = 1. |
---|
114 | IF( new_oliq ) tab_cntrl( 9 ) = 1. |
---|
115 | IF( ok_orodr ) tab_cntrl(10 ) = 1. |
---|
116 | IF( ok_orolf ) tab_cntrl(11 ) = 1. |
---|
117 | |
---|
118 | tab_cntrl(13) = day_end |
---|
119 | tab_cntrl(14) = annee_ref |
---|
120 | tab_cntrl(15) = itau_phy |
---|
121 | |
---|
122 | ! co2_ppm0 : initial value of atmospheric CO2 |
---|
123 | tab_cntrl(16) = co2_ppm0 |
---|
124 | |
---|
125 | CALL put_var("controle", "Parametres de controle", tab_cntrl) |
---|
126 | |
---|
127 | CALL put_field("longitude", & |
---|
128 | "Longitudes de la grille physique", longitude_deg) |
---|
129 | |
---|
130 | CALL put_field("latitude", "Latitudes de la grille physique", latitude_deg) |
---|
131 | |
---|
132 | ! PB ajout du masque terre/mer |
---|
133 | |
---|
134 | CALL put_field("masque", "masque terre mer", zmasq) |
---|
135 | |
---|
136 | ! BP ajout des fraction de chaque sous-surface |
---|
137 | |
---|
138 | ! Get last fractions from slab ocean |
---|
139 | IF (type_ocean == 'slab' .AND. version_ocean == "sicINT") THEN |
---|
140 | WHERE (1.-zmasq(:).GT.EPSFRA) |
---|
141 | pctsrf(:,is_oce)=(1.-fsic(:))*(1.-zmasq(:)) |
---|
142 | pctsrf(:,is_sic)=fsic(:)*(1.-zmasq(:)) |
---|
143 | END WHERE |
---|
144 | END IF |
---|
145 | |
---|
146 | ! 1. fraction de terre |
---|
147 | |
---|
148 | CALL put_field("FTER", "fraction de continent", pctsrf(:, is_ter)) |
---|
149 | |
---|
150 | ! 2. Fraction de glace de terre |
---|
151 | |
---|
152 | CALL put_field("FLIC", "fraction glace de terre", pctsrf(:, is_lic)) |
---|
153 | |
---|
154 | ! 3. fraction ocean |
---|
155 | |
---|
156 | CALL put_field("FOCE", "fraction ocean", pctsrf(:, is_oce)) |
---|
157 | |
---|
158 | ! 4. Fraction glace de mer |
---|
159 | |
---|
160 | CALL put_field("FSIC", "fraction glace mer", pctsrf(:, is_sic)) |
---|
161 | |
---|
162 | IF(nbsrf>99) THEN |
---|
163 | PRINT*, "Trop de sous-mailles"; CALL abort_physic("phyredem", "", 1) |
---|
164 | END IF |
---|
165 | IF(nsoilmx>99) THEN |
---|
166 | PRINT*, "Trop de sous-surfaces"; CALL abort_physic("phyredem", "", 1) |
---|
167 | END IF |
---|
168 | IF(nsw>99) THEN |
---|
169 | PRINT*, "Trop de bandes"; CALL abort_physic("phyredem", "", 1) |
---|
170 | END IF |
---|
171 | |
---|
172 | CALL put_field_srf1("TS","Temperature",ftsol(:,:)) |
---|
173 | |
---|
174 | ! ================== Albedo ======================================= |
---|
175 | print*,'PHYREDEM NOUVEAU' |
---|
176 | CALL put_field_srf2("A_dir_SW","Albedo direct",falb_dir(:,:,:)) |
---|
177 | CALL put_field_srf2("A_dif_SW","Albedo diffus",falb_dif(:,:,:)) |
---|
178 | |
---|
179 | CALL put_field_srf1("U10M", "u a 10m", u10m) |
---|
180 | |
---|
181 | CALL put_field_srf1("V10M", "v a 10m", v10m) |
---|
182 | |
---|
183 | |
---|
184 | ! ================== Tsoil ========================================= |
---|
185 | CALL put_field_srf2("Tsoil","Temperature",tsoil(:,:,:)) |
---|
186 | |
---|
187 | CALL put_field_srf1("QS" , "Humidite",qsurf(:,:)) |
---|
188 | |
---|
189 | CALL put_field ("QSOL", "Eau dans le sol (mm)", qsol) |
---|
190 | |
---|
191 | CALL put_field_srf1("EVAP", "Evaporation", fevap(:,:)) |
---|
192 | |
---|
193 | CALL put_field_srf1("SNOW", "Neige", snow(:,:)) |
---|
194 | |
---|
195 | CALL put_field("RADS", "Rayonnement net a la surface", radsol) |
---|
196 | |
---|
197 | CALL put_field("solsw", "Rayonnement solaire a la surface", solsw) |
---|
198 | |
---|
199 | CALL put_field("sollw", "Rayonnement IF a la surface", sollw) |
---|
200 | |
---|
201 | CALL put_field("sollwdown", "Rayonnement down IF a la surface", sollwdown) |
---|
202 | |
---|
203 | CALL put_field("fder", "Derive de flux", fder) |
---|
204 | |
---|
205 | CALL put_field("rain_f", "precipitation liquide", rain_fall) |
---|
206 | |
---|
207 | CALL put_field("snow_f", "precipitation solide", snow_fall) |
---|
208 | |
---|
209 | CALL put_field_srf1("Z0m", "rugosite", z0m(:,:)) |
---|
210 | |
---|
211 | CALL put_field_srf1("Z0h", "rugosite", z0h(:,:)) |
---|
212 | |
---|
213 | CALL put_field_srf1("AGESNO", "Age de la neige", agesno(:,:)) |
---|
214 | |
---|
215 | CALL put_field("ZMEA", "ZMEA", zmea) |
---|
216 | |
---|
217 | CALL put_field("ZSTD", "ZSTD", zstd) |
---|
218 | |
---|
219 | CALL put_field("ZSIG", "ZSIG", zsig) |
---|
220 | |
---|
221 | CALL put_field("ZGAM", "ZGAM", zgam) |
---|
222 | |
---|
223 | CALL put_field("ZTHE", "ZTHE", zthe) |
---|
224 | |
---|
225 | CALL put_field("ZPIC", "ZPIC", zpic) |
---|
226 | |
---|
227 | CALL put_field("ZVAL", "ZVAL", zval) |
---|
228 | |
---|
229 | CALL put_field("RUGSREL", "RUGSREL", rugoro) |
---|
230 | |
---|
231 | CALL put_field("TANCIEN", "TANCIEN", t_ancien) |
---|
232 | |
---|
233 | CALL put_field("QANCIEN", "QANCIEN", q_ancien) |
---|
234 | |
---|
235 | CALL put_field("QLANCIEN", "QLANCIEN", ql_ancien) |
---|
236 | |
---|
237 | CALL put_field("QSANCIEN", "QSANCIEN", qs_ancien) |
---|
238 | |
---|
239 | CALL put_field("PRWANCIEN", "PRWANCIEN", prw_ancien) |
---|
240 | |
---|
241 | CALL put_field("PRLWANCIEN", "PRLWANCIEN", prlw_ancien) |
---|
242 | |
---|
243 | CALL put_field("PRSWANCIEN", "PRSWANCIEN", prsw_ancien) |
---|
244 | |
---|
245 | CALL put_field("UANCIEN", "UANCIEN", u_ancien) |
---|
246 | |
---|
247 | CALL put_field("VANCIEN", "VANCIEN", v_ancien) |
---|
248 | |
---|
249 | CALL put_field("CLWCON", "Eau liquide convective", clwcon) |
---|
250 | |
---|
251 | CALL put_field("RNEBCON", "Nebulosite convective", rnebcon) |
---|
252 | |
---|
253 | CALL put_field("RATQS", "Ratqs", ratqs) |
---|
254 | |
---|
255 | ! run_off_lic_0 |
---|
256 | |
---|
257 | CALL put_field("RUNOFFLIC0", "Runofflic0", run_off_lic_0) |
---|
258 | |
---|
259 | ! DEB TKE PBL ! |
---|
260 | |
---|
261 | IF (iflag_pbl>1) then |
---|
262 | CALL put_field_srf3("TKE", "Energ. Cineti. Turb.", & |
---|
263 | pbl_tke(:,:,:)) |
---|
264 | CALL put_field_srf3("DELTATKE", "Del TKE wk/env.", & |
---|
265 | wake_delta_pbl_tke(:,:,:)) |
---|
266 | END IF |
---|
267 | |
---|
268 | ! FIN TKE PBL ! |
---|
269 | !IM ajout zmax0, f0, sig1, w01 |
---|
270 | !IM wake_deltat, wake_deltaq, wake_s, wake_cstar, wake_pe, wake_fip |
---|
271 | |
---|
272 | CALL put_field("ZMAX0", "ZMAX0", zmax0) |
---|
273 | |
---|
274 | CALL put_field("F0", "F0", f0) |
---|
275 | |
---|
276 | CALL put_field("sig1", "sig1 Emanuel", sig1) |
---|
277 | |
---|
278 | CALL put_field("w01", "w01 Emanuel", w01) |
---|
279 | |
---|
280 | ! wake_deltat |
---|
281 | CALL put_field("WAKE_DELTAT", "WAKE_DELTAT", wake_deltat) |
---|
282 | |
---|
283 | CALL put_field("WAKE_DELTAQ", "WAKE_DELTAQ", wake_deltaq) |
---|
284 | |
---|
285 | CALL put_field("WAKE_S", "WAKE_S", wake_s) |
---|
286 | |
---|
287 | CALL put_field("WAKE_CSTAR", "WAKE_CSTAR", wake_cstar) |
---|
288 | |
---|
289 | CALL put_field("WAKE_PE", "WAKE_PE", wake_pe) |
---|
290 | |
---|
291 | CALL put_field("WAKE_FIP", "WAKE_FIP", wake_fip) |
---|
292 | |
---|
293 | ! thermiques |
---|
294 | |
---|
295 | CALL put_field("FM_THERM", "FM_THERM", fm_therm) |
---|
296 | |
---|
297 | CALL put_field("ENTR_THERM", "ENTR_THERM", entr_therm) |
---|
298 | |
---|
299 | CALL put_field("DETR_THERM", "DETR_THERM", detr_therm) |
---|
300 | |
---|
301 | CALL put_field("ALE_BL", "ALE_BL", Ale_bl) |
---|
302 | |
---|
303 | CALL put_field("ALE_BL_TRIG", "ALE_BL_TRIG", Ale_bl_trig) |
---|
304 | |
---|
305 | CALL put_field("ALP_BL", "ALP_BL", Alp_bl) |
---|
306 | |
---|
307 | ! trs from traclmdz_mod |
---|
308 | IF (type_trac == 'lmdz') THEN |
---|
309 | CALL traclmdz_to_restart(trs) |
---|
310 | #ifdef ISO |
---|
311 | DO it=1, nbtr |
---|
312 | iq=itr_indice(it) ! jyg |
---|
313 | iiq=niadv(iq) ! jyg |
---|
314 | CALL put_field("trs_"//tname(iiq), "", trs(:, it)) |
---|
315 | END DO |
---|
316 | #else |
---|
317 | DO it=1, nbtr |
---|
318 | !! iiq=niadv(it+2) ! jyg |
---|
319 | iiq=niadv(it+nqo) ! jyg |
---|
320 | CALL put_field("trs_"//tname(iiq), "", trs(:, it)) |
---|
321 | END DO |
---|
322 | #endif |
---|
323 | IF (carbon_cycle_cpl) THEN |
---|
324 | IF (.NOT. ALLOCATED(co2_send)) THEN |
---|
325 | ! This is the case of create_etat0_limit, ce0l |
---|
326 | ALLOCATE(co2_send(klon)) |
---|
327 | co2_send(:) = co2_ppm0 |
---|
328 | END IF |
---|
329 | CALL put_field("co2_send", "co2_ppm for coupling", co2_send) |
---|
330 | END IF |
---|
331 | END IF |
---|
332 | |
---|
333 | ! Restart variables for Slab ocean |
---|
334 | IF (type_ocean == 'slab') THEN |
---|
335 | CALL put_field("tslab", "Slab ocean temperature", tslab) |
---|
336 | IF (version_ocean == 'sicINT') THEN |
---|
337 | CALL put_field("seaice", "Slab seaice (kg/m2)", seaice) |
---|
338 | CALL put_field("slab_tice", "Slab sea ice temperature", tice) |
---|
339 | END IF |
---|
340 | END IF |
---|
341 | |
---|
342 | if (ok_gwd_rando) call put_field("du_gwd_rando", & |
---|
343 | "tendency on zonal wind due to flott gravity waves", du_gwd_rando) |
---|
344 | |
---|
345 | IF (.not. ok_hines .and. ok_gwd_rando) call put_field("du_gwd_front", & |
---|
346 | "tendency on zonal wind due to acama gravity waves", du_gwd_front) |
---|
347 | |
---|
348 | #ifdef ISO |
---|
349 | write(*,*) 'phyredem 342' |
---|
350 | call phyisoredem ( & |
---|
351 | & xtsnow, & |
---|
352 | & xtrun_off_lic_0,Rland_ice, & |
---|
353 | & run_off_lic_0) |
---|
354 | #endif |
---|
355 | |
---|
356 | CALL close_restartphy |
---|
357 | !$OMP BARRIER |
---|
358 | |
---|
359 | |
---|
360 | CONTAINS |
---|
361 | |
---|
362 | |
---|
363 | SUBROUTINE put_field_srf1(nam,lnam,field) |
---|
364 | |
---|
365 | IMPLICIT NONE |
---|
366 | CHARACTER(LEN=*), INTENT(IN) :: nam, lnam |
---|
367 | REAL, INTENT(IN) :: field(:,:) |
---|
368 | CHARACTER(LEN=256) :: nm, lm, str |
---|
369 | DO nsrf = 1, SIZE(field,2) |
---|
370 | WRITE(str, '(i2.2)') nsrf |
---|
371 | nm=TRIM(nam)//TRIM(str) |
---|
372 | lm=TRIM(lnam)//" de surface No. "//TRIM(str) |
---|
373 | CALL put_field(nm,lm,field(:,nsrf)) |
---|
374 | END DO |
---|
375 | |
---|
376 | END SUBROUTINE put_field_srf1 |
---|
377 | |
---|
378 | |
---|
379 | SUBROUTINE put_field_srf2(nam,lnam,field) |
---|
380 | |
---|
381 | IMPLICIT NONE |
---|
382 | CHARACTER(LEN=*), INTENT(IN) :: nam, lnam |
---|
383 | REAL, INTENT(IN) :: field(:,:,:) |
---|
384 | CHARACTER(LEN=256) :: nm, lm, str |
---|
385 | DO nsrf = 1, SIZE(field,3) |
---|
386 | DO isoil=1, SIZE(field,2) |
---|
387 | WRITE(str, '(i2.2,"srf",i2.2)')isoil,nsrf |
---|
388 | ! WRITE(lunout,*)"PHYREDEM ",TRIM(nam)//TRIM(str) |
---|
389 | nm=TRIM(nam)//TRIM(str) |
---|
390 | lm=TRIM(lnam)//" du sol No. "//TRIM(str) |
---|
391 | CALL put_field(nm,lm,field(:,isoil,nsrf)) |
---|
392 | END DO |
---|
393 | END DO |
---|
394 | |
---|
395 | END SUBROUTINE put_field_srf2 |
---|
396 | |
---|
397 | |
---|
398 | SUBROUTINE put_field_srf3(nam,lnam,field) |
---|
399 | |
---|
400 | IMPLICIT NONE |
---|
401 | CHARACTER(LEN=*), INTENT(IN) :: nam, lnam |
---|
402 | REAL, INTENT(IN) :: field(:,:,:) |
---|
403 | CHARACTER(LEN=256) :: nm, lm, str |
---|
404 | DO nsrf = 1, SIZE(field,3) |
---|
405 | WRITE(str, '(i2.2)') nsrf |
---|
406 | nm=TRIM(nam)//TRIM(str) |
---|
407 | lm=TRIM(lnam)//TRIM(str) |
---|
408 | CALL put_field(nm,lm,field(:,1:klev+1,nsrf)) |
---|
409 | END DO |
---|
410 | |
---|
411 | END SUBROUTINE put_field_srf3 |
---|
412 | |
---|
413 | #ifdef ISO |
---|
414 | ! je voulais mettre cette subroutine dans isotopes_mod, mais elle a besoin de put_field_srf1 qui est contenue dans la subroutine phyredem. Si on veut mettre cette routine dans isotopes_mod, il faudrait convertir ce fichier en module pour pouvoir en appeler des routines |
---|
415 | |
---|
416 | SUBROUTINE phyisoredem ( & |
---|
417 | & xtsnow, & |
---|
418 | & xtrun_off_lic_0,Rland_ice, & |
---|
419 | & run_off_lic_0) |
---|
420 | USE dimphy |
---|
421 | !USE mod_grid_phy_lmdz |
---|
422 | !USE mod_phys_lmdz_para |
---|
423 | USE phys_state_var_mod, ONLY: q_ancien,xt_ancien,wake_deltaq,wake_deltaxt, & |
---|
424 | xtrain_fall,xtsnow_fall, ql_ancien,xtl_ancien,qs_ancien,xts_ancien, & |
---|
425 | xtsol,fxtevap |
---|
426 | USE infotrac_phy,ONLY: niso, ntraciso |
---|
427 | !USE control_mod |
---|
428 | USE indice_sol_mod, ONLY: nbsrf |
---|
429 | USE iostart, ONLY: put_field |
---|
430 | USE isotopes_mod, ONLY: striso,iso_eau |
---|
431 | #ifdef ISOVERIF |
---|
432 | !USE infotrac_phy, ONLY: use_iso |
---|
433 | USE isotopes_verif_mod |
---|
434 | #endif |
---|
435 | #ifdef ISOTRAC |
---|
436 | use isotrac_mod, only: index_zone,index_iso,strtrac |
---|
437 | #endif |
---|
438 | !USE phyredem, ONLY: put_field_srf1 |
---|
439 | |
---|
440 | implicit none |
---|
441 | |
---|
442 | ! equivalent isotopique de phyredem |
---|
443 | |
---|
444 | #include "dimsoil.h" |
---|
445 | #include "clesphys.h" |
---|
446 | #include "thermcell.h" |
---|
447 | #include "compbl.h" |
---|
448 | ! inputs |
---|
449 | !REAL xtsol(niso,klon) |
---|
450 | REAL xtsnow(niso,klon,nbsrf) |
---|
451 | !REAL xtevap(ntraciso,klon,nbsrf) |
---|
452 | REAL xtrun_off_lic_0(niso,klon) |
---|
453 | REAL Rland_ice(niso,klon) |
---|
454 | real run_off_lic_0(klon) |
---|
455 | |
---|
456 | ! locals |
---|
457 | real iso_tmp(klon) |
---|
458 | real iso_tmp_lonlev(klon,klev) |
---|
459 | real iso_tmp_lonsrf(klon,nbsrf) |
---|
460 | integer i,ixt,k,nsrf |
---|
461 | INTEGER nid, nvarid |
---|
462 | INTEGER ierr |
---|
463 | CHARACTER*7 str7 |
---|
464 | CHARACTER*2 str2 |
---|
465 | CHARACTER*50 striso_sortie |
---|
466 | integer lnblnk |
---|
467 | #ifdef ISOTRAC |
---|
468 | integer iiso,izone |
---|
469 | #endif |
---|
470 | #ifdef ISOVERIF |
---|
471 | integer iso_verif_egalite_nostop |
---|
472 | #endif |
---|
473 | |
---|
474 | write(*,*) 'phyisoredem 41: entrée' |
---|
475 | #ifdef ISOVERIF |
---|
476 | if (iso_eau.gt.0) then |
---|
477 | do k=1,klev |
---|
478 | do i=1,klon |
---|
479 | call iso_verif_egalite(xt_ancien(iso_eau,i,k),q_ancien(i,k), & |
---|
480 | & 'phyisoredem 50a') |
---|
481 | call iso_verif_egalite(xtl_ancien(iso_eau,i,k),ql_ancien(i,k), & |
---|
482 | & 'phyisoredem 50b') |
---|
483 | call iso_verif_egalite(xts_ancien(iso_eau,i,k),qs_ancien(i,k), & |
---|
484 | & 'phyisoredem 50c') |
---|
485 | |
---|
486 | enddo !do i=1,klon |
---|
487 | enddo !do k=1,klev |
---|
488 | do i=1,klon |
---|
489 | DO nsrf = 1, nbsrf |
---|
490 | call iso_verif_egalite(fxtevap(iso_eau,i,nsrf),fevap(i,nsrf), & |
---|
491 | & 'phyisoredem 50d') |
---|
492 | enddo !DO nsrf = 1, nbsrf |
---|
493 | enddo |
---|
494 | endif !if (iso_eau.gt.0) then |
---|
495 | #ifdef ISOTRAC |
---|
496 | do k=1,klev |
---|
497 | do i=1,klon |
---|
498 | call iso_verif_traceur(xt_ancien(1,i,k), & |
---|
499 | & 'phyisoredem 60') |
---|
500 | enddo !do i=1,klon |
---|
501 | enddo !do k=1,kle |
---|
502 | #endif |
---|
503 | #endif |
---|
504 | #ifdef ISOVERIF |
---|
505 | do i=1,klon |
---|
506 | do ixt=1,niso |
---|
507 | call iso_verif_noNaN(xtsol(ixt,i),'phyisoredem 72') |
---|
508 | enddo !do ixt=1,niso |
---|
509 | enddo !do i=1,klon |
---|
510 | #endif |
---|
511 | |
---|
512 | do ixt=1,niso |
---|
513 | |
---|
514 | do i=1,klon |
---|
515 | iso_tmp(i)=xtsol(ixt,i) |
---|
516 | enddo !do i=1,klon |
---|
517 | CALL put_field("XTSOL"//striso(ixt), & |
---|
518 | & "Eau dans le sol (mm)",iso_tmp) |
---|
519 | |
---|
520 | DO nsrf = 1, nbsrf |
---|
521 | do i=1,klon |
---|
522 | iso_tmp_lonsrf(i,nsrf)=fxtevap(ixt,i,nsrf) |
---|
523 | enddo !do i=1,klon |
---|
524 | enddo ! DO nsrf = 1, nbsrf |
---|
525 | #ifdef ISOVERIF |
---|
526 | if (iso_eau.gt.0) then |
---|
527 | write(*,*) 'phyredem tmp 502: fxtevap(iso_eau,1,:)=', & |
---|
528 | fxtevap(iso_eau,1,:) |
---|
529 | endif |
---|
530 | #endif |
---|
531 | striso_sortie="XTEVAP"//striso(ixt) |
---|
532 | CALL put_field_srf1(striso_sortie(1:lnblnk(striso_sortie)), & |
---|
533 | & "Evaporation de surface",iso_tmp_lonsrf) |
---|
534 | |
---|
535 | DO nsrf = 1, nbsrf |
---|
536 | do i=1,klon |
---|
537 | iso_tmp_lonsrf(i,nsrf)=xtsnow(ixt,i,nsrf) |
---|
538 | enddo !do i=1,klon |
---|
539 | enddo !DO nsrf = 1, nbsrf |
---|
540 | striso_sortie="XTSNOW"//striso(ixt) |
---|
541 | CALL put_field_srf1(striso_sortie(1:lnblnk(striso_sortie)), & |
---|
542 | & "NEIGE",iso_tmp_lonsrf) |
---|
543 | |
---|
544 | do i=1,klon |
---|
545 | iso_tmp(i)=xtrain_fall(ixt,i) |
---|
546 | enddo !do i=1,klon |
---|
547 | write(*,*) 'phyisoredem 515: on ecrit xtrain_f'//striso(ixt) |
---|
548 | CALL put_field("xtrain_f"//striso(ixt), & |
---|
549 | & "precipitation liquide",iso_tmp) |
---|
550 | |
---|
551 | do i=1,klon |
---|
552 | iso_tmp(i)=xtsnow_fall(ixt,i) |
---|
553 | enddo !do i=1,klon |
---|
554 | CALL put_field("xtsnow_f"//striso(ixt), & |
---|
555 | & "precipitation solide",iso_tmp) |
---|
556 | |
---|
557 | do k=1,klev |
---|
558 | do i=1,klon |
---|
559 | iso_tmp_lonlev(i,k)=xt_ancien(ixt,i,k) |
---|
560 | enddo !do i=1,klon |
---|
561 | enddo |
---|
562 | CALL put_field("XTANCIEN"//striso(ixt), & |
---|
563 | & "XTANCIEN",iso_tmp_lonlev) |
---|
564 | |
---|
565 | do k=1,klev |
---|
566 | do i=1,klon |
---|
567 | iso_tmp_lonlev(i,k)=xtl_ancien(ixt,i,k) |
---|
568 | enddo !do i=1,klon |
---|
569 | enddo |
---|
570 | CALL put_field("XTLANCIEN"//striso(ixt), & |
---|
571 | & "XTLANCIEN",iso_tmp_lonlev) |
---|
572 | |
---|
573 | do k=1,klev |
---|
574 | do i=1,klon |
---|
575 | iso_tmp_lonlev(i,k)=xts_ancien(ixt,i,k) |
---|
576 | enddo !do i=1,klon |
---|
577 | enddo |
---|
578 | CALL put_field("XTSANCIEN"//striso(ixt), & |
---|
579 | & "XTSANCIEN",iso_tmp_lonlev) |
---|
580 | |
---|
581 | do k=1,klev |
---|
582 | do i=1,klon |
---|
583 | iso_tmp_lonlev(i,k)=wake_deltaxt(ixt,i,k) |
---|
584 | enddo !do i=1,klon |
---|
585 | enddo |
---|
586 | CALL put_field("WAKE_DELTAXT"//striso(ixt), & |
---|
587 | & "WAKE_DELTAXT",iso_tmp_lonlev) |
---|
588 | |
---|
589 | #ifdef ISOVERIF |
---|
590 | if (iso_eau.gt.0) then |
---|
591 | do i=1,klon |
---|
592 | if (iso_verif_egalite_nostop(run_off_lic_0(i), & |
---|
593 | & xtrun_off_lic_0(iso_eau,i),'phyisoredem 137') & |
---|
594 | & .eq.1) then |
---|
595 | write(*,*) 'i=',i |
---|
596 | stop |
---|
597 | endif |
---|
598 | enddo !do i=1,klon |
---|
599 | endif !if (iso_eau.gt.0) then |
---|
600 | #endif |
---|
601 | do i=1,klon |
---|
602 | iso_tmp(i)=xtrun_off_lic_0(ixt,i) |
---|
603 | enddo !do i=1,klon |
---|
604 | CALL put_field("XTRUNOFFLIC0"//striso(ixt), & |
---|
605 | & "Runofflic0",iso_tmp) |
---|
606 | |
---|
607 | do k=1,klev |
---|
608 | do i=1,klon |
---|
609 | iso_tmp_lonlev(i,k)=wake_deltaxt(ixt,i,k) |
---|
610 | enddo !do i=1,klon |
---|
611 | enddo |
---|
612 | CALL put_field("WAKE_DELTAXT"//striso(ixt), & |
---|
613 | & "WAKE_DELTAXT"//striso(ixt), & |
---|
614 | & iso_tmp_lonlev) |
---|
615 | |
---|
616 | do i=1,klon |
---|
617 | iso_tmp(i)=Rland_ice(ixt,i) |
---|
618 | enddo !do i=1,klon |
---|
619 | CALL put_field("Rland_ice"//striso(ixt), & |
---|
620 | & "ratio land ice",iso_tmp) |
---|
621 | |
---|
622 | enddo !do ixt=1,niso |
---|
623 | |
---|
624 | #ifdef ISOTRAC |
---|
625 | do ixt=niso+1,ntraciso |
---|
626 | iiso=index_iso(ixt) |
---|
627 | izone=index_zone(ixt) |
---|
628 | |
---|
629 | striso_sortie=striso(iiso)//strtrac(izone) |
---|
630 | |
---|
631 | DO nsrf = 1, nbsrf |
---|
632 | do i=1,klon |
---|
633 | iso_tmp_lonsrf(i,nsrf)=fxtevap(ixt,i,nsrf) |
---|
634 | enddo !do i=1,klon |
---|
635 | enddo !DO nsrf = 1, nbsrf |
---|
636 | CALL put_field_srf1("XTEVAP"//striso_sortie(1:lnblnk(striso_sortie)), & |
---|
637 | & "Evaporation de surface No."//str2 & |
---|
638 | & ,iso_tmp_lonsrf) |
---|
639 | |
---|
640 | do i=1,klon |
---|
641 | iso_tmp(i)=xtrain_fall(ixt,i) |
---|
642 | enddo !do i=1,klon |
---|
643 | CALL put_field("xtrain_f"//striso_sortie(1:lnblnk(striso_sortie)), & |
---|
644 | & "precipitation liquide",iso_tmp) |
---|
645 | |
---|
646 | do i=1,klon |
---|
647 | iso_tmp(i)=xtsnow_fall(ixt,i) |
---|
648 | enddo !do i=1,klon |
---|
649 | CALL put_field("xtsnow_f"//striso_sortie(1:lnblnk(striso_sortie)), & |
---|
650 | & "precipitation solide",iso_tmp) |
---|
651 | |
---|
652 | do k=1,klev |
---|
653 | do i=1,klon |
---|
654 | iso_tmp_lonlev(i,k)=xt_ancien(ixt,i,k) |
---|
655 | enddo !do i=1,klon |
---|
656 | enddo |
---|
657 | CALL put_field("XTANCIEN"//striso_sortie(1:lnblnk(striso_sortie)), & |
---|
658 | & "XTANCIEN",iso_tmp_lonlev) |
---|
659 | |
---|
660 | do k=1,klev |
---|
661 | do i=1,klon |
---|
662 | iso_tmp_lonlev(i,k)=xtl_ancien(ixt,i,k) |
---|
663 | enddo !do i=1,klon |
---|
664 | enddo |
---|
665 | CALL put_field("XTLANCIEN"//striso_sortie(1:lnblnk(striso_sortie)), & |
---|
666 | & "XTLANCIEN",iso_tmp_lonlev) |
---|
667 | |
---|
668 | do k=1,klev |
---|
669 | do i=1,klon |
---|
670 | iso_tmp_lonlev(i,k)=xts_ancien(ixt,i,k) |
---|
671 | enddo !do i=1,klon |
---|
672 | enddo |
---|
673 | CALL put_field("XTSANCIEN"//striso_sortie(1:lnblnk(striso_sortie)), & |
---|
674 | & "XTSANCIEN",iso_tmp_lonlev) |
---|
675 | |
---|
676 | do k=1,klev |
---|
677 | do i=1,klon |
---|
678 | iso_tmp_lonlev(i,k)=wake_deltaxt(ixt,i,k) |
---|
679 | enddo !do i=1,klon |
---|
680 | enddo |
---|
681 | CALL put_field("WAKE_DELTAXT"//striso_sortie(1:lnblnk(striso_sortie)), & |
---|
682 | & "WAKE_DELTAXT",iso_tmp_lonlev) |
---|
683 | |
---|
684 | enddo !do ixt=niso+1,ntraciso |
---|
685 | #endif |
---|
686 | |
---|
687 | write(*,*) 'phyisoredem 261: sortie' |
---|
688 | END SUBROUTINE phyisoredem |
---|
689 | #endif |
---|
690 | |
---|
691 | END SUBROUTINE phyredem |
---|