/[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 49 by guez, Wed Aug 24 11:43:14 2011 UTC revision 72 by guez, Tue Jul 23 13:00:07 2013 UTC
# Line 14  contains Line 14  contains
14         qsurf, qsol, snow, albe, alblw, evap, rain_fall, snow_fall, solsw, &         qsurf, qsol, snow, albe, alblw, evap, rain_fall, snow_fall, solsw, &
15         sollw, fder, radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, &         sollw, fder, radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, &
16         zpic, zval, t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, &         zpic, zval, t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, &
17         run_off_lic_0)         run_off_lic_0, sig1, w01)
18    
19      ! From phylmd/phyetat0.F, version 1.4 2005/06/03 10:03:07      ! From phylmd/phyetat0.F, version 1.4 2005/06/03 10:03:07
20      ! Author: Z.X. Li (LMD/CNRS)      ! Author: Z.X. Li (LMD/CNRS)
21      ! Date: 19930818      ! Date: 1993/08/18
22      ! Objet : Lecture de l'état initial pour la physique      ! 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 dimphy, only: zmasq, klev
25      USE dimsoil, ONLY : nsoilmx      USE dimsoil, ONLY : nsoilmx
26      USE temps, ONLY : itau_phy      USE indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
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           nf90_get_var, NF90_NOWRITE           NF90_NOWRITE
29      use netcdf95, only: handle_err, nf95_get_var, nf95_close, NF95_OPEN      use netcdf95, only: handle_err, nf95_get_var, nf95_close, NF95_OPEN, &
30      use dimphy, only: zmasq, klev           nf95_inq_varid
31        USE temps, ONLY : itau_phy
32    
33      CHARACTER(len=*), intent(in):: fichnom      CHARACTER(len=*), intent(in):: fichnom
34        REAL pctsrf(klon, nbsrf)
35      REAL tsol(klon, nbsrf)      REAL tsol(klon, nbsrf)
36      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
37        CHARACTER(len=*), intent(in):: ocean
38      REAL tslab(klon), seaice(klon)      REAL tslab(klon), seaice(klon)
39      REAL qsurf(klon, nbsrf)      REAL qsurf(klon, nbsrf)
40      REAL qsol(klon)      REAL qsol(klon)
# Line 39  contains Line 42  contains
42      REAL albe(klon, nbsrf)      REAL albe(klon, nbsrf)
43      REAL alblw(klon, nbsrf)      REAL alblw(klon, nbsrf)
44      REAL evap(klon, nbsrf)      REAL evap(klon, nbsrf)
45      REAL radsol(klon)      REAL, intent(out):: rain_fall(klon)
     REAL rain_fall(klon)  
46      REAL snow_fall(klon)      REAL snow_fall(klon)
     REAL sollw(klon)  
47      real solsw(klon)      real solsw(klon)
48        REAL, intent(out):: sollw(klon)
49      real fder(klon)      real fder(klon)
50        REAL radsol(klon)
51      REAL frugs(klon, nbsrf)      REAL frugs(klon, nbsrf)
52      REAL agesno(klon, nbsrf)      REAL agesno(klon, nbsrf)
53      REAL zmea(klon)      REAL zmea(klon)
# Line 54  contains Line 57  contains
57      REAL zthe(klon)      REAL zthe(klon)
58      REAL zpic(klon)      REAL zpic(klon)
59      REAL zval(klon)      REAL zval(klon)
     REAL pctsrf(klon, nbsrf)  
     REAL fractint(klon)  
     REAL run_off_lic_0(klon)  
   
60      REAL t_ancien(klon, klev), q_ancien(klon, klev)      REAL t_ancien(klon, klev), q_ancien(klon, klev)
     real rnebcon(klon, klev), clwcon(klon, klev), ratqs(klon, klev)  
61      LOGICAL, intent(out):: ancien_ok      LOGICAL, intent(out):: ancien_ok
62        real rnebcon(klon, klev), ratqs(klon, klev), clwcon(klon, klev)
63        REAL run_off_lic_0(klon)
64        real, intent(out):: sig1(klon, klev) ! section adiabatic updraft
65    
66      CHARACTER(len=*), intent(in):: ocean      real, intent(out):: w01(klon, klev)
67        ! vertical velocity within adiabatic updraft
68    
69        ! Local:
70        REAL fractint(klon)
71      REAL xmin, xmax      REAL xmin, xmax
   
72      INTEGER ncid, varid      INTEGER ncid, varid
73      INTEGER ierr, i, nsrf, isoil      INTEGER ierr, i, nsrf, isoil
74      CHARACTER*7 str7      CHARACTER(len=7) str7
75      CHARACTER*2 str2      CHARACTER(len=2) str2
76    
77      !---------------------------------------------------------------      !---------------------------------------------------------------
78    
79      print *, "Call sequence information: phyetat0"      print *, "Call sequence information: phyetat0"
80    
81      ! Ouvrir le fichier contenant l'etat initial:      ! Fichier contenant l'état initial :
82      print *, 'fichnom = ', fichnom      print *, 'fichnom = ', fichnom
83      call NF95_OPEN(fichnom, NF90_NOWRITE, ncid)      call NF95_OPEN(fichnom, NF90_NOWRITE, ncid)
84    
# Line 84  contains Line 87  contains
87    
88      ! Lecture des latitudes (coordonnees):      ! Lecture des latitudes (coordonnees):
89    
90      ierr = NF90_INQ_VARID(ncid, "latitude", varid)      call NF95_INQ_VARID(ncid, "latitude", varid)
91      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, rlat)
        PRINT *, 'phyetat0: Le champ <latitude> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, rlat)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <latitude>'  
        stop 1  
     ENDIF  
92    
93      ! Lecture des longitudes (coordonnees):      ! Lecture des longitudes (coordonnees):
94    
95      ierr = NF90_INQ_VARID(ncid, "longitude", varid)      call NF95_INQ_VARID(ncid, "longitude", varid)
96      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, rlon)
        PRINT *, 'phyetat0: Le champ <longitude> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, rlon)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <latitude>'  
        stop 1  
     ENDIF  
97    
98      ! Lecture du masque terre mer      ! Lecture du masque terre mer
99    
100      ierr = NF90_INQ_VARID(ncid, "masque", varid)      ierr = NF90_INQ_VARID(ncid, "masque", varid)
101      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
102         call nf95_get_var(ncid, varid, zmasq)         call nf95_get_var(ncid, varid, zmasq)
103      else      else
104         PRINT *, 'phyetat0: Le champ <masque> est absent'         PRINT *, 'phyetat0: Le champ <masque> est absent'
105         PRINT *, 'fichier startphy non compatible avec phyetat0'         PRINT *, 'fichier startphy non compatible avec phyetat0'
        !      stop 1  
106      ENDIF      ENDIF
107      ! Lecture des fractions pour chaque sous-surface      ! Lecture des fractions pour chaque sous-surface
108    
# Line 127  contains Line 113  contains
113      ! fraction de terre      ! fraction de terre
114    
115      ierr = NF90_INQ_VARID(ncid, "FTER", varid)      ierr = NF90_INQ_VARID(ncid, "FTER", varid)
116      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
117         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_ter))         call nf95_get_var(ncid, varid, pctsrf(:, is_ter))
118      else      else
119         PRINT *, 'phyetat0: Le champ <FTER> est absent'         PRINT *, 'phyetat0: Le champ <FTER> est absent'
        !$$$         stop 1  
120      ENDIF      ENDIF
121    
122      ! fraction de glace de terre      ! fraction de glace de terre
123    
124      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)
125      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
126         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_lic))         call nf95_get_var(ncid, varid, pctsrf(:, is_lic))
127      else      else
128         PRINT *, 'phyetat0: Le champ <FLIC> est absent'         PRINT *, 'phyetat0: Le champ <FLIC> est absent'
        !$$$         stop 1  
129      ENDIF      ENDIF
130    
131      ! fraction d'ocean      ! fraction d'ocean
132    
133      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)
134      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
135         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_oce))         call nf95_get_var(ncid, varid, pctsrf(:, is_oce))
136      else      else
137         PRINT *, 'phyetat0: Le champ <FOCE> est absent'         PRINT *, 'phyetat0: Le champ <FOCE> est absent'
        !$$$         stop 1  
138      ENDIF      ENDIF
139    
140      ! fraction glace de mer      ! fraction glace de mer
141    
142      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)
143      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
144         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_sic))         call nf95_get_var(ncid, varid, pctsrf(:, is_sic))
145      else      else
146         PRINT *, 'phyetat0: Le champ <FSIC> est absent'         PRINT *, 'phyetat0: Le champ <FSIC> est absent'
        !$$$         stop 1  
147      ENDIF      ENDIF
148    
149      !  Verification de l'adequation entre le masque et les sous-surfaces      ! Verification de l'adequation entre le masque et les sous-surfaces
150    
151      fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &      fractint = pctsrf(:, is_ter) + pctsrf(:, is_lic)
          + pctsrf(1 : klon, is_lic)  
152      DO i = 1 , klon      DO i = 1 , klon
153         IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN         IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN
154            WRITE(*, *) 'phyetat0: attention fraction terre pas ',  &            WRITE(*, *) 'phyetat0: attention fraction terre pas ', &
155                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
156                 , pctsrf(i, is_lic)                 , pctsrf(i, is_lic)
157         ENDIF         ENDIF
158      END DO      END DO
159      fractint(1 : klon) =  pctsrf(1 : klon, is_oce)  &      fractint = pctsrf(:, is_oce) + pctsrf(:, is_sic)
          + pctsrf(1 : klon, is_sic)  
160      DO i = 1 , klon      DO i = 1 , klon
161         IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN         IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN
162            WRITE(*, *) 'phyetat0 attention fraction ocean pas ',  &            WRITE(*, *) 'phyetat0 attention fraction ocean pas ', &
163                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
164                 , pctsrf(i, is_sic)                 , pctsrf(i, is_sic)
165         ENDIF         ENDIF
# Line 190  contains Line 170  contains
170      ierr = NF90_INQ_VARID(ncid, "TS", varid)      ierr = NF90_INQ_VARID(ncid, "TS", varid)
171      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
172         PRINT *, 'phyetat0 : Le champ <TS> est absent'         PRINT *, 'phyetat0 : Le champ <TS> est absent'
173         PRINT *, '          Mais je vais essayer de lire TS**'         PRINT *, ' Mais je vais essayer de lire TS**'
174         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
175            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
176               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
177               stop 1               stop 1
178            ENDIF            ENDIF
179            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
180            ierr = NF90_INQ_VARID(ncid, "TS"//str2, varid)            call NF95_INQ_VARID(ncid, "TS"//str2, varid)
181            IF (ierr /= NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, tsol(:, nsrf))
              PRINT *, "phyetat0: Le champ <TS"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF90_GET_VAR(ncid, varid, tsol(1, nsrf))  
           IF (ierr /= NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <TS"//str2//">"  
              stop 1  
           ENDIF  
182            xmin = 1.0E+20            xmin = 1.0E+20
183            xmax = -1.0E+20            xmax = -1.0E+20
184            DO i = 1, klon            DO i = 1, klon
# Line 217  contains Line 189  contains
189         ENDDO         ENDDO
190      ELSE      ELSE
191         PRINT *, 'phyetat0: Le champ <TS> est present'         PRINT *, 'phyetat0: Le champ <TS> est present'
192         PRINT *, '          J ignore donc les autres temperatures TS**'         PRINT *, ' J ignore donc les autres temperatures TS**'
193         call nf95_get_var(ncid, varid, tsol(:, 1))         call nf95_get_var(ncid, varid, tsol(:, 1))
194         xmin = 1.0E+20         xmin = 1.0E+20
195         xmax = -1.0E+20         xmax = -1.0E+20
# Line 237  contains Line 209  contains
209    
210      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
211         DO isoil=1, nsoilmx         DO isoil=1, nsoilmx
212            IF (isoil.GT.99 .AND. nsrf.GT.99) THEN            IF (isoil > 99 .AND. nsrf > 99) THEN
213               PRINT *, "Trop de couches ou sous-mailles"               PRINT *, "Trop de couches ou sous-mailles"
214               stop 1               stop 1
215            ENDIF            ENDIF
# Line 245  contains Line 217  contains
217            ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)            ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)
218            IF (ierr /= NF90_NOERR) THEN            IF (ierr /= NF90_NOERR) THEN
219               PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"               PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
220               PRINT *, "          Il prend donc la valeur de surface"               PRINT *, " Il prend donc la valeur de surface"
221               DO i=1, klon               DO i=1, klon
222                  tsoil(i, isoil, nsrf)=tsol(i, nsrf)                  tsoil(i, isoil, nsrf)=tsol(i, nsrf)
223               ENDDO               ENDDO
224            ELSE            ELSE
225               ierr = NF90_GET_VAR(ncid, varid, tsoil(1, isoil, nsrf))               call NF95_GET_VAR(ncid, varid, tsoil(:, isoil, nsrf))
              IF (ierr /= NF90_NOERR) THEN  
                 PRINT *, "Lecture echouee pour <Tsoil"//str7//">"  
                 stop 1  
              ENDIF  
226            ENDIF            ENDIF
227         ENDDO         ENDDO
228      ENDDO      ENDDO
229    
230      !IM "slab" ocean      !IM "slab" ocean
231    
232      ! Lecture de tslab (pour slab ocean seulement):            ! Lecture de tslab (pour slab ocean seulement):
233    
234      IF (ocean .eq. 'slab  ') then      IF (ocean .eq. 'slab ') then
235         ierr = NF90_INQ_VARID(ncid, "TSLAB", varid)         call NF95_INQ_VARID(ncid, "TSLAB", varid)
        IF (ierr /= NF90_NOERR) THEN  
           PRINT *, "phyetat0: Le champ <TSLAB> est absent"  
           stop 1  
        ENDIF  
236         call nf95_get_var(ncid, varid, tslab)         call nf95_get_var(ncid, varid, tslab)
237         xmin = 1.0E+20         xmin = 1.0E+20
238         xmax = -1.0E+20         xmax = -1.0E+20
# Line 280  contains Line 244  contains
244    
245         ! Lecture de seaice (pour slab ocean seulement):         ! Lecture de seaice (pour slab ocean seulement):
246    
247         ierr = NF90_INQ_VARID(ncid, "SEAICE", varid)         call NF95_INQ_VARID(ncid, "SEAICE", varid)
        IF (ierr /= NF90_NOERR) THEN  
           PRINT *, "phyetat0: Le champ <SEAICE> est absent"  
           stop 1  
        ENDIF  
248         call nf95_get_var(ncid, varid, seaice)         call nf95_get_var(ncid, varid, seaice)
249         xmin = 1.0E+20         xmin = 1.0E+20
250         xmax = -1.0E+20         xmax = -1.0E+20
# Line 303  contains Line 263  contains
263      ierr = NF90_INQ_VARID(ncid, "QS", varid)      ierr = NF90_INQ_VARID(ncid, "QS", varid)
264      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
265         PRINT *, 'phyetat0: Le champ <QS> est absent'         PRINT *, 'phyetat0: Le champ <QS> est absent'
266         PRINT *, '          Mais je vais essayer de lire QS**'         PRINT *, ' Mais je vais essayer de lire QS**'
267         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
268            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
269               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
270               stop 1               stop 1
271            ENDIF            ENDIF
272            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
273            ierr = NF90_INQ_VARID(ncid, "QS"//str2, varid)            call NF95_INQ_VARID(ncid, "QS"//str2, varid)
274            IF (ierr /= NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, qsurf(:, nsrf))
              PRINT *, "phyetat0: Le champ <QS"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF90_GET_VAR(ncid, varid, qsurf(1, nsrf))  
           IF (ierr /= NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <QS"//str2//">"  
              stop 1  
           ENDIF  
275            xmin = 1.0E+20            xmin = 1.0E+20
276            xmax = -1.0E+20            xmax = -1.0E+20
277            DO i = 1, klon            DO i = 1, klon
# Line 330  contains Line 282  contains
282         ENDDO         ENDDO
283      ELSE      ELSE
284         PRINT *, 'phyetat0: Le champ <QS> est present'         PRINT *, 'phyetat0: Le champ <QS> est present'
285         PRINT *, '          J ignore donc les autres humidites QS**'         PRINT *, ' J ignore donc les autres humidites QS**'
286         call nf95_get_var(ncid, varid, qsurf(:, 1))         call nf95_get_var(ncid, varid, qsurf(:, 1))
287         xmin = 1.0E+20         xmin = 1.0E+20
288         xmax = -1.0E+20         xmax = -1.0E+20
# Line 349  contains Line 301  contains
301      ! Eau dans le sol (pour le modele de sol "bucket")      ! Eau dans le sol (pour le modele de sol "bucket")
302    
303      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
304      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
305         call nf95_get_var(ncid, varid, qsol)         call nf95_get_var(ncid, varid, qsol)
306      else      else
307         PRINT *, 'phyetat0: Le champ <QSOL> est absent'         PRINT *, 'phyetat0: Le champ <QSOL> est absent'
308         PRINT *, '          Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
309         qsol = 0.         qsol = 0.
310      ENDIF      ENDIF
311      xmin = 1.0E+20      xmin = 1.0E+20
# Line 369  contains Line 321  contains
321      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)
322      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
323         PRINT *, 'phyetat0: Le champ <SNOW> est absent'         PRINT *, 'phyetat0: Le champ <SNOW> est absent'
324         PRINT *, '          Mais je vais essayer de lire SNOW**'         PRINT *, ' Mais je vais essayer de lire SNOW**'
325         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
326            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
327               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
328               stop 1               stop 1
329            ENDIF            ENDIF
330            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
331            ierr = NF90_INQ_VARID(ncid, "SNOW"//str2, varid)            call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)
332            IF (ierr /= NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, snow(:, nsrf))
              PRINT *, "phyetat0: Le champ <SNOW"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF90_GET_VAR(ncid, varid, snow(1, nsrf))  
           IF (ierr /= NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <SNOW"//str2//">"  
              stop 1  
           ENDIF  
333            xmin = 1.0E+20            xmin = 1.0E+20
334            xmax = -1.0E+20            xmax = -1.0E+20
335            DO i = 1, klon            DO i = 1, klon
# Line 396  contains Line 340  contains
340         ENDDO         ENDDO
341      ELSE      ELSE
342         PRINT *, 'phyetat0: Le champ <SNOW> est present'         PRINT *, 'phyetat0: Le champ <SNOW> est present'
343         PRINT *, '          J ignore donc les autres neiges SNOW**'         PRINT *, ' J ignore donc les autres neiges SNOW**'
344         call nf95_get_var(ncid, varid, snow(:, 1))         call nf95_get_var(ncid, varid, snow(:, 1))
345         xmin = 1.0E+20         xmin = 1.0E+20
346         xmax = -1.0E+20         xmax = -1.0E+20
# Line 417  contains Line 361  contains
361      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)
362      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
363         PRINT *, 'phyetat0: Le champ <ALBE> est absent'         PRINT *, 'phyetat0: Le champ <ALBE> est absent'
364         PRINT *, '          Mais je vais essayer de lire ALBE**'         PRINT *, ' Mais je vais essayer de lire ALBE**'
365         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
366            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
367               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
368               stop 1               stop 1
369            ENDIF            ENDIF
370            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
371            ierr = NF90_INQ_VARID(ncid, "ALBE"//str2, varid)            call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)
372            IF (ierr /= NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, albe(:, nsrf))
              PRINT *, "phyetat0: Le champ <ALBE"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF90_GET_VAR(ncid, varid, albe(1, nsrf))  
           IF (ierr /= NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <ALBE"//str2//">"  
              stop 1  
           ENDIF  
373            xmin = 1.0E+20            xmin = 1.0E+20
374            xmax = -1.0E+20            xmax = -1.0E+20
375            DO i = 1, klon            DO i = 1, klon
# Line 444  contains Line 380  contains
380         ENDDO         ENDDO
381      ELSE      ELSE
382         PRINT *, 'phyetat0: Le champ <ALBE> est present'         PRINT *, 'phyetat0: Le champ <ALBE> est present'
383         PRINT *, '          J ignore donc les autres ALBE**'         PRINT *, ' J ignore donc les autres ALBE**'
384         call nf95_get_var(ncid, varid, albe(:, 1))         call nf95_get_var(ncid, varid, albe(:, 1))
385         xmin = 1.0E+20         xmin = 1.0E+20
386         xmax = -1.0E+20         xmax = -1.0E+20
# Line 465  contains Line 401  contains
401      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)
402      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
403         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'
404         !        PRINT *, '          Mais je vais essayer de lire ALBLW**'         ! PRINT *, ' Mais je vais essayer de lire ALBLW**'
405         PRINT *, '          Mais je vais prendre ALBE**'         PRINT *, ' Mais je vais prendre ALBE**'
406         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
407            DO i = 1, klon            DO i = 1, klon
408               alblw(i, nsrf) = albe(i, nsrf)               alblw(i, nsrf) = albe(i, nsrf)
# Line 474  contains Line 410  contains
410         ENDDO         ENDDO
411      ELSE      ELSE
412         PRINT *, 'phyetat0: Le champ <ALBLW> est present'         PRINT *, 'phyetat0: Le champ <ALBLW> est present'
413         PRINT *, '          J ignore donc les autres ALBLW**'         PRINT *, ' J ignore donc les autres ALBLW**'
414         call nf95_get_var(ncid, varid, alblw(:, 1))         call nf95_get_var(ncid, varid, alblw(:, 1))
415         xmin = 1.0E+20         xmin = 1.0E+20
416         xmax = -1.0E+20         xmax = -1.0E+20
# Line 490  contains Line 426  contains
426         ENDDO         ENDDO
427      ENDIF      ENDIF
428    
429      ! Lecture de evaporation:        ! Lecture de evaporation:
430    
431      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)
432      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
433         PRINT *, 'phyetat0: Le champ <EVAP> est absent'         PRINT *, 'phyetat0: Le champ <EVAP> est absent'
434         PRINT *, '          Mais je vais essayer de lire EVAP**'         PRINT *, ' Mais je vais essayer de lire EVAP**'
435         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
436            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
437               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
438               stop 1               stop 1
439            ENDIF            ENDIF
440            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
441            ierr = NF90_INQ_VARID(ncid, "EVAP"//str2, varid)            call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)
442            IF (ierr /= NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, evap(:, nsrf))
              PRINT *, "phyetat0: Le champ <EVAP"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF90_GET_VAR(ncid, varid, evap(1, nsrf))  
           IF (ierr /= NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <EVAP"//str2//">"  
              stop 1  
           ENDIF  
443            xmin = 1.0E+20            xmin = 1.0E+20
444            xmax = -1.0E+20            xmax = -1.0E+20
445            DO i = 1, klon            DO i = 1, klon
# Line 522  contains Line 450  contains
450         ENDDO         ENDDO
451      ELSE      ELSE
452         PRINT *, 'phyetat0: Le champ <EVAP> est present'         PRINT *, 'phyetat0: Le champ <EVAP> est present'
453         PRINT *, '          J ignore donc les autres EVAP**'         PRINT *, ' J ignore donc les autres EVAP**'
454         call nf95_get_var(ncid, varid, evap(:, 1))         call nf95_get_var(ncid, varid, evap(:, 1))
455         xmin = 1.0E+20         xmin = 1.0E+20
456         xmax = -1.0E+20         xmax = -1.0E+20
# Line 540  contains Line 468  contains
468    
469      ! Lecture precipitation liquide:      ! Lecture precipitation liquide:
470    
471      ierr = NF90_INQ_VARID(ncid, "rain_f", varid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
472      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, rain_fall)
        PRINT *, 'phyetat0: Le champ <rain_f> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, rain_fall)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <rain_f>'  
        stop 1  
     ENDIF  
473      xmin = 1.0E+20      xmin = 1.0E+20
474      xmax = -1.0E+20      xmax = -1.0E+20
475      DO i = 1, klon      DO i = 1, klon
# Line 560  contains Line 480  contains
480    
481      ! Lecture precipitation solide:      ! Lecture precipitation solide:
482    
483      ierr = NF90_INQ_VARID(ncid, "snow_f", varid)      call NF95_INQ_VARID(ncid, "snow_f", varid)
484      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, snow_fall)
        PRINT *, 'phyetat0: Le champ <snow_f> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, snow_fall)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <snow_f>'  
        stop 1  
     ENDIF  
485      xmin = 1.0E+20      xmin = 1.0E+20
486      xmax = -1.0E+20      xmax = -1.0E+20
487      DO i = 1, klon      DO i = 1, klon
# Line 606  contains Line 518  contains
518      ELSE      ELSE
519         call nf95_get_var(ncid, varid, sollw)         call nf95_get_var(ncid, varid, sollw)
520      ENDIF      ENDIF
521      xmin = 1.0E+20      PRINT *, 'Rayonnement IF au sol sollw:', minval(sollw), maxval(sollw)
     xmax = -1.0E+20  
     DO i = 1, klon  
        xmin = MIN(sollw(i), xmin)  
        xmax = MAX(sollw(i), xmax)  
     ENDDO  
     PRINT *, 'Rayonnement IF au sol sollw:', xmin, xmax  
522    
523      ! Lecture derive des flux:      ! Lecture derive des flux:
524    
# Line 634  contains Line 540  contains
540    
541      ! Lecture du rayonnement net au sol:      ! Lecture du rayonnement net au sol:
542    
543      ierr = NF90_INQ_VARID(ncid, "RADS", varid)      call NF95_INQ_VARID(ncid, "RADS", varid)
544      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, radsol)
        PRINT *, 'phyetat0: Le champ <RADS> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, radsol)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <RADS>'  
        stop 1  
     ENDIF  
545      xmin = 1.0E+20      xmin = 1.0E+20
546      xmax = -1.0E+20      xmax = -1.0E+20
547      DO i = 1, klon      DO i = 1, klon
# Line 657  contains Line 555  contains
555      ierr = NF90_INQ_VARID(ncid, "RUG", varid)      ierr = NF90_INQ_VARID(ncid, "RUG", varid)
556      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
557         PRINT *, 'phyetat0: Le champ <RUG> est absent'         PRINT *, 'phyetat0: Le champ <RUG> est absent'
558         PRINT *, '          Mais je vais essayer de lire RUG**'         PRINT *, ' Mais je vais essayer de lire RUG**'
559         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
560            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
561               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
562               stop 1               stop 1
563            ENDIF            ENDIF
564            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
565            ierr = NF90_INQ_VARID(ncid, "RUG"//str2, varid)            call NF95_INQ_VARID(ncid, "RUG"//str2, varid)
566            IF (ierr /= NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, frugs(:, nsrf))
              PRINT *, "phyetat0: Le champ <RUG"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF90_GET_VAR(ncid, varid, frugs(1, nsrf))  
           IF (ierr /= NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <RUG"//str2//">"  
              stop 1  
           ENDIF  
567            xmin = 1.0E+20            xmin = 1.0E+20
568            xmax = -1.0E+20            xmax = -1.0E+20
569            DO i = 1, klon            DO i = 1, klon
# Line 684  contains Line 574  contains
574         ENDDO         ENDDO
575      ELSE      ELSE
576         PRINT *, 'phyetat0: Le champ <RUG> est present'         PRINT *, 'phyetat0: Le champ <RUG> est present'
577         PRINT *, '          J ignore donc les autres RUG**'         PRINT *, ' J ignore donc les autres RUG**'
578         call nf95_get_var(ncid, varid, frugs(:, 1))         call nf95_get_var(ncid, varid, frugs(:, 1))
579         xmin = 1.0E+20         xmin = 1.0E+20
580         xmax = -1.0E+20         xmax = -1.0E+20
# Line 705  contains Line 595  contains
595      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)
596      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
597         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
598         PRINT *, '          Mais je vais essayer de lire AGESNO**'         PRINT *, ' Mais je vais essayer de lire AGESNO**'
599         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
600            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
601               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
602               stop 1               stop 1
603            ENDIF            ENDIF
# Line 717  contains Line 607  contains
607               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
608               agesno = 50.0               agesno = 50.0
609            ENDIF            ENDIF
610            ierr = NF90_GET_VAR(ncid, varid, agesno(1, nsrf))            call NF95_GET_VAR(ncid, varid, agesno(:, nsrf))
           IF (ierr /= NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <AGESNO"//str2//">"  
              stop 1  
           ENDIF  
611            xmin = 1.0E+20            xmin = 1.0E+20
612            xmax = -1.0E+20            xmax = -1.0E+20
613            DO i = 1, klon            DO i = 1, klon
# Line 732  contains Line 618  contains
618         ENDDO         ENDDO
619      ELSE      ELSE
620         PRINT *, 'phyetat0: Le champ <AGESNO> est present'         PRINT *, 'phyetat0: Le champ <AGESNO> est present'
621         PRINT *, '          J ignore donc les autres AGESNO**'         PRINT *, ' J ignore donc les autres AGESNO**'
622         call nf95_get_var(ncid, varid, agesno(:, 1))         call nf95_get_var(ncid, varid, agesno(:, 1))
623         xmin = 1.0E+20         xmin = 1.0E+20
624         xmax = -1.0E+20         xmax = -1.0E+20
# Line 748  contains Line 634  contains
634         ENDDO         ENDDO
635      ENDIF      ENDIF
636    
637      ierr = NF90_INQ_VARID(ncid, "ZMEA", varid)      call NF95_INQ_VARID(ncid, "ZMEA", varid)
638      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zmea)
        PRINT *, 'phyetat0: Le champ <ZMEA> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, zmea)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZMEA>'  
        stop 1  
     ENDIF  
639      xmin = 1.0E+20      xmin = 1.0E+20
640      xmax = -1.0E+20      xmax = -1.0E+20
641      DO i = 1, klon      DO i = 1, klon
# Line 766  contains Line 644  contains
644      ENDDO      ENDDO
645      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
646    
647      ierr = NF90_INQ_VARID(ncid, "ZSTD", varid)      call NF95_INQ_VARID(ncid, "ZSTD", varid)
648      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zstd)
        PRINT *, 'phyetat0: Le champ <ZSTD> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, zstd)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZSTD>'  
        stop 1  
     ENDIF  
649      xmin = 1.0E+20      xmin = 1.0E+20
650      xmax = -1.0E+20      xmax = -1.0E+20
651      DO i = 1, klon      DO i = 1, klon
# Line 784  contains Line 654  contains
654      ENDDO      ENDDO
655      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
656    
657      ierr = NF90_INQ_VARID(ncid, "ZSIG", varid)      call NF95_INQ_VARID(ncid, "ZSIG", varid)
658      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zsig)
        PRINT *, 'phyetat0: Le champ <ZSIG> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, zsig)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZSIG>'  
        stop 1  
     ENDIF  
659      xmin = 1.0E+20      xmin = 1.0E+20
660      xmax = -1.0E+20      xmax = -1.0E+20
661      DO i = 1, klon      DO i = 1, klon
# Line 802  contains Line 664  contains
664      ENDDO      ENDDO
665      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
666    
667      ierr = NF90_INQ_VARID(ncid, "ZGAM", varid)      call NF95_INQ_VARID(ncid, "ZGAM", varid)
668      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zgam)
        PRINT *, 'phyetat0: Le champ <ZGAM> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, zgam)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZGAM>'  
        stop 1  
     ENDIF  
669      xmin = 1.0E+20      xmin = 1.0E+20
670      xmax = -1.0E+20      xmax = -1.0E+20
671      DO i = 1, klon      DO i = 1, klon
# Line 820  contains Line 674  contains
674      ENDDO      ENDDO
675      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
676    
677      ierr = NF90_INQ_VARID(ncid, "ZTHE", varid)      call NF95_INQ_VARID(ncid, "ZTHE", varid)
678      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zthe)
        PRINT *, 'phyetat0: Le champ <ZTHE> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, zthe)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZTHE>'  
        stop 1  
     ENDIF  
679      xmin = 1.0E+20      xmin = 1.0E+20
680      xmax = -1.0E+20      xmax = -1.0E+20
681      DO i = 1, klon      DO i = 1, klon
# Line 838  contains Line 684  contains
684      ENDDO      ENDDO
685      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
686    
687      ierr = NF90_INQ_VARID(ncid, "ZPIC", varid)      call NF95_INQ_VARID(ncid, "ZPIC", varid)
688      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zpic)
        PRINT *, 'phyetat0: Le champ <ZPIC> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, zpic)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZPIC>'  
        stop 1  
     ENDIF  
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
# Line 856  contains Line 694  contains
694      ENDDO      ENDDO
695      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
696    
697      ierr = NF90_INQ_VARID(ncid, "ZVAL", varid)      call NF95_INQ_VARID(ncid, "ZVAL", varid)
698      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zval)
        PRINT *, 'phyetat0: Le champ <ZVAL> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, zval)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZVAL>'  
        stop 1  
     ENDIF  
699      xmin = 1.0E+20      xmin = 1.0E+20
700      xmax = -1.0E+20      xmax = -1.0E+20
701      DO i = 1, klon      DO i = 1, klon
# Line 900  contains Line 730  contains
730         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
731         clwcon = 0.         clwcon = 0.
732      ELSE      ELSE
733         call nf95_get_var(ncid, varid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
734           clwcon(:, 2:) = 0.
735      ENDIF      ENDIF
736      xmin = 1.0E+20      xmin = 1.0E+20
737      xmax = -1.0E+20      xmax = -1.0E+20
# Line 914  contains Line 745  contains
745         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
746         rnebcon = 0.         rnebcon = 0.
747      ELSE      ELSE
748         call nf95_get_var(ncid, varid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
749           rnebcon(:, 2:) = 0.
750      ENDIF      ENDIF
751      xmin = 1.0E+20      xmin = 1.0E+20
752      xmax = -1.0E+20      xmax = -1.0E+20
# Line 930  contains Line 762  contains
762         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
763         ratqs = 0.         ratqs = 0.
764      ELSE      ELSE
765         call nf95_get_var(ncid, varid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
766           ratqs(:, 2:) = 0.
767      ENDIF      ENDIF
768      xmin = 1.0E+20      xmin = 1.0E+20
769      xmax = -1.0E+20      xmax = -1.0E+20
# Line 954  contains Line 787  contains
787      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
788      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
789    
790        call nf95_inq_varid(ncid, "sig1", varid)
791        call nf95_get_var(ncid, varid, sig1)
792    
793        call nf95_inq_varid(ncid, "w01", varid)
794        call nf95_get_var(ncid, varid, w01)
795    
796      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
797    
798    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0

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

  ViewVC Help
Powered by ViewVC 1.1.21