/[lmdze]/trunk/Sources/phylmd/phyetat0.f
ViewVC logotype

Contents of /trunk/Sources/phylmd/phyetat0.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 140 - (show annotations)
Fri Jun 5 18:58:06 2015 UTC (8 years, 11 months ago) by guez
File size: 21375 byte(s)
Changed unit of variables lat_min_guide and lat_max_guide from module
conf_guide_m from degrees to rad. Then we do not have to convert the
whole array rlat from rad to degrees in SUBROUTINE tau2alpha.

Removed some useless computations in inigeom.

Removed module coefils. Moved variables sddv, unsddv, sddu, unsddu,
eignfnu, eignfnv of module coefils to module inifgn_m. Downgraded
variables coefilu, coefilu2, coefilv, coefilv2, modfrstu, modfrstv of
module coefils to local variables of SUBROUTINE inifilr.

Write and read a 3-dimensional variable Tsoil in restartphy.nc and
startphy.nc instead of multiple variables for the different
subs-urfaces and soil layers. This does not allow any longer to
provide only the surface value in startphy.nc and spread it to other
layers. Instead, if necessary, pre-process the file startphy.nc to
spread the surface value.

1 module phyetat0_m
2
3 use dimphy, only: klon
4
5 IMPLICIT none
6
7 REAL, save:: rlat(klon), rlon(klon)
8 ! latitude and longitude of a point of the scalar grid identified
9 ! by a simple index, in degrees
10
11 private klon
12
13 contains
14
15 SUBROUTINE phyetat0(pctsrf, tsol, tsoil, tslab, seaice, qsurf, qsol, &
16 snow, albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, &
17 radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
18 t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, &
19 sig1, w01)
20
21 ! From phylmd/phyetat0.F, version 1.4 2005/06/03 10:03:07
22 ! Author: Z.X. Li (LMD/CNRS)
23 ! Date: 1993/08/18
24 ! Objet : lecture de l'état initial pour la physique
25
26 use dimphy, only: zmasq, klev
27 USE dimsoil, ONLY : nsoilmx
28 USE indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
29 use netcdf, only: nf90_global, nf90_inq_varid, NF90_NOERR, &
30 NF90_NOWRITE
31 use netcdf95, only: nf95_close, nf95_get_att, nf95_get_var, &
32 nf95_inq_varid, nf95_inquire_variable, NF95_OPEN
33 USE temps, ONLY : itau_phy
34
35 REAL pctsrf(klon, nbsrf)
36 REAL tsol(klon, nbsrf)
37 REAL tsoil(klon, nsoilmx, nbsrf)
38 REAL tslab(klon), seaice(klon)
39 REAL qsurf(klon, nbsrf)
40 REAL, intent(out):: qsol(:) ! (klon)
41 REAL snow(klon, nbsrf)
42 REAL albe(klon, nbsrf)
43 REAL alblw(klon, nbsrf)
44 REAL evap(klon, nbsrf)
45 REAL, intent(out):: rain_fall(klon)
46 REAL snow_fall(klon)
47 real solsw(klon)
48 REAL, intent(out):: sollw(klon)
49 real fder(klon)
50 REAL radsol(klon)
51 REAL frugs(klon, nbsrf)
52 REAL agesno(klon, nbsrf)
53 REAL zmea(klon)
54 REAL, intent(out):: zstd(klon)
55 REAL, intent(out):: zsig(klon)
56 REAL zgam(klon)
57 REAL zthe(klon)
58 REAL zpic(klon)
59 REAL zval(klon)
60 REAL t_ancien(klon, klev), q_ancien(klon, klev)
61 LOGICAL, intent(out):: ancien_ok
62 real rnebcon(klon, klev), ratqs(klon, klev), clwcon(klon, klev)
63 REAL run_off_lic_0(klon)
64 real, intent(out):: sig1(klon, klev) ! section adiabatic updraft
65
66 real, intent(out):: w01(klon, klev)
67 ! vertical velocity within adiabatic updraft
68
69 ! Local:
70 REAL fractint(klon)
71 REAL xmin, xmax
72 INTEGER ncid, varid, ndims
73 INTEGER ierr, i, nsrf
74 CHARACTER(len=2) str2
75
76 !---------------------------------------------------------------
77
78 print *, "Call sequence information: phyetat0"
79
80 ! Fichier contenant l'état initial :
81 call NF95_OPEN("startphy.nc", NF90_NOWRITE, ncid)
82
83 call nf95_get_att(ncid, nf90_global, "itau_phy", itau_phy)
84
85 ! Lecture des latitudes (coordonnees):
86
87 call NF95_INQ_VARID(ncid, "latitude", varid)
88 call NF95_GET_VAR(ncid, varid, rlat)
89
90 ! Lecture des longitudes (coordonnees):
91
92 call NF95_INQ_VARID(ncid, "longitude", varid)
93 call NF95_GET_VAR(ncid, varid, rlon)
94
95 ! Lecture du masque terre mer
96
97 call NF95_INQ_VARID(ncid, "masque", varid)
98 call nf95_get_var(ncid, varid, zmasq)
99
100 ! Lecture des fractions pour chaque sous-surface
101
102 ! initialisation des sous-surfaces
103
104 pctsrf = 0.
105
106 ! fraction de terre
107
108 ierr = NF90_INQ_VARID(ncid, "FTER", varid)
109 IF (ierr == NF90_NOERR) THEN
110 call nf95_get_var(ncid, varid, pctsrf(:, is_ter))
111 else
112 PRINT *, 'phyetat0: Le champ <FTER> est absent'
113 ENDIF
114
115 ! fraction de glace de terre
116
117 ierr = NF90_INQ_VARID(ncid, "FLIC", varid)
118 IF (ierr == NF90_NOERR) THEN
119 call nf95_get_var(ncid, varid, pctsrf(:, is_lic))
120 else
121 PRINT *, 'phyetat0: Le champ <FLIC> est absent'
122 ENDIF
123
124 ! fraction d'ocean
125
126 ierr = NF90_INQ_VARID(ncid, "FOCE", varid)
127 IF (ierr == NF90_NOERR) THEN
128 call nf95_get_var(ncid, varid, pctsrf(:, is_oce))
129 else
130 PRINT *, 'phyetat0: Le champ <FOCE> est absent'
131 ENDIF
132
133 ! fraction glace de mer
134
135 ierr = NF90_INQ_VARID(ncid, "FSIC", varid)
136 IF (ierr == NF90_NOERR) THEN
137 call nf95_get_var(ncid, varid, pctsrf(:, is_sic))
138 else
139 PRINT *, 'phyetat0: Le champ <FSIC> est absent'
140 ENDIF
141
142 ! Verification de l'adequation entre le masque et les sous-surfaces
143
144 fractint = pctsrf(:, is_ter) + pctsrf(:, is_lic)
145 DO i = 1 , klon
146 IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN
147 WRITE(*, *) 'phyetat0: attention fraction terre pas ', &
148 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
149 , pctsrf(i, is_lic)
150 ENDIF
151 END DO
152 fractint = pctsrf(:, is_oce) + pctsrf(:, is_sic)
153 DO i = 1 , klon
154 IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN
155 WRITE(*, *) 'phyetat0 attention fraction ocean pas ', &
156 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
157 , pctsrf(i, is_sic)
158 ENDIF
159 END DO
160
161 ! Lecture des temperatures du sol:
162 call NF95_INQ_VARID(ncid, "TS", varid)
163 call nf95_inquire_variable(ncid, varid, ndims = ndims)
164 if (ndims == 2) then
165 call NF95_GET_VAR(ncid, varid, tsol)
166 else
167 print *, "Found only one surface type for soil temperature."
168 call nf95_get_var(ncid, varid, tsol(:, 1))
169 tsol(:, 2:nbsrf) = spread(tsol(:, 1), dim = 2, ncopies = nbsrf - 1)
170 end if
171
172 ! Lecture des temperatures du sol profond:
173
174 call NF95_INQ_VARID(ncid, 'Tsoil', varid)
175 call NF95_GET_VAR(ncid, varid, tsoil)
176
177 !IM "slab" ocean
178 ! Lecture de tslab (pour slab ocean seulement):
179 tslab = 0.
180 seaice = 0.
181
182 ! Lecture de l'humidite de l'air juste au dessus du sol:
183
184 ierr = NF90_INQ_VARID(ncid, "QS", varid)
185 IF (ierr /= NF90_NOERR) THEN
186 PRINT *, 'phyetat0: Le champ <QS> est absent'
187 PRINT *, ' Mais je vais essayer de lire QS**'
188 DO nsrf = 1, nbsrf
189 IF (nsrf > 99) THEN
190 PRINT *, "Trop de sous-mailles"
191 stop 1
192 ENDIF
193 WRITE(str2, '(i2.2)') nsrf
194 call NF95_INQ_VARID(ncid, "QS"//str2, varid)
195 call NF95_GET_VAR(ncid, varid, qsurf(:, nsrf))
196 xmin = 1.0E+20
197 xmax = -1.0E+20
198 DO i = 1, klon
199 xmin = MIN(qsurf(i, nsrf), xmin)
200 xmax = MAX(qsurf(i, nsrf), xmax)
201 ENDDO
202 PRINT *, 'Humidite pres du sol QS**:', nsrf, xmin, xmax
203 ENDDO
204 ELSE
205 PRINT *, 'phyetat0: Le champ <QS> est present'
206 PRINT *, ' J ignore donc les autres humidites QS**'
207 call nf95_get_var(ncid, varid, qsurf(:, 1))
208 xmin = 1.0E+20
209 xmax = -1.0E+20
210 DO i = 1, klon
211 xmin = MIN(qsurf(i, 1), xmin)
212 xmax = MAX(qsurf(i, 1), xmax)
213 ENDDO
214 PRINT *, 'Humidite pres du sol <QS>', xmin, xmax
215 DO nsrf = 2, nbsrf
216 DO i = 1, klon
217 qsurf(i, nsrf) = qsurf(i, 1)
218 ENDDO
219 ENDDO
220 ENDIF
221
222 ! Eau dans le sol (pour le modele de sol "bucket")
223
224 ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
225 IF (ierr == NF90_NOERR) THEN
226 call nf95_get_var(ncid, varid, qsol)
227 else
228 PRINT *, 'phyetat0: Le champ <QSOL> est absent'
229 PRINT *, ' Valeur par defaut nulle'
230 qsol = 0.
231 ENDIF
232
233 ! Lecture de neige au sol:
234
235 ierr = NF90_INQ_VARID(ncid, "SNOW", varid)
236 IF (ierr /= NF90_NOERR) THEN
237 PRINT *, 'phyetat0: Le champ <SNOW> est absent'
238 PRINT *, ' Mais je vais essayer de lire SNOW**'
239 DO nsrf = 1, nbsrf
240 IF (nsrf > 99) THEN
241 PRINT *, "Trop de sous-mailles"
242 stop 1
243 ENDIF
244 WRITE(str2, '(i2.2)') nsrf
245 call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)
246 call NF95_GET_VAR(ncid, varid, snow(:, nsrf))
247 xmin = 1.0E+20
248 xmax = -1.0E+20
249 DO i = 1, klon
250 xmin = MIN(snow(i, nsrf), xmin)
251 xmax = MAX(snow(i, nsrf), xmax)
252 ENDDO
253 PRINT *, 'Neige du sol SNOW**:', nsrf, xmin, xmax
254 ENDDO
255 ELSE
256 PRINT *, 'phyetat0: Le champ <SNOW> est present'
257 PRINT *, ' J ignore donc les autres neiges SNOW**'
258 call nf95_get_var(ncid, varid, snow(:, 1))
259 xmin = 1.0E+20
260 xmax = -1.0E+20
261 DO i = 1, klon
262 xmin = MIN(snow(i, 1), xmin)
263 xmax = MAX(snow(i, 1), xmax)
264 ENDDO
265 PRINT *, 'Neige du sol <SNOW>', xmin, xmax
266 DO nsrf = 2, nbsrf
267 DO i = 1, klon
268 snow(i, nsrf) = snow(i, 1)
269 ENDDO
270 ENDDO
271 ENDIF
272
273 ! Lecture de albedo au sol:
274
275 ierr = NF90_INQ_VARID(ncid, "ALBE", varid)
276 IF (ierr /= NF90_NOERR) THEN
277 PRINT *, 'phyetat0: Le champ <ALBE> est absent'
278 PRINT *, ' Mais je vais essayer de lire ALBE**'
279 DO nsrf = 1, nbsrf
280 IF (nsrf > 99) THEN
281 PRINT *, "Trop de sous-mailles"
282 stop 1
283 ENDIF
284 WRITE(str2, '(i2.2)') nsrf
285 call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)
286 call NF95_GET_VAR(ncid, varid, albe(:, nsrf))
287 xmin = 1.0E+20
288 xmax = -1.0E+20
289 DO i = 1, klon
290 xmin = MIN(albe(i, nsrf), xmin)
291 xmax = MAX(albe(i, nsrf), xmax)
292 ENDDO
293 PRINT *, 'Albedo du sol ALBE**:', nsrf, xmin, xmax
294 ENDDO
295 ELSE
296 PRINT *, 'phyetat0: Le champ <ALBE> est present'
297 PRINT *, ' J ignore donc les autres ALBE**'
298 call nf95_get_var(ncid, varid, albe(:, 1))
299 xmin = 1.0E+20
300 xmax = -1.0E+20
301 DO i = 1, klon
302 xmin = MIN(albe(i, 1), xmin)
303 xmax = MAX(albe(i, 1), xmax)
304 ENDDO
305 PRINT *, 'Neige du sol <ALBE>', xmin, xmax
306 DO nsrf = 2, nbsrf
307 DO i = 1, klon
308 albe(i, nsrf) = albe(i, 1)
309 ENDDO
310 ENDDO
311 ENDIF
312
313 ! Lecture de albedo au sol LW:
314
315 ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)
316 IF (ierr /= NF90_NOERR) THEN
317 PRINT *, 'phyetat0: Le champ <ALBLW> est absent'
318 ! PRINT *, ' Mais je vais essayer de lire ALBLW**'
319 PRINT *, ' Mais je vais prendre ALBE**'
320 DO nsrf = 1, nbsrf
321 DO i = 1, klon
322 alblw(i, nsrf) = albe(i, nsrf)
323 ENDDO
324 ENDDO
325 ELSE
326 PRINT *, 'phyetat0: Le champ <ALBLW> est present'
327 PRINT *, ' J ignore donc les autres ALBLW**'
328 call nf95_get_var(ncid, varid, alblw(:, 1))
329 xmin = 1.0E+20
330 xmax = -1.0E+20
331 DO i = 1, klon
332 xmin = MIN(alblw(i, 1), xmin)
333 xmax = MAX(alblw(i, 1), xmax)
334 ENDDO
335 PRINT *, 'Neige du sol <ALBLW>', xmin, xmax
336 DO nsrf = 2, nbsrf
337 DO i = 1, klon
338 alblw(i, nsrf) = alblw(i, 1)
339 ENDDO
340 ENDDO
341 ENDIF
342
343 ! Lecture de evaporation:
344
345 ierr = NF90_INQ_VARID(ncid, "EVAP", varid)
346 IF (ierr /= NF90_NOERR) THEN
347 PRINT *, 'phyetat0: Le champ <EVAP> est absent'
348 PRINT *, ' Mais je vais essayer de lire EVAP**'
349 DO nsrf = 1, nbsrf
350 IF (nsrf > 99) THEN
351 PRINT *, "Trop de sous-mailles"
352 stop 1
353 ENDIF
354 WRITE(str2, '(i2.2)') nsrf
355 call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)
356 call NF95_GET_VAR(ncid, varid, evap(:, nsrf))
357 xmin = 1.0E+20
358 xmax = -1.0E+20
359 DO i = 1, klon
360 xmin = MIN(evap(i, nsrf), xmin)
361 xmax = MAX(evap(i, nsrf), xmax)
362 ENDDO
363 PRINT *, 'evap du sol EVAP**:', nsrf, xmin, xmax
364 ENDDO
365 ELSE
366 PRINT *, 'phyetat0: Le champ <EVAP> est present'
367 PRINT *, ' J ignore donc les autres EVAP**'
368 call nf95_get_var(ncid, varid, evap(:, 1))
369 xmin = 1.0E+20
370 xmax = -1.0E+20
371 DO i = 1, klon
372 xmin = MIN(evap(i, 1), xmin)
373 xmax = MAX(evap(i, 1), xmax)
374 ENDDO
375 PRINT *, 'Evap du sol <EVAP>', xmin, xmax
376 DO nsrf = 2, nbsrf
377 DO i = 1, klon
378 evap(i, nsrf) = evap(i, 1)
379 ENDDO
380 ENDDO
381 ENDIF
382
383 ! Lecture precipitation liquide:
384
385 call NF95_INQ_VARID(ncid, "rain_f", varid)
386 call NF95_GET_VAR(ncid, varid, rain_fall)
387
388 ! Lecture precipitation solide:
389
390 call NF95_INQ_VARID(ncid, "snow_f", varid)
391 call NF95_GET_VAR(ncid, varid, snow_fall)
392 xmin = 1.0E+20
393 xmax = -1.0E+20
394 DO i = 1, klon
395 xmin = MIN(snow_fall(i), xmin)
396 xmax = MAX(snow_fall(i), xmax)
397 ENDDO
398 PRINT *, 'Precipitation solide snow_f:', xmin, xmax
399
400 ! Lecture rayonnement solaire au sol:
401
402 ierr = NF90_INQ_VARID(ncid, "solsw", varid)
403 IF (ierr /= NF90_NOERR) THEN
404 PRINT *, 'phyetat0: Le champ <solsw> est absent'
405 PRINT *, 'mis a zero'
406 solsw = 0.
407 ELSE
408 call nf95_get_var(ncid, varid, solsw)
409 ENDIF
410 xmin = 1.0E+20
411 xmax = -1.0E+20
412 DO i = 1, klon
413 xmin = MIN(solsw(i), xmin)
414 xmax = MAX(solsw(i), xmax)
415 ENDDO
416 PRINT *, 'Rayonnement solaire au sol solsw:', xmin, xmax
417
418 ! Lecture rayonnement IF au sol:
419
420 ierr = NF90_INQ_VARID(ncid, "sollw", varid)
421 IF (ierr /= NF90_NOERR) THEN
422 PRINT *, 'phyetat0: Le champ <sollw> est absent'
423 PRINT *, 'mis a zero'
424 sollw = 0.
425 ELSE
426 call nf95_get_var(ncid, varid, sollw)
427 ENDIF
428 PRINT *, 'Rayonnement IF au sol sollw:', minval(sollw), maxval(sollw)
429
430 ! Lecture derive des flux:
431
432 ierr = NF90_INQ_VARID(ncid, "fder", varid)
433 IF (ierr /= NF90_NOERR) THEN
434 PRINT *, 'phyetat0: Le champ <fder> est absent'
435 PRINT *, 'mis a zero'
436 fder = 0.
437 ELSE
438 call nf95_get_var(ncid, varid, fder)
439 ENDIF
440 xmin = 1.0E+20
441 xmax = -1.0E+20
442 DO i = 1, klon
443 xmin = MIN(fder(i), xmin)
444 xmax = MAX(fder(i), xmax)
445 ENDDO
446 PRINT *, 'Derive des flux fder:', xmin, xmax
447
448 ! Lecture du rayonnement net au sol:
449
450 call NF95_INQ_VARID(ncid, "RADS", varid)
451 call NF95_GET_VAR(ncid, varid, radsol)
452 xmin = 1.0E+20
453 xmax = -1.0E+20
454 DO i = 1, klon
455 xmin = MIN(radsol(i), xmin)
456 xmax = MAX(radsol(i), xmax)
457 ENDDO
458 PRINT *, 'Rayonnement net au sol radsol:', xmin, xmax
459
460 ! Lecture de la longueur de rugosite
461
462 ierr = NF90_INQ_VARID(ncid, "RUG", varid)
463 IF (ierr /= NF90_NOERR) THEN
464 PRINT *, 'phyetat0: Le champ <RUG> est absent'
465 PRINT *, ' Mais je vais essayer de lire RUG**'
466 DO nsrf = 1, nbsrf
467 IF (nsrf > 99) THEN
468 PRINT *, "Trop de sous-mailles"
469 stop 1
470 ENDIF
471 WRITE(str2, '(i2.2)') nsrf
472 call NF95_INQ_VARID(ncid, "RUG"//str2, varid)
473 call NF95_GET_VAR(ncid, varid, frugs(:, nsrf))
474 xmin = 1.0E+20
475 xmax = -1.0E+20
476 DO i = 1, klon
477 xmin = MIN(frugs(i, nsrf), xmin)
478 xmax = MAX(frugs(i, nsrf), xmax)
479 ENDDO
480 PRINT *, 'rugosite du sol RUG**:', nsrf, xmin, xmax
481 ENDDO
482 ELSE
483 PRINT *, 'phyetat0: Le champ <RUG> est present'
484 PRINT *, ' J ignore donc les autres RUG**'
485 call nf95_get_var(ncid, varid, frugs(:, 1))
486 xmin = 1.0E+20
487 xmax = -1.0E+20
488 DO i = 1, klon
489 xmin = MIN(frugs(i, 1), xmin)
490 xmax = MAX(frugs(i, 1), xmax)
491 ENDDO
492 PRINT *, 'rugosite <RUG>', xmin, xmax
493 DO nsrf = 2, nbsrf
494 DO i = 1, klon
495 frugs(i, nsrf) = frugs(i, 1)
496 ENDDO
497 ENDDO
498 ENDIF
499
500 ! Lecture de l'age de la neige:
501
502 ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)
503 IF (ierr /= NF90_NOERR) THEN
504 PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
505 PRINT *, ' Mais je vais essayer de lire AGESNO**'
506 DO nsrf = 1, nbsrf
507 IF (nsrf > 99) THEN
508 PRINT *, "Trop de sous-mailles"
509 stop 1
510 ENDIF
511 WRITE(str2, '(i2.2)') nsrf
512 ierr = NF90_INQ_VARID(ncid, "AGESNO"//str2, varid)
513 IF (ierr /= NF90_NOERR) THEN
514 PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
515 agesno = 50.0
516 ENDIF
517 call NF95_GET_VAR(ncid, varid, agesno(:, nsrf))
518 xmin = 1.0E+20
519 xmax = -1.0E+20
520 DO i = 1, klon
521 xmin = MIN(agesno(i, nsrf), xmin)
522 xmax = MAX(agesno(i, nsrf), xmax)
523 ENDDO
524 PRINT *, 'Age de la neige AGESNO**:', nsrf, xmin, xmax
525 ENDDO
526 ELSE
527 PRINT *, 'phyetat0: Le champ <AGESNO> est present'
528 PRINT *, ' J ignore donc les autres AGESNO**'
529 call nf95_get_var(ncid, varid, agesno(:, 1))
530 xmin = 1.0E+20
531 xmax = -1.0E+20
532 DO i = 1, klon
533 xmin = MIN(agesno(i, 1), xmin)
534 xmax = MAX(agesno(i, 1), xmax)
535 ENDDO
536 PRINT *, 'Age de la neige <AGESNO>', xmin, xmax
537 DO nsrf = 2, nbsrf
538 DO i = 1, klon
539 agesno(i, nsrf) = agesno(i, 1)
540 ENDDO
541 ENDDO
542 ENDIF
543
544 call NF95_INQ_VARID(ncid, "ZMEA", varid)
545 call NF95_GET_VAR(ncid, varid, zmea)
546 xmin = 1.0E+20
547 xmax = -1.0E+20
548 DO i = 1, klon
549 xmin = MIN(zmea(i), xmin)
550 xmax = MAX(zmea(i), xmax)
551 ENDDO
552 PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
553
554 call NF95_INQ_VARID(ncid, "ZSTD", varid)
555 call NF95_GET_VAR(ncid, varid, zstd)
556 xmin = 1.0E+20
557 xmax = -1.0E+20
558 DO i = 1, klon
559 xmin = MIN(zstd(i), xmin)
560 xmax = MAX(zstd(i), xmax)
561 ENDDO
562 PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
563
564 call NF95_INQ_VARID(ncid, "ZSIG", varid)
565 call NF95_GET_VAR(ncid, varid, zsig)
566 xmin = 1.0E+20
567 xmax = -1.0E+20
568 DO i = 1, klon
569 xmin = MIN(zsig(i), xmin)
570 xmax = MAX(zsig(i), xmax)
571 ENDDO
572 PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
573
574 call NF95_INQ_VARID(ncid, "ZGAM", varid)
575 call NF95_GET_VAR(ncid, varid, zgam)
576 xmin = 1.0E+20
577 xmax = -1.0E+20
578 DO i = 1, klon
579 xmin = MIN(zgam(i), xmin)
580 xmax = MAX(zgam(i), xmax)
581 ENDDO
582 PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
583
584 call NF95_INQ_VARID(ncid, "ZTHE", varid)
585 call NF95_GET_VAR(ncid, varid, zthe)
586 xmin = 1.0E+20
587 xmax = -1.0E+20
588 DO i = 1, klon
589 xmin = MIN(zthe(i), xmin)
590 xmax = MAX(zthe(i), xmax)
591 ENDDO
592 PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
593
594 call NF95_INQ_VARID(ncid, "ZPIC", varid)
595 call NF95_GET_VAR(ncid, varid, zpic)
596 xmin = 1.0E+20
597 xmax = -1.0E+20
598 DO i = 1, klon
599 xmin = MIN(zpic(i), xmin)
600 xmax = MAX(zpic(i), xmax)
601 ENDDO
602 PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
603
604 call NF95_INQ_VARID(ncid, "ZVAL", varid)
605 call NF95_GET_VAR(ncid, varid, zval)
606 xmin = 1.0E+20
607 xmax = -1.0E+20
608 DO i = 1, klon
609 xmin = MIN(zval(i), xmin)
610 xmax = MAX(zval(i), xmax)
611 ENDDO
612 PRINT *, 'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
613
614 ancien_ok = .TRUE.
615
616 ierr = NF90_INQ_VARID(ncid, "TANCIEN", varid)
617 IF (ierr /= NF90_NOERR) THEN
618 PRINT *, "phyetat0: Le champ <TANCIEN> est absent"
619 PRINT *, "Depart legerement fausse. Mais je continue"
620 ancien_ok = .FALSE.
621 ELSE
622 call nf95_get_var(ncid, varid, t_ancien)
623 ENDIF
624
625 ierr = NF90_INQ_VARID(ncid, "QANCIEN", varid)
626 IF (ierr /= NF90_NOERR) THEN
627 PRINT *, "phyetat0: Le champ <QANCIEN> est absent"
628 PRINT *, "Depart legerement fausse. Mais je continue"
629 ancien_ok = .FALSE.
630 ELSE
631 call nf95_get_var(ncid, varid, q_ancien)
632 ENDIF
633
634 ierr = NF90_INQ_VARID(ncid, "CLWCON", varid)
635 IF (ierr /= NF90_NOERR) THEN
636 PRINT *, "phyetat0: Le champ CLWCON est absent"
637 PRINT *, "Depart legerement fausse. Mais je continue"
638 clwcon = 0.
639 ELSE
640 call nf95_get_var(ncid, varid, clwcon(:, 1))
641 clwcon(:, 2:) = 0.
642 ENDIF
643 xmin = 1.0E+20
644 xmax = -1.0E+20
645 xmin = MINval(clwcon)
646 xmax = MAXval(clwcon)
647 PRINT *, 'Eau liquide convective (ecart-type) clwcon:', xmin, xmax
648
649 ierr = NF90_INQ_VARID(ncid, "RNEBCON", varid)
650 IF (ierr /= NF90_NOERR) THEN
651 PRINT *, "phyetat0: Le champ RNEBCON est absent"
652 PRINT *, "Depart legerement fausse. Mais je continue"
653 rnebcon = 0.
654 ELSE
655 call nf95_get_var(ncid, varid, rnebcon(:, 1))
656 rnebcon(:, 2:) = 0.
657 ENDIF
658 xmin = 1.0E+20
659 xmax = -1.0E+20
660 xmin = MINval(rnebcon)
661 xmax = MAXval(rnebcon)
662 PRINT *, 'Nebulosite convective (ecart-type) rnebcon:', xmin, xmax
663
664 ! Lecture ratqs
665
666 ierr = NF90_INQ_VARID(ncid, "RATQS", varid)
667 IF (ierr /= NF90_NOERR) THEN
668 PRINT *, "phyetat0: Le champ <RATQS> est absent"
669 PRINT *, "Depart legerement fausse. Mais je continue"
670 ratqs = 0.
671 ELSE
672 call nf95_get_var(ncid, varid, ratqs(:, 1))
673 ratqs(:, 2:) = 0.
674 ENDIF
675 xmin = 1.0E+20
676 xmax = -1.0E+20
677 xmin = MINval(ratqs)
678 xmax = MAXval(ratqs)
679 PRINT *, '(ecart-type) ratqs:', xmin, xmax
680
681 ! Lecture run_off_lic_0
682
683 ierr = NF90_INQ_VARID(ncid, "RUNOFFLIC0", varid)
684 IF (ierr /= NF90_NOERR) THEN
685 PRINT *, "phyetat0: Le champ <RUNOFFLIC0> est absent"
686 PRINT *, "Depart legerement fausse. Mais je continue"
687 run_off_lic_0 = 0.
688 ELSE
689 call nf95_get_var(ncid, varid, run_off_lic_0)
690 ENDIF
691 xmin = 1.0E+20
692 xmax = -1.0E+20
693 xmin = MINval(run_off_lic_0)
694 xmax = MAXval(run_off_lic_0)
695 PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
696
697 call nf95_inq_varid(ncid, "sig1", varid)
698 call nf95_get_var(ncid, varid, sig1)
699
700 call nf95_inq_varid(ncid, "w01", varid)
701 call nf95_get_var(ncid, varid, w01)
702
703 call NF95_CLOSE(ncid)
704
705 END SUBROUTINE phyetat0
706
707 end module phyetat0_m

  ViewVC Help
Powered by ViewVC 1.1.21