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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 43 - (hide annotations)
Fri Apr 8 12:43:31 2011 UTC (13 years, 1 month ago) by guez
Original Path: trunk/libf/phylmd/phyetat0.f90
File size: 29762 byte(s)
"start_init_phys" is now called directly by "etat0" instead of through
"start_init_dyn". "qsol_2d" is no longer a variable of module
"start_init_phys_m", it is an argument of
"start_init_phys". "start_init_dyn" now receives "tsol_2d" from
"etat0".

Split file "vlspltqs.f" into "vlspltqs.f90", "vlxqs.f90" and
""vlyqs.f90".

In "start_init_orog", replaced calls to "flin*" by calls to NetCDF95.

1 guez 3 module phyetat0_m
2    
3 guez 15 use dimphy, only: klon
4 guez 12
5 guez 3 IMPLICIT none
6    
7 guez 22 REAL, save:: rlat(klon), rlon(klon) ! latitude and longitude, in degrees
8 guez 3
9 guez 15 private klon
10 guez 3
11     contains
12    
13 guez 12 SUBROUTINE phyetat0(fichnom, pctsrf, tsol,tsoil, ocean, tslab,seaice, &
14 guez 3 qsurf,qsol,snow, &
15     albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, &
16 guez 13 fder,radsol,frugs,agesno, &
17     zmea,zstd,zsig,zgam,zthe,zpic,zval, &
18 guez 3 t_ancien,q_ancien,ancien_ok, rnebcon, ratqs,clwcon, &
19     run_off_lic_0)
20    
21     ! From phylmd/phyetat0.F,v 1.4 2005/06/03 10:03:07
22     ! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
23     ! Objet: Lecture de l'etat initial pour la physique
24    
25 guez 12 USE indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
26     USE dimsoil, ONLY : nsoilmx
27     USE temps, ONLY : itau_phy
28 guez 43 use netcdf, only: nf90_get_att, nf90_global, nf90_inq_varid, NF90_NOERR
29     use netcdf95, only: handle_err, nf95_get_var
30 guez 15 use dimphy, only: zmasq, klev
31 guez 12
32 guez 3 include "netcdf.inc"
33    
34 guez 12 CHARACTER(len=*) fichnom
35 guez 3 REAL tsol(klon,nbsrf)
36     REAL tsoil(klon,nsoilmx,nbsrf)
37     !IM "slab" ocean
38     REAL tslab(klon), seaice(klon)
39     REAL qsurf(klon,nbsrf)
40     REAL qsol(klon)
41     REAL snow(klon,nbsrf)
42     REAL albe(klon,nbsrf)
43     REAL alblw(klon,nbsrf)
44     REAL evap(klon,nbsrf)
45     REAL radsol(klon)
46     REAL rain_fall(klon)
47     REAL snow_fall(klon)
48     REAL sollw(klon)
49     real solsw(klon)
50     real fder(klon)
51     REAL frugs(klon,nbsrf)
52     REAL agesno(klon,nbsrf)
53     REAL zmea(klon)
54 guez 13 REAL, intent(out):: zstd(klon)
55     REAL, intent(out):: zsig(klon)
56 guez 3 REAL zgam(klon)
57     REAL zthe(klon)
58     REAL zpic(klon)
59     REAL zval(klon)
60     REAL pctsrf(klon, nbsrf)
61     REAL fractint(klon)
62     REAL run_off_lic_0(klon)
63    
64     REAL t_ancien(klon,klev), q_ancien(klon,klev)
65     real rnebcon(klon,klev),clwcon(klon,klev),ratqs(klon,klev)
66     LOGICAL ancien_ok
67    
68 guez 12 CHARACTER(len=*), intent(in):: ocean
69 guez 3
70     REAL xmin, xmax
71    
72     INTEGER nid, nvarid
73     INTEGER ierr, i, nsrf, isoil
74     CHARACTER*7 str7
75     CHARACTER*2 str2
76    
77     !---------------------------------------------------------------
78    
79     print *, "Call sequence information: phyetat0"
80    
81     ! Ouvrir le fichier contenant l'etat initial:
82    
83     print *, 'fichnom = ', fichnom
84     ierr = NF_OPEN (fichnom, NF_NOWRITE,nid)
85 guez 43 IF (ierr.NE.NF90_NOERR) THEN
86 guez 3 write(6,*)' Pb d''ouverture du fichier '//fichnom
87     write(6,*)' ierr = ', ierr
88     STOP 1
89     ENDIF
90    
91 guez 12 ierr = nf90_get_att(nid, nf90_global, "itau_phy", itau_phy)
92     call handle_err("phyetat0 itau_phy", ierr, nid, nf90_global)
93 guez 3
94     ! Lecture des latitudes (coordonnees):
95    
96 guez 43 ierr = NF90_INQ_VARID (nid, "latitude", nvarid)
97     IF (ierr.NE.NF90_NOERR) THEN
98     PRINT *, 'phyetat0: Le champ <latitude> est absent'
99 guez 3 stop 1
100     ENDIF
101     ierr = NF_GET_VAR_REAL(nid, nvarid, rlat)
102 guez 43 IF (ierr.NE.NF90_NOERR) THEN
103     PRINT *, 'phyetat0: Lecture echouee pour <latitude>'
104 guez 3 stop 1
105     ENDIF
106    
107     ! Lecture des longitudes (coordonnees):
108    
109 guez 43 ierr = NF90_INQ_VARID (nid, "longitude", nvarid)
110     IF (ierr.NE.NF90_NOERR) THEN
111     PRINT *, 'phyetat0: Le champ <longitude> est absent'
112 guez 3 stop 1
113     ENDIF
114     ierr = NF_GET_VAR_REAL(nid, nvarid, rlon)
115 guez 43 IF (ierr.NE.NF90_NOERR) THEN
116     PRINT *, 'phyetat0: Lecture echouee pour <latitude>'
117 guez 3 stop 1
118     ENDIF
119    
120    
121     ! Lecture du masque terre mer
122    
123 guez 43 ierr = NF90_INQ_VARID (nid, "masque", nvarid)
124     IF (ierr == NF90_NOERR) THEN
125     call nf95_get_var(nid, nvarid, zmasq)
126 guez 3 else
127 guez 43 PRINT *, 'phyetat0: Le champ <masque> est absent'
128     PRINT *, 'fichier startphy non compatible avec phyetat0'
129 guez 3 ! stop 1
130     ENDIF
131     ! Lecture des fractions pour chaque sous-surface
132    
133     ! initialisation des sous-surfaces
134    
135     pctsrf = 0.
136    
137     ! fraction de terre
138    
139 guez 43 ierr = NF90_INQ_VARID (nid, "FTER", nvarid)
140     IF (ierr == NF90_NOERR) THEN
141     call nf95_get_var(nid, nvarid, pctsrf(1 : klon,is_ter))
142 guez 3 else
143 guez 43 PRINT *, 'phyetat0: Le champ <FTER> est absent'
144 guez 3 !$$$ stop 1
145     ENDIF
146    
147     ! fraction de glace de terre
148    
149 guez 43 ierr = NF90_INQ_VARID (nid, "FLIC", nvarid)
150     IF (ierr == NF90_NOERR) THEN
151     call nf95_get_var(nid, nvarid, pctsrf(1 : klon,is_lic))
152 guez 3 else
153 guez 43 PRINT *, 'phyetat0: Le champ <FLIC> est absent'
154 guez 3 !$$$ stop 1
155     ENDIF
156    
157     ! fraction d'ocean
158    
159 guez 43 ierr = NF90_INQ_VARID (nid, "FOCE", nvarid)
160     IF (ierr == NF90_NOERR) THEN
161     call nf95_get_var(nid, nvarid, pctsrf(1 : klon,is_oce))
162 guez 3 else
163 guez 43 PRINT *, 'phyetat0: Le champ <FOCE> est absent'
164 guez 3 !$$$ stop 1
165     ENDIF
166    
167     ! fraction glace de mer
168    
169 guez 43 ierr = NF90_INQ_VARID (nid, "FSIC", nvarid)
170     IF (ierr == NF90_NOERR) THEN
171     call nf95_get_var(nid, nvarid, pctsrf(1 : klon, is_sic))
172 guez 3 else
173 guez 43 PRINT *, 'phyetat0: Le champ <FSIC> est absent'
174 guez 3 !$$$ stop 1
175     ENDIF
176    
177     ! Verification de l'adequation entre le masque et les sous-surfaces
178    
179     fractint( 1 : klon) = pctsrf(1 : klon, is_ter) &
180     + pctsrf(1 : klon, is_lic)
181     DO i = 1 , klon
182     IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN
183     WRITE(*,*) 'phyetat0: attention fraction terre pas ', &
184     'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
185     ,pctsrf(i, is_lic)
186     ENDIF
187     END DO
188     fractint (1 : klon) = pctsrf(1 : klon, is_oce) &
189     + pctsrf(1 : klon, is_sic)
190     DO i = 1 , klon
191     IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN
192     WRITE(*,*) 'phyetat0 attention fraction ocean pas ', &
193     'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
194     ,pctsrf(i, is_sic)
195     ENDIF
196     END DO
197    
198     ! Lecture des temperatures du sol:
199    
200 guez 43 ierr = NF90_INQ_VARID (nid, "TS", nvarid)
201     IF (ierr.NE.NF90_NOERR) THEN
202     PRINT *, 'phyetat0: Le champ <TS> est absent'
203     PRINT *, ' Mais je vais essayer de lire TS**'
204 guez 3 DO nsrf = 1, nbsrf
205     IF (nsrf.GT.99) THEN
206 guez 43 PRINT *, "Trop de sous-mailles"
207 guez 3 stop 1
208     ENDIF
209     WRITE(str2,'(i2.2)') nsrf
210 guez 43 ierr = NF90_INQ_VARID (nid, "TS"//str2, nvarid)
211     IF (ierr.NE.NF90_NOERR) THEN
212     PRINT *, "phyetat0: Le champ <TS"//str2//"> est absent"
213 guez 3 stop 1
214     ENDIF
215     ierr = NF_GET_VAR_REAL(nid, nvarid, tsol(1,nsrf))
216 guez 43 IF (ierr.NE.NF90_NOERR) THEN
217     PRINT *, "phyetat0: Lecture echouee pour <TS"//str2//">"
218 guez 3 stop 1
219     ENDIF
220     xmin = 1.0E+20
221     xmax = -1.0E+20
222     DO i = 1, klon
223     xmin = MIN(tsol(i,nsrf),xmin)
224     xmax = MAX(tsol(i,nsrf),xmax)
225     ENDDO
226 guez 43 PRINT *,'Temperature du sol TS**:', nsrf, xmin, xmax
227 guez 3 ENDDO
228     ELSE
229 guez 43 PRINT *, 'phyetat0: Le champ <TS> est present'
230     PRINT *, ' J ignore donc les autres temperatures TS**'
231     call nf95_get_var(nid, nvarid, tsol(:,1))
232 guez 3 xmin = 1.0E+20
233     xmax = -1.0E+20
234     DO i = 1, klon
235     xmin = MIN(tsol(i,1),xmin)
236     xmax = MAX(tsol(i,1),xmax)
237     ENDDO
238 guez 43 PRINT *,'Temperature du sol <TS>', xmin, xmax
239 guez 3 DO nsrf = 2, nbsrf
240     DO i = 1, klon
241     tsol(i,nsrf) = tsol(i,1)
242     ENDDO
243     ENDDO
244     ENDIF
245    
246     ! Lecture des temperatures du sol profond:
247    
248     DO nsrf = 1, nbsrf
249     DO isoil=1, nsoilmx
250     IF (isoil.GT.99 .AND. nsrf.GT.99) THEN
251 guez 43 PRINT *, "Trop de couches ou sous-mailles"
252 guez 3 stop 1
253     ENDIF
254     WRITE(str7,'(i2.2,"srf",i2.2)') isoil, nsrf
255 guez 43 ierr = NF90_INQ_VARID (nid, 'Tsoil'//str7, nvarid)
256     IF (ierr.NE.NF90_NOERR) THEN
257     PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
258     PRINT *, " Il prend donc la valeur de surface"
259 guez 3 DO i=1, klon
260     tsoil(i,isoil,nsrf)=tsol(i,nsrf)
261     ENDDO
262     ELSE
263     ierr = NF_GET_VAR_REAL(nid, nvarid, tsoil(1,isoil,nsrf))
264 guez 43 IF (ierr.NE.NF90_NOERR) THEN
265     PRINT *, "Lecture echouee pour <Tsoil"//str7//">"
266 guez 3 stop 1
267     ENDIF
268     ENDIF
269     ENDDO
270     ENDDO
271    
272     !IM "slab" ocean
273    
274     ! Lecture de tslab (pour slab ocean seulement):
275    
276     IF (ocean .eq. 'slab ') then
277 guez 43 ierr = NF90_INQ_VARID (nid, "TSLAB", nvarid)
278     IF (ierr.NE.NF90_NOERR) THEN
279     PRINT *, "phyetat0: Le champ <TSLAB> est absent"
280 guez 3 stop 1
281     ENDIF
282 guez 43 call nf95_get_var(nid, nvarid, tslab)
283 guez 3 xmin = 1.0E+20
284     xmax = -1.0E+20
285     DO i = 1, klon
286     xmin = MIN(tslab(i),xmin)
287     xmax = MAX(tslab(i),xmax)
288     ENDDO
289 guez 43 PRINT *,'Ecart de la SST tslab:', xmin, xmax
290 guez 3
291     ! Lecture de seaice (pour slab ocean seulement):
292    
293 guez 43 ierr = NF90_INQ_VARID (nid, "SEAICE", nvarid)
294     IF (ierr.NE.NF90_NOERR) THEN
295     PRINT *, "phyetat0: Le champ <SEAICE> est absent"
296 guez 3 stop 1
297     ENDIF
298 guez 43 call nf95_get_var(nid, nvarid, seaice)
299 guez 3 xmin = 1.0E+20
300     xmax = -1.0E+20
301     DO i = 1, klon
302     xmin = MIN(seaice(i),xmin)
303     xmax = MAX(seaice(i),xmax)
304     ENDDO
305 guez 43 PRINT *,'Masse de la glace de mer seaice:', xmin, xmax
306 guez 3 ELSE
307     tslab = 0.
308     seaice = 0.
309     ENDIF
310    
311     ! Lecture de l'humidite de l'air juste au dessus du sol:
312    
313 guez 43 ierr = NF90_INQ_VARID (nid, "QS", nvarid)
314     IF (ierr.NE.NF90_NOERR) THEN
315     PRINT *, 'phyetat0: Le champ <QS> est absent'
316     PRINT *, ' Mais je vais essayer de lire QS**'
317 guez 3 DO nsrf = 1, nbsrf
318     IF (nsrf.GT.99) THEN
319 guez 43 PRINT *, "Trop de sous-mailles"
320 guez 3 stop 1
321     ENDIF
322     WRITE(str2,'(i2.2)') nsrf
323 guez 43 ierr = NF90_INQ_VARID (nid, "QS"//str2, nvarid)
324     IF (ierr.NE.NF90_NOERR) THEN
325     PRINT *, "phyetat0: Le champ <QS"//str2//"> est absent"
326 guez 3 stop 1
327     ENDIF
328     ierr = NF_GET_VAR_REAL(nid, nvarid, qsurf(1,nsrf))
329 guez 43 IF (ierr.NE.NF90_NOERR) THEN
330     PRINT *, "phyetat0: Lecture echouee pour <QS"//str2//">"
331 guez 3 stop 1
332     ENDIF
333     xmin = 1.0E+20
334     xmax = -1.0E+20
335     DO i = 1, klon
336     xmin = MIN(qsurf(i,nsrf),xmin)
337     xmax = MAX(qsurf(i,nsrf),xmax)
338     ENDDO
339 guez 43 PRINT *,'Humidite pres du sol QS**:', nsrf, xmin, xmax
340 guez 3 ENDDO
341     ELSE
342 guez 43 PRINT *, 'phyetat0: Le champ <QS> est present'
343     PRINT *, ' J ignore donc les autres humidites QS**'
344     call nf95_get_var(nid, nvarid, qsurf(:,1))
345 guez 3 xmin = 1.0E+20
346     xmax = -1.0E+20
347     DO i = 1, klon
348     xmin = MIN(qsurf(i,1),xmin)
349     xmax = MAX(qsurf(i,1),xmax)
350     ENDDO
351 guez 43 PRINT *,'Humidite pres du sol <QS>', xmin, xmax
352 guez 3 DO nsrf = 2, nbsrf
353     DO i = 1, klon
354     qsurf(i,nsrf) = qsurf(i,1)
355     ENDDO
356     ENDDO
357     ENDIF
358    
359     ! Eau dans le sol (pour le modele de sol "bucket")
360    
361 guez 43 ierr = NF90_INQ_VARID(nid, "QSOL", nvarid)
362     IF (ierr == NF90_NOERR) THEN
363     call nf95_get_var(nid, nvarid, qsol)
364 guez 3 else
365 guez 43 PRINT *, 'phyetat0: Le champ <QSOL> est absent'
366     PRINT *, ' Valeur par defaut nulle'
367     qsol = 0.
368 guez 3 ENDIF
369     xmin = 1.0E+20
370     xmax = -1.0E+20
371     DO i = 1, klon
372     xmin = MIN(qsol(i),xmin)
373     xmax = MAX(qsol(i),xmax)
374     ENDDO
375 guez 43 PRINT *,'Eau dans le sol (mm) <QSOL>', xmin, xmax
376 guez 3
377     ! Lecture de neige au sol:
378    
379 guez 43 ierr = NF90_INQ_VARID (nid, "SNOW", nvarid)
380     IF (ierr.NE.NF90_NOERR) THEN
381     PRINT *, 'phyetat0: Le champ <SNOW> est absent'
382     PRINT *, ' Mais je vais essayer de lire SNOW**'
383 guez 3 DO nsrf = 1, nbsrf
384     IF (nsrf.GT.99) THEN
385 guez 43 PRINT *, "Trop de sous-mailles"
386 guez 3 stop 1
387     ENDIF
388     WRITE(str2,'(i2.2)') nsrf
389 guez 43 ierr = NF90_INQ_VARID (nid, "SNOW"//str2, nvarid)
390     IF (ierr.NE.NF90_NOERR) THEN
391     PRINT *, "phyetat0: Le champ <SNOW"//str2//"> est absent"
392 guez 3 stop 1
393     ENDIF
394     ierr = NF_GET_VAR_REAL(nid, nvarid, snow(1,nsrf))
395 guez 43 IF (ierr.NE.NF90_NOERR) THEN
396     PRINT *, "phyetat0: Lecture echouee pour <SNOW"//str2//">"
397 guez 3 stop 1
398     ENDIF
399     xmin = 1.0E+20
400     xmax = -1.0E+20
401     DO i = 1, klon
402     xmin = MIN(snow(i,nsrf),xmin)
403     xmax = MAX(snow(i,nsrf),xmax)
404     ENDDO
405 guez 43 PRINT *,'Neige du sol SNOW**:', nsrf, xmin, xmax
406 guez 3 ENDDO
407     ELSE
408 guez 43 PRINT *, 'phyetat0: Le champ <SNOW> est present'
409     PRINT *, ' J ignore donc les autres neiges SNOW**'
410     call nf95_get_var(nid, nvarid, snow(:,1))
411 guez 3 xmin = 1.0E+20
412     xmax = -1.0E+20
413     DO i = 1, klon
414     xmin = MIN(snow(i,1),xmin)
415     xmax = MAX(snow(i,1),xmax)
416     ENDDO
417 guez 43 PRINT *,'Neige du sol <SNOW>', xmin, xmax
418 guez 3 DO nsrf = 2, nbsrf
419     DO i = 1, klon
420     snow(i,nsrf) = snow(i,1)
421     ENDDO
422     ENDDO
423     ENDIF
424    
425     ! Lecture de albedo au sol:
426    
427 guez 43 ierr = NF90_INQ_VARID (nid, "ALBE", nvarid)
428     IF (ierr.NE.NF90_NOERR) THEN
429     PRINT *, 'phyetat0: Le champ <ALBE> est absent'
430     PRINT *, ' Mais je vais essayer de lire ALBE**'
431 guez 3 DO nsrf = 1, nbsrf
432     IF (nsrf.GT.99) THEN
433 guez 43 PRINT *, "Trop de sous-mailles"
434 guez 3 stop 1
435     ENDIF
436     WRITE(str2,'(i2.2)') nsrf
437 guez 43 ierr = NF90_INQ_VARID (nid, "ALBE"//str2, nvarid)
438     IF (ierr.NE.NF90_NOERR) THEN
439     PRINT *, "phyetat0: Le champ <ALBE"//str2//"> est absent"
440 guez 3 stop 1
441     ENDIF
442     ierr = NF_GET_VAR_REAL(nid, nvarid, albe(1,nsrf))
443 guez 43 IF (ierr.NE.NF90_NOERR) THEN
444     PRINT *, "phyetat0: Lecture echouee pour <ALBE"//str2//">"
445 guez 3 stop 1
446     ENDIF
447     xmin = 1.0E+20
448     xmax = -1.0E+20
449     DO i = 1, klon
450     xmin = MIN(albe(i,nsrf),xmin)
451     xmax = MAX(albe(i,nsrf),xmax)
452     ENDDO
453 guez 43 PRINT *,'Albedo du sol ALBE**:', nsrf, xmin, xmax
454 guez 3 ENDDO
455     ELSE
456 guez 43 PRINT *, 'phyetat0: Le champ <ALBE> est present'
457     PRINT *, ' J ignore donc les autres ALBE**'
458     call nf95_get_var(nid, nvarid, albe(:,1))
459 guez 3 xmin = 1.0E+20
460     xmax = -1.0E+20
461     DO i = 1, klon
462     xmin = MIN(albe(i,1),xmin)
463     xmax = MAX(albe(i,1),xmax)
464     ENDDO
465 guez 43 PRINT *,'Neige du sol <ALBE>', xmin, xmax
466 guez 3 DO nsrf = 2, nbsrf
467     DO i = 1, klon
468     albe(i,nsrf) = albe(i,1)
469     ENDDO
470     ENDDO
471     ENDIF
472    
473    
474     ! Lecture de albedo au sol LW:
475    
476 guez 43 ierr = NF90_INQ_VARID (nid, "ALBLW", nvarid)
477     IF (ierr.NE.NF90_NOERR) THEN
478     PRINT *, 'phyetat0: Le champ <ALBLW> est absent'
479     ! PRINT *, ' Mais je vais essayer de lire ALBLW**'
480     PRINT *, ' Mais je vais prendre ALBE**'
481 guez 3 DO nsrf = 1, nbsrf
482     DO i = 1, klon
483     alblw(i,nsrf) = albe(i,nsrf)
484     ENDDO
485     ENDDO
486     ELSE
487 guez 43 PRINT *, 'phyetat0: Le champ <ALBLW> est present'
488     PRINT *, ' J ignore donc les autres ALBLW**'
489     call nf95_get_var(nid, nvarid, alblw(:,1))
490 guez 3 xmin = 1.0E+20
491     xmax = -1.0E+20
492     DO i = 1, klon
493     xmin = MIN(alblw(i,1),xmin)
494     xmax = MAX(alblw(i,1),xmax)
495     ENDDO
496 guez 43 PRINT *,'Neige du sol <ALBLW>', xmin, xmax
497 guez 3 DO nsrf = 2, nbsrf
498     DO i = 1, klon
499     alblw(i,nsrf) = alblw(i,1)
500     ENDDO
501     ENDDO
502     ENDIF
503    
504     ! Lecture de evaporation:
505    
506 guez 43 ierr = NF90_INQ_VARID (nid, "EVAP", nvarid)
507     IF (ierr.NE.NF90_NOERR) THEN
508     PRINT *, 'phyetat0: Le champ <EVAP> est absent'
509     PRINT *, ' Mais je vais essayer de lire EVAP**'
510 guez 3 DO nsrf = 1, nbsrf
511     IF (nsrf.GT.99) THEN
512 guez 43 PRINT *, "Trop de sous-mailles"
513 guez 3 stop 1
514     ENDIF
515     WRITE(str2,'(i2.2)') nsrf
516 guez 43 ierr = NF90_INQ_VARID (nid, "EVAP"//str2, nvarid)
517     IF (ierr.NE.NF90_NOERR) THEN
518     PRINT *, "phyetat0: Le champ <EVAP"//str2//"> est absent"
519 guez 3 stop 1
520     ENDIF
521     ierr = NF_GET_VAR_REAL(nid, nvarid, evap(1,nsrf))
522 guez 43 IF (ierr.NE.NF90_NOERR) THEN
523     PRINT *, "phyetat0: Lecture echouee pour <EVAP"//str2//">"
524 guez 3 stop 1
525     ENDIF
526     xmin = 1.0E+20
527     xmax = -1.0E+20
528     DO i = 1, klon
529     xmin = MIN(evap(i,nsrf),xmin)
530     xmax = MAX(evap(i,nsrf),xmax)
531     ENDDO
532 guez 43 PRINT *,'evap du sol EVAP**:', nsrf, xmin, xmax
533 guez 3 ENDDO
534     ELSE
535 guez 43 PRINT *, 'phyetat0: Le champ <EVAP> est present'
536     PRINT *, ' J ignore donc les autres EVAP**'
537     call nf95_get_var(nid, nvarid, evap(:,1))
538 guez 3 xmin = 1.0E+20
539     xmax = -1.0E+20
540     DO i = 1, klon
541     xmin = MIN(evap(i,1),xmin)
542     xmax = MAX(evap(i,1),xmax)
543     ENDDO
544 guez 43 PRINT *,'Evap du sol <EVAP>', xmin, xmax
545 guez 3 DO nsrf = 2, nbsrf
546     DO i = 1, klon
547     evap(i,nsrf) = evap(i,1)
548     ENDDO
549     ENDDO
550     ENDIF
551    
552     ! Lecture precipitation liquide:
553    
554 guez 43 ierr = NF90_INQ_VARID (nid, "rain_f", nvarid)
555     IF (ierr.NE.NF90_NOERR) THEN
556     PRINT *, 'phyetat0: Le champ <rain_f> est absent'
557 guez 3 stop 1
558     ENDIF
559     ierr = NF_GET_VAR_REAL(nid, nvarid, rain_fall)
560 guez 43 IF (ierr.NE.NF90_NOERR) THEN
561     PRINT *, 'phyetat0: Lecture echouee pour <rain_f>'
562 guez 3 stop 1
563     ENDIF
564     xmin = 1.0E+20
565     xmax = -1.0E+20
566     DO i = 1, klon
567     xmin = MIN(rain_fall(i),xmin)
568     xmax = MAX(rain_fall(i),xmax)
569     ENDDO
570 guez 43 PRINT *,'Precipitation liquide rain_f:', xmin, xmax
571 guez 3
572     ! Lecture precipitation solide:
573    
574 guez 43 ierr = NF90_INQ_VARID (nid, "snow_f", nvarid)
575     IF (ierr.NE.NF90_NOERR) THEN
576     PRINT *, 'phyetat0: Le champ <snow_f> est absent'
577 guez 3 stop 1
578     ENDIF
579     ierr = NF_GET_VAR_REAL(nid, nvarid, snow_fall)
580 guez 43 IF (ierr.NE.NF90_NOERR) THEN
581     PRINT *, 'phyetat0: Lecture echouee pour <snow_f>'
582 guez 3 stop 1
583     ENDIF
584     xmin = 1.0E+20
585     xmax = -1.0E+20
586     DO i = 1, klon
587     xmin = MIN(snow_fall(i),xmin)
588     xmax = MAX(snow_fall(i),xmax)
589     ENDDO
590 guez 43 PRINT *,'Precipitation solide snow_f:', xmin, xmax
591 guez 3
592     ! Lecture rayonnement solaire au sol:
593    
594 guez 43 ierr = NF90_INQ_VARID (nid, "solsw", nvarid)
595     IF (ierr.NE.NF90_NOERR) THEN
596     PRINT *, 'phyetat0: Le champ <solsw> est absent'
597     PRINT *, 'mis a zero'
598 guez 3 solsw = 0.
599     ELSE
600 guez 43 call nf95_get_var(nid, nvarid, solsw)
601 guez 3 ENDIF
602     xmin = 1.0E+20
603     xmax = -1.0E+20
604     DO i = 1, klon
605     xmin = MIN(solsw(i),xmin)
606     xmax = MAX(solsw(i),xmax)
607     ENDDO
608 guez 43 PRINT *,'Rayonnement solaire au sol solsw:', xmin, xmax
609 guez 3
610     ! Lecture rayonnement IF au sol:
611    
612 guez 43 ierr = NF90_INQ_VARID (nid, "sollw", nvarid)
613     IF (ierr.NE.NF90_NOERR) THEN
614     PRINT *, 'phyetat0: Le champ <sollw> est absent'
615     PRINT *, 'mis a zero'
616 guez 3 sollw = 0.
617     ELSE
618 guez 43 call nf95_get_var(nid, nvarid, sollw)
619 guez 3 ENDIF
620     xmin = 1.0E+20
621     xmax = -1.0E+20
622     DO i = 1, klon
623     xmin = MIN(sollw(i),xmin)
624     xmax = MAX(sollw(i),xmax)
625     ENDDO
626 guez 43 PRINT *,'Rayonnement IF au sol sollw:', xmin, xmax
627 guez 3
628    
629     ! Lecture derive des flux:
630    
631 guez 43 ierr = NF90_INQ_VARID (nid, "fder", nvarid)
632     IF (ierr.NE.NF90_NOERR) THEN
633     PRINT *, 'phyetat0: Le champ <fder> est absent'
634     PRINT *, 'mis a zero'
635 guez 3 fder = 0.
636     ELSE
637 guez 43 call nf95_get_var(nid, nvarid, fder)
638 guez 3 ENDIF
639     xmin = 1.0E+20
640     xmax = -1.0E+20
641     DO i = 1, klon
642     xmin = MIN(fder(i),xmin)
643     xmax = MAX(fder(i),xmax)
644     ENDDO
645 guez 43 PRINT *,'Derive des flux fder:', xmin, xmax
646 guez 3
647    
648     ! Lecture du rayonnement net au sol:
649    
650 guez 43 ierr = NF90_INQ_VARID (nid, "RADS", nvarid)
651     IF (ierr.NE.NF90_NOERR) THEN
652     PRINT *, 'phyetat0: Le champ <RADS> est absent'
653 guez 3 stop 1
654     ENDIF
655     ierr = NF_GET_VAR_REAL(nid, nvarid, radsol)
656 guez 43 IF (ierr.NE.NF90_NOERR) THEN
657     PRINT *, 'phyetat0: Lecture echouee pour <RADS>'
658 guez 3 stop 1
659     ENDIF
660     xmin = 1.0E+20
661     xmax = -1.0E+20
662     DO i = 1, klon
663     xmin = MIN(radsol(i),xmin)
664     xmax = MAX(radsol(i),xmax)
665     ENDDO
666 guez 43 PRINT *,'Rayonnement net au sol radsol:', xmin, xmax
667 guez 3
668     ! Lecture de la longueur de rugosite
669    
670    
671 guez 43 ierr = NF90_INQ_VARID (nid, "RUG", nvarid)
672     IF (ierr.NE.NF90_NOERR) THEN
673     PRINT *, 'phyetat0: Le champ <RUG> est absent'
674     PRINT *, ' Mais je vais essayer de lire RUG**'
675 guez 3 DO nsrf = 1, nbsrf
676     IF (nsrf.GT.99) THEN
677 guez 43 PRINT *, "Trop de sous-mailles"
678 guez 3 stop 1
679     ENDIF
680     WRITE(str2,'(i2.2)') nsrf
681 guez 43 ierr = NF90_INQ_VARID (nid, "RUG"//str2, nvarid)
682     IF (ierr.NE.NF90_NOERR) THEN
683     PRINT *, "phyetat0: Le champ <RUG"//str2//"> est absent"
684 guez 3 stop 1
685     ENDIF
686     ierr = NF_GET_VAR_REAL(nid, nvarid, frugs(1,nsrf))
687 guez 43 IF (ierr.NE.NF90_NOERR) THEN
688     PRINT *, "phyetat0: Lecture echouee pour <RUG"//str2//">"
689 guez 3 stop 1
690     ENDIF
691     xmin = 1.0E+20
692     xmax = -1.0E+20
693     DO i = 1, klon
694     xmin = MIN(frugs(i,nsrf),xmin)
695     xmax = MAX(frugs(i,nsrf),xmax)
696     ENDDO
697 guez 43 PRINT *,'rugosite du sol RUG**:', nsrf, xmin, xmax
698 guez 3 ENDDO
699     ELSE
700 guez 43 PRINT *, 'phyetat0: Le champ <RUG> est present'
701     PRINT *, ' J ignore donc les autres RUG**'
702     call nf95_get_var(nid, nvarid, frugs(:,1))
703 guez 3 xmin = 1.0E+20
704     xmax = -1.0E+20
705     DO i = 1, klon
706     xmin = MIN(frugs(i,1),xmin)
707     xmax = MAX(frugs(i,1),xmax)
708     ENDDO
709 guez 43 PRINT *,'rugosite <RUG>', xmin, xmax
710 guez 3 DO nsrf = 2, nbsrf
711     DO i = 1, klon
712     frugs(i,nsrf) = frugs(i,1)
713     ENDDO
714     ENDDO
715     ENDIF
716    
717    
718     ! Lecture de l'age de la neige:
719    
720 guez 43 ierr = NF90_INQ_VARID (nid, "AGESNO", nvarid)
721     IF (ierr.NE.NF90_NOERR) THEN
722     PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
723     PRINT *, ' Mais je vais essayer de lire AGESNO**'
724 guez 3 DO nsrf = 1, nbsrf
725     IF (nsrf.GT.99) THEN
726 guez 43 PRINT *, "Trop de sous-mailles"
727 guez 3 stop 1
728     ENDIF
729     WRITE(str2,'(i2.2)') nsrf
730 guez 43 ierr = NF90_INQ_VARID (nid, "AGESNO"//str2, nvarid)
731     IF (ierr.NE.NF90_NOERR) THEN
732     PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
733 guez 3 agesno = 50.0
734     ENDIF
735     ierr = NF_GET_VAR_REAL(nid, nvarid, agesno(1,nsrf))
736 guez 43 IF (ierr.NE.NF90_NOERR) THEN
737     PRINT *, "phyetat0: Lecture echouee pour <AGESNO"//str2//">"
738 guez 3 stop 1
739     ENDIF
740     xmin = 1.0E+20
741     xmax = -1.0E+20
742     DO i = 1, klon
743     xmin = MIN(agesno(i,nsrf),xmin)
744     xmax = MAX(agesno(i,nsrf),xmax)
745     ENDDO
746 guez 43 PRINT *,'Age de la neige AGESNO**:', nsrf, xmin, xmax
747 guez 3 ENDDO
748     ELSE
749 guez 43 PRINT *, 'phyetat0: Le champ <AGESNO> est present'
750     PRINT *, ' J ignore donc les autres AGESNO**'
751     call nf95_get_var(nid, nvarid, agesno(:,1))
752 guez 3 xmin = 1.0E+20
753     xmax = -1.0E+20
754     DO i = 1, klon
755     xmin = MIN(agesno(i,1),xmin)
756     xmax = MAX(agesno(i,1),xmax)
757     ENDDO
758 guez 43 PRINT *,'Age de la neige <AGESNO>', xmin, xmax
759 guez 3 DO nsrf = 2, nbsrf
760     DO i = 1, klon
761     agesno(i,nsrf) = agesno(i,1)
762     ENDDO
763     ENDDO
764     ENDIF
765    
766    
767 guez 43 ierr = NF90_INQ_VARID (nid, "ZMEA", nvarid)
768     IF (ierr.NE.NF90_NOERR) THEN
769     PRINT *, 'phyetat0: Le champ <ZMEA> est absent'
770 guez 3 stop 1
771     ENDIF
772     ierr = NF_GET_VAR_REAL(nid, nvarid, zmea)
773 guez 43 IF (ierr.NE.NF90_NOERR) THEN
774     PRINT *, 'phyetat0: Lecture echouee pour <ZMEA>'
775 guez 3 stop 1
776     ENDIF
777     xmin = 1.0E+20
778     xmax = -1.0E+20
779     DO i = 1, klon
780     xmin = MIN(zmea(i),xmin)
781     xmax = MAX(zmea(i),xmax)
782     ENDDO
783 guez 43 PRINT *,'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
784 guez 3
785    
786 guez 43 ierr = NF90_INQ_VARID (nid, "ZSTD", nvarid)
787     IF (ierr.NE.NF90_NOERR) THEN
788     PRINT *, 'phyetat0: Le champ <ZSTD> est absent'
789 guez 3 stop 1
790     ENDIF
791     ierr = NF_GET_VAR_REAL(nid, nvarid, zstd)
792 guez 43 IF (ierr.NE.NF90_NOERR) THEN
793     PRINT *, 'phyetat0: Lecture echouee pour <ZSTD>'
794 guez 3 stop 1
795     ENDIF
796     xmin = 1.0E+20
797     xmax = -1.0E+20
798     DO i = 1, klon
799     xmin = MIN(zstd(i),xmin)
800     xmax = MAX(zstd(i),xmax)
801     ENDDO
802 guez 43 PRINT *,'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
803 guez 3
804    
805 guez 43 ierr = NF90_INQ_VARID (nid, "ZSIG", nvarid)
806     IF (ierr.NE.NF90_NOERR) THEN
807     PRINT *, 'phyetat0: Le champ <ZSIG> est absent'
808 guez 3 stop 1
809     ENDIF
810     ierr = NF_GET_VAR_REAL(nid, nvarid, zsig)
811 guez 43 IF (ierr.NE.NF90_NOERR) THEN
812     PRINT *, 'phyetat0: Lecture echouee pour <ZSIG>'
813 guez 3 stop 1
814     ENDIF
815     xmin = 1.0E+20
816     xmax = -1.0E+20
817     DO i = 1, klon
818     xmin = MIN(zsig(i),xmin)
819     xmax = MAX(zsig(i),xmax)
820     ENDDO
821 guez 43 PRINT *,'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
822 guez 3
823    
824 guez 43 ierr = NF90_INQ_VARID (nid, "ZGAM", nvarid)
825     IF (ierr.NE.NF90_NOERR) THEN
826     PRINT *, 'phyetat0: Le champ <ZGAM> est absent'
827 guez 3 stop 1
828     ENDIF
829     ierr = NF_GET_VAR_REAL(nid, nvarid, zgam)
830 guez 43 IF (ierr.NE.NF90_NOERR) THEN
831     PRINT *, 'phyetat0: Lecture echouee pour <ZGAM>'
832 guez 3 stop 1
833     ENDIF
834     xmin = 1.0E+20
835     xmax = -1.0E+20
836     DO i = 1, klon
837     xmin = MIN(zgam(i),xmin)
838     xmax = MAX(zgam(i),xmax)
839     ENDDO
840 guez 43 PRINT *,'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
841 guez 3
842    
843 guez 43 ierr = NF90_INQ_VARID (nid, "ZTHE", nvarid)
844     IF (ierr.NE.NF90_NOERR) THEN
845     PRINT *, 'phyetat0: Le champ <ZTHE> est absent'
846 guez 3 stop 1
847     ENDIF
848     ierr = NF_GET_VAR_REAL(nid, nvarid, zthe)
849 guez 43 IF (ierr.NE.NF90_NOERR) THEN
850     PRINT *, 'phyetat0: Lecture echouee pour <ZTHE>'
851 guez 3 stop 1
852     ENDIF
853     xmin = 1.0E+20
854     xmax = -1.0E+20
855     DO i = 1, klon
856     xmin = MIN(zthe(i),xmin)
857     xmax = MAX(zthe(i),xmax)
858     ENDDO
859 guez 43 PRINT *,'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
860 guez 3
861    
862 guez 43 ierr = NF90_INQ_VARID (nid, "ZPIC", nvarid)
863     IF (ierr.NE.NF90_NOERR) THEN
864     PRINT *, 'phyetat0: Le champ <ZPIC> est absent'
865 guez 3 stop 1
866     ENDIF
867     ierr = NF_GET_VAR_REAL(nid, nvarid, zpic)
868 guez 43 IF (ierr.NE.NF90_NOERR) THEN
869     PRINT *, 'phyetat0: Lecture echouee pour <ZPIC>'
870 guez 3 stop 1
871     ENDIF
872     xmin = 1.0E+20
873     xmax = -1.0E+20
874     DO i = 1, klon
875     xmin = MIN(zpic(i),xmin)
876     xmax = MAX(zpic(i),xmax)
877     ENDDO
878 guez 43 PRINT *,'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
879 guez 3
880 guez 43 ierr = NF90_INQ_VARID (nid, "ZVAL", nvarid)
881     IF (ierr.NE.NF90_NOERR) THEN
882     PRINT *, 'phyetat0: Le champ <ZVAL> est absent'
883 guez 3 stop 1
884     ENDIF
885     ierr = NF_GET_VAR_REAL(nid, nvarid, zval)
886 guez 43 IF (ierr.NE.NF90_NOERR) THEN
887     PRINT *, 'phyetat0: Lecture echouee pour <ZVAL>'
888 guez 3 stop 1
889     ENDIF
890     xmin = 1.0E+20
891     xmax = -1.0E+20
892     DO i = 1, klon
893     xmin = MIN(zval(i),xmin)
894     xmax = MAX(zval(i),xmax)
895     ENDDO
896 guez 43 PRINT *,'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
897 guez 3
898     ancien_ok = .TRUE.
899    
900 guez 43 ierr = NF90_INQ_VARID (nid, "TANCIEN", nvarid)
901     IF (ierr.NE.NF90_NOERR) THEN
902     PRINT *, "phyetat0: Le champ <TANCIEN> est absent"
903     PRINT *, "Depart legerement fausse. Mais je continue"
904 guez 3 ancien_ok = .FALSE.
905     ELSE
906 guez 43 call nf95_get_var(nid, nvarid, t_ancien)
907 guez 3 ENDIF
908    
909 guez 43 ierr = NF90_INQ_VARID (nid, "QANCIEN", nvarid)
910     IF (ierr.NE.NF90_NOERR) THEN
911     PRINT *, "phyetat0: Le champ <QANCIEN> est absent"
912     PRINT *, "Depart legerement fausse. Mais je continue"
913 guez 3 ancien_ok = .FALSE.
914     ELSE
915 guez 43 call nf95_get_var(nid, nvarid, q_ancien)
916 guez 3 ENDIF
917    
918 guez 43 ierr = NF90_INQ_VARID (nid, "CLWCON", nvarid)
919     IF (ierr.NE.NF90_NOERR) THEN
920     PRINT *, "phyetat0: Le champ CLWCON est absent"
921     PRINT *, "Depart legerement fausse. Mais je continue"
922 guez 3 clwcon = 0.
923     ELSE
924 guez 43 call nf95_get_var(nid, nvarid, clwcon)
925 guez 3 ENDIF
926     xmin = 1.0E+20
927     xmax = -1.0E+20
928     xmin = MINval(clwcon)
929     xmax = MAXval(clwcon)
930 guez 43 PRINT *,'Eau liquide convective (ecart-type) clwcon:', xmin, xmax
931 guez 3
932 guez 43 ierr = NF90_INQ_VARID (nid, "RNEBCON", nvarid)
933     IF (ierr.NE.NF90_NOERR) THEN
934     PRINT *, "phyetat0: Le champ RNEBCON est absent"
935     PRINT *, "Depart legerement fausse. Mais je continue"
936 guez 3 rnebcon = 0.
937     ELSE
938 guez 43 call nf95_get_var(nid, nvarid, rnebcon)
939 guez 3 ENDIF
940     xmin = 1.0E+20
941     xmax = -1.0E+20
942     xmin = MINval(rnebcon)
943     xmax = MAXval(rnebcon)
944 guez 43 PRINT *,'Nebulosite convective (ecart-type) rnebcon:', xmin, xmax
945 guez 3
946    
947 guez 43 ierr = NF90_INQ_VARID (nid, "QANCIEN", nvarid)
948     IF (ierr.NE.NF90_NOERR) THEN
949     PRINT *, "phyetat0: Le champ <QANCIEN> est absent"
950     PRINT *, "Depart legerement fausse. Mais je continue"
951 guez 3 ancien_ok = .FALSE.
952     ELSE
953 guez 43 call nf95_get_var(nid, nvarid, q_ancien)
954 guez 3 ENDIF
955    
956     ! Lecture ratqs
957    
958 guez 43 ierr = NF90_INQ_VARID (nid, "RATQS", nvarid)
959     IF (ierr.NE.NF90_NOERR) THEN
960     PRINT *, "phyetat0: Le champ <RATQS> est absent"
961     PRINT *, "Depart legerement fausse. Mais je continue"
962 guez 3 ratqs = 0.
963     ELSE
964 guez 43 call nf95_get_var(nid, nvarid, ratqs)
965 guez 3 ENDIF
966     xmin = 1.0E+20
967     xmax = -1.0E+20
968     xmin = MINval(ratqs)
969     xmax = MAXval(ratqs)
970 guez 43 PRINT *,'(ecart-type) ratqs:', xmin, xmax
971 guez 3
972     ! Lecture run_off_lic_0
973    
974 guez 43 ierr = NF90_INQ_VARID (nid, "RUNOFFLIC0", nvarid)
975     IF (ierr.NE.NF90_NOERR) THEN
976     PRINT *, "phyetat0: Le champ <RUNOFFLIC0> est absent"
977     PRINT *, "Depart legerement fausse. Mais je continue"
978 guez 3 run_off_lic_0 = 0.
979     ELSE
980 guez 43 call nf95_get_var(nid, nvarid, run_off_lic_0)
981 guez 3 ENDIF
982     xmin = 1.0E+20
983     xmax = -1.0E+20
984     xmin = MINval(run_off_lic_0)
985     xmax = MAXval(run_off_lic_0)
986 guez 43 PRINT *,'(ecart-type) run_off_lic_0:', xmin, xmax
987 guez 3
988     ! Fermer le fichier:
989    
990     ierr = NF_CLOSE(nid)
991    
992     END SUBROUTINE phyetat0
993    
994     end module phyetat0_m

  ViewVC Help
Powered by ViewVC 1.1.21