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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 12 - (hide annotations)
Mon Jul 21 16:05:07 2008 UTC (15 years, 10 months ago) by guez
Original Path: trunk/libf/phylmd/phyetat0.f90
File size: 33812 byte(s)
-- Minor modification of input/output:

Created procedure "read_logic". Variables of module "logic" are read
by "read_logic" instead of "conf_gcm". Variable "offline" of module
"conf_gcm" is read from namelist instead of "*.def".

Deleted arguments "dtime", "co2_ppm_etat0", "solaire_etat0",
"tabcntr0" and local variables "radpas", "tab_cntrl" of
"phyetat0". "phyetat0" does not read "controle" in "startphy.nc" any
longer. "phyetat0" now reads global attribute "itau_phy" from
"startphy.nc". "phyredem" does not create variable "controle" in
"startphy.nc" any longer. "phyredem" now writes global attribute
"itau_phy" of "startphy.nc". Deleted argument "tabcntr0" of
"printflag". Removed diagnostic messages written by "printflag" for
comparison of the variable "controle" of "startphy.nc" and the
variables read from "*.def" or namelist input.

-- Removing unwanted functionality:

Removed variable "lunout" from module "iniprint", replaced everywhere
by standard output.

Removed case "ocean == 'couple'" in "clmain", "interfsurf_hq" and
"physiq". Removed procedure "interfoce_cpl".

-- Should not change anything at run time:

Automated creation of graphs in documentation. More documentation on
input files.

Converted Fortran files to free format: "phyredem.f90", "printflag.f90".

Split module "clesphy" into "clesphys" and "clesphys2".

Removed variables "conser", "leapf", "forward", "apphys", "apdiss" and
"statcl" from module "logic". Added arguments "conser" to "advect",
"leapf" to "integrd". Added local variables "forward", "leapf",
"apphys", "conser", "apdiss" in "leapfrog".

Added intent attributes.

Deleted arguments "dtime" of "phyredem", "pdtime" of "flxdtdq", "sh"
of "phytrac", "dt" of "yamada".

Deleted local variables "dtime", "co2_ppm_etat0", "solaire_etat0",
"length", "tabcntr0" in "physiq". Replaced all references to "dtime"
by references to "pdtphys".

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

  ViewVC Help
Powered by ViewVC 1.1.21