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

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

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

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

Legend:
Removed from v.43  
changed lines
  Added in v.49

  ViewVC Help
Powered by ViewVC 1.1.21