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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 13 - (hide annotations)
Fri Jul 25 19:59:34 2008 UTC (15 years, 10 months ago) by guez
Original Path: trunk/libf/phylmd/phyetat0.f90
File size: 32727 byte(s)
-- Minor change of behaviour:

"etat0" does not compute "rugsrel" nor "radpas". Deleted arguments
"radpas" and "rugsrel" of "phyredem". Deleted argument "rugsrel" of
"phyetat0". "startphy.nc" does not contain the variable "RUGSREL". In
"physiq", "rugoro" is set to 0 if not "ok_orodr". The whole program
"etat0_lim" does not use "clesphys2".

-- Minor modification of input/output:

Created subroutine "read_clesphys2". Variables of "clesphys2" are read
in "read_clesphys2" instead of "conf_gcm". "printflag" does not print
variables of "clesphys2".

-- Should not change any result at run time:

References to module "numer_rec" instead of individual modules of
"Numer_rec_Lionel".

Deleted argument "clesphy0" of "calfis", "physiq", "conf_gcm",
"leapfrog", "phyetat0". Deleted variable "clesphy0" in
"gcm". "phyetat0" does not modify variables of "clesphys2".

The program unit "gcm" does not modify "itau_phy".

Added some "intent" attributes.

"regr11_lint" does not call "polint".

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

  ViewVC Help
Powered by ViewVC 1.1.21