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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 15 - (hide annotations)
Fri Aug 1 15:24:12 2008 UTC (15 years, 9 months ago) by guez
Original Path: trunk/libf/phylmd/phyetat0.f90
File size: 32735 byte(s)
-- Minor modification of input/output:

Added variable "Sigma_O3_Royer" to "histday.nc". "ecrit_day" is not
modified in "physiq". Removed variables "pyu1", "pyv1", "ftsol1",
"ftsol2", "ftsol3", "ftsol4", "psrf1", "psrf2", "psrf3", "psrf4"
"mfu", "mfd", "en_u", "en_d", "de_d", "de_u", "coefh" from
"histrac.nc".

Variable "raz_date" of module "conf_gcm_m" has logical type instead of
integer type.

-- Should not change any result at run time:

Modified calls to "IOIPSL_Lionel" procedures because the interfaces of
these procedures have been simplified.

Changed name of variable in module "start_init_orog_m": "masque" to
"mask".

Created a module containing procedure "phyredem".

Removed arguments "punjours", "pdayref" and "ptimestep" of procedure
"iniphysiq".

Renamed procedure "gr_phy_write" to "gr_phy_write_2d". Created
procedure "gr_phy_write_3d".

Removed procedures "ini_undefstd", "moy_undefSTD", "calcul_STDlev",
"calcul_divers".

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

  ViewVC Help
Powered by ViewVC 1.1.21