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

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

Parent Directory Parent Directory | Revision Log Revision Log


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

  ViewVC Help
Powered by ViewVC 1.1.21