/[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

trunk/libf/phylmd/phyetat0.f90 revision 49 by guez, Wed Aug 24 11:43:14 2011 UTC trunk/phylmd/phyetat0.f revision 99 by guez, Wed Jul 2 18:39:15 2014 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(pctsrf, tsol, tsoil, tslab, seaice, qsurf, qsol, &
14         qsurf, qsol, snow, albe, alblw, evap, rain_fall, snow_fall, solsw, &         snow, albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, &
15         sollw, fder, radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, &         radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
16         zpic, zval, t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, &         t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, &
17         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      REAL pctsrf(klon, nbsrf)
34      REAL tsol(klon, nbsrf)      REAL tsol(klon, nbsrf)
35      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
36      REAL tslab(klon), seaice(klon)      REAL tslab(klon), seaice(klon)
37      REAL qsurf(klon, nbsrf)      REAL qsurf(klon, nbsrf)
38      REAL qsol(klon)      REAL, intent(out):: qsol(:) ! (klon)
39      REAL snow(klon, nbsrf)      REAL snow(klon, nbsrf)
40      REAL albe(klon, nbsrf)      REAL albe(klon, nbsrf)
41      REAL alblw(klon, nbsrf)      REAL alblw(klon, nbsrf)
42      REAL evap(klon, nbsrf)      REAL evap(klon, nbsrf)
43      REAL radsol(klon)      REAL, intent(out):: rain_fall(klon)
     REAL rain_fall(klon)  
44      REAL snow_fall(klon)      REAL snow_fall(klon)
     REAL sollw(klon)  
45      real solsw(klon)      real solsw(klon)
46        REAL, intent(out):: sollw(klon)
47      real fder(klon)      real fder(klon)
48        REAL radsol(klon)
49      REAL frugs(klon, nbsrf)      REAL frugs(klon, nbsrf)
50      REAL agesno(klon, nbsrf)      REAL agesno(klon, nbsrf)
51      REAL zmea(klon)      REAL zmea(klon)
# Line 54  contains Line 55  contains
55      REAL zthe(klon)      REAL zthe(klon)
56      REAL zpic(klon)      REAL zpic(klon)
57      REAL zval(klon)      REAL zval(klon)
     REAL pctsrf(klon, nbsrf)  
     REAL fractint(klon)  
     REAL run_off_lic_0(klon)  
   
58      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)  
59      LOGICAL, intent(out):: ancien_ok      LOGICAL, intent(out):: ancien_ok
60        real rnebcon(klon, klev), ratqs(klon, klev), clwcon(klon, klev)
61        REAL run_off_lic_0(klon)
62        real, intent(out):: sig1(klon, klev) ! section adiabatic updraft
63    
64      CHARACTER(len=*), intent(in):: ocean      real, intent(out):: w01(klon, klev)
65        ! vertical velocity within adiabatic updraft
66    
67        ! Local:
68        REAL fractint(klon)
69      REAL xmin, xmax      REAL xmin, xmax
   
70      INTEGER ncid, varid      INTEGER ncid, varid
71      INTEGER ierr, i, nsrf, isoil      INTEGER ierr, i, nsrf, isoil
72      CHARACTER*7 str7      CHARACTER(len=7) str7
73      CHARACTER*2 str2      CHARACTER(len=2) str2
74    
75      !---------------------------------------------------------------      !---------------------------------------------------------------
76    
77      print *, "Call sequence information: phyetat0"      print *, "Call sequence information: phyetat0"
78    
79      ! Ouvrir le fichier contenant l'etat initial:      ! Fichier contenant l'état initial :
80      print *, 'fichnom = ', fichnom      call NF95_OPEN("startphy.nc", NF90_NOWRITE, ncid)
     call NF95_OPEN(fichnom, NF90_NOWRITE, ncid)  
81    
82      ierr = nf90_get_att(ncid, 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, ncid, 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(ncid, "latitude", varid)      call NF95_INQ_VARID(ncid, "latitude", varid)
88      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  
89    
90      ! Lecture des longitudes (coordonnees):      ! Lecture des longitudes (coordonnees):
91    
92      ierr = NF90_INQ_VARID(ncid, "longitude", varid)      call NF95_INQ_VARID(ncid, "longitude", varid)
93      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  
94    
95      ! Lecture du masque terre mer      ! Lecture du masque terre mer
96    
97      ierr = NF90_INQ_VARID(ncid, "masque", varid)      ierr = NF90_INQ_VARID(ncid, "masque", varid)
98      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
99         call nf95_get_var(ncid, varid, zmasq)         call nf95_get_var(ncid, varid, zmasq)
100      else      else
101         PRINT *, 'phyetat0: Le champ <masque> est absent'         PRINT *, 'phyetat0: Le champ <masque> est absent'
102         PRINT *, 'fichier startphy non compatible avec phyetat0'         PRINT *, 'fichier startphy non compatible avec phyetat0'
        !      stop 1  
103      ENDIF      ENDIF
104      ! Lecture des fractions pour chaque sous-surface      ! Lecture des fractions pour chaque sous-surface
105    
# Line 127  contains Line 110  contains
110      ! fraction de terre      ! fraction de terre
111    
112      ierr = NF90_INQ_VARID(ncid, "FTER", varid)      ierr = NF90_INQ_VARID(ncid, "FTER", varid)
113      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
114         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_ter))         call nf95_get_var(ncid, varid, pctsrf(:, is_ter))
115      else      else
116         PRINT *, 'phyetat0: Le champ <FTER> est absent'         PRINT *, 'phyetat0: Le champ <FTER> est absent'
        !$$$         stop 1  
117      ENDIF      ENDIF
118    
119      ! fraction de glace de terre      ! fraction de glace de terre
120    
121      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)
122      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
123         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_lic))         call nf95_get_var(ncid, varid, pctsrf(:, is_lic))
124      else      else
125         PRINT *, 'phyetat0: Le champ <FLIC> est absent'         PRINT *, 'phyetat0: Le champ <FLIC> est absent'
        !$$$         stop 1  
126      ENDIF      ENDIF
127    
128      ! fraction d'ocean      ! fraction d'ocean
129    
130      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)
131      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
132         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_oce))         call nf95_get_var(ncid, varid, pctsrf(:, is_oce))
133      else      else
134         PRINT *, 'phyetat0: Le champ <FOCE> est absent'         PRINT *, 'phyetat0: Le champ <FOCE> est absent'
        !$$$         stop 1  
135      ENDIF      ENDIF
136    
137      ! fraction glace de mer      ! fraction glace de mer
138    
139      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)
140      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
141         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_sic))         call nf95_get_var(ncid, varid, pctsrf(:, is_sic))
142      else      else
143         PRINT *, 'phyetat0: Le champ <FSIC> est absent'         PRINT *, 'phyetat0: Le champ <FSIC> est absent'
        !$$$         stop 1  
144      ENDIF      ENDIF
145    
146      !  Verification de l'adequation entre le masque et les sous-surfaces      ! Verification de l'adequation entre le masque et les sous-surfaces
147    
148      fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &      fractint = pctsrf(:, is_ter) + pctsrf(:, is_lic)
          + pctsrf(1 : klon, is_lic)  
149      DO i = 1 , klon      DO i = 1 , klon
150         IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN         IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN
151            WRITE(*, *) 'phyetat0: attention fraction terre pas ',  &            WRITE(*, *) 'phyetat0: attention fraction terre pas ', &
152                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
153                 , pctsrf(i, is_lic)                 , pctsrf(i, is_lic)
154         ENDIF         ENDIF
155      END DO      END DO
156      fractint(1 : klon) =  pctsrf(1 : klon, is_oce)  &      fractint = pctsrf(:, is_oce) + pctsrf(:, is_sic)
          + pctsrf(1 : klon, is_sic)  
157      DO i = 1 , klon      DO i = 1 , klon
158         IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN         IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN
159            WRITE(*, *) 'phyetat0 attention fraction ocean pas ',  &            WRITE(*, *) 'phyetat0 attention fraction ocean pas ', &
160                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
161                 , pctsrf(i, is_sic)                 , pctsrf(i, is_sic)
162         ENDIF         ENDIF
# Line 190  contains Line 167  contains
167      ierr = NF90_INQ_VARID(ncid, "TS", varid)      ierr = NF90_INQ_VARID(ncid, "TS", varid)
168      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
169         PRINT *, 'phyetat0 : Le champ <TS> est absent'         PRINT *, 'phyetat0 : Le champ <TS> est absent'
170         PRINT *, '          Mais je vais essayer de lire TS**'         PRINT *, ' Mais je vais essayer de lire TS**'
171         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
172            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
173               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
174               stop 1               stop 1
175            ENDIF            ENDIF
176            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
177            ierr = NF90_INQ_VARID(ncid, "TS"//str2, varid)            call NF95_INQ_VARID(ncid, "TS"//str2, varid)
178            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  
179            xmin = 1.0E+20            xmin = 1.0E+20
180            xmax = -1.0E+20            xmax = -1.0E+20
181            DO i = 1, klon            DO i = 1, klon
# Line 217  contains Line 186  contains
186         ENDDO         ENDDO
187      ELSE      ELSE
188         PRINT *, 'phyetat0: Le champ <TS> est present'         PRINT *, 'phyetat0: Le champ <TS> est present'
189         PRINT *, '          J ignore donc les autres temperatures TS**'         PRINT *, ' J ignore donc les autres temperatures TS**'
190         call nf95_get_var(ncid, varid, tsol(:, 1))         call nf95_get_var(ncid, varid, tsol(:, 1))
191         xmin = 1.0E+20         xmin = 1.0E+20
192         xmax = -1.0E+20         xmax = -1.0E+20
# Line 237  contains Line 206  contains
206    
207      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
208         DO isoil=1, nsoilmx         DO isoil=1, nsoilmx
209            IF (isoil.GT.99 .AND. nsrf.GT.99) THEN            IF (isoil > 99 .AND. nsrf > 99) THEN
210               PRINT *, "Trop de couches ou sous-mailles"               PRINT *, "Trop de couches ou sous-mailles"
211               stop 1               stop 1
212            ENDIF            ENDIF
# Line 245  contains Line 214  contains
214            ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)            ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)
215            IF (ierr /= NF90_NOERR) THEN            IF (ierr /= NF90_NOERR) THEN
216               PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"               PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
217               PRINT *, "          Il prend donc la valeur de surface"               PRINT *, " Il prend donc la valeur de surface"
218               DO i=1, klon               DO i=1, klon
219                  tsoil(i, isoil, nsrf)=tsol(i, nsrf)                  tsoil(i, isoil, nsrf)=tsol(i, nsrf)
220               ENDDO               ENDDO
221            ELSE            ELSE
222               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  
223            ENDIF            ENDIF
224         ENDDO         ENDDO
225      ENDDO      ENDDO
226    
227      !IM "slab" ocean      !IM "slab" ocean
228        ! Lecture de tslab (pour slab ocean seulement):
229      ! Lecture de tslab (pour slab ocean seulement):            tslab = 0.
230        seaice = 0.
     IF (ocean .eq. 'slab  ') then  
        ierr = NF90_INQ_VARID(ncid, "TSLAB", varid)  
        IF (ierr /= NF90_NOERR) THEN  
           PRINT *, "phyetat0: Le champ <TSLAB> est absent"  
           stop 1  
        ENDIF  
        call nf95_get_var(ncid, varid, tslab)  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(tslab(i), xmin)  
           xmax = MAX(tslab(i), xmax)  
        ENDDO  
        PRINT *, 'Ecart de la SST tslab:', xmin, xmax  
   
        ! Lecture de seaice (pour slab ocean seulement):  
   
        ierr = NF90_INQ_VARID(ncid, "SEAICE", varid)  
        IF (ierr /= NF90_NOERR) THEN  
           PRINT *, "phyetat0: Le champ <SEAICE> est absent"  
           stop 1  
        ENDIF  
        call nf95_get_var(ncid, varid, seaice)  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(seaice(i), xmin)  
           xmax = MAX(seaice(i), xmax)  
        ENDDO  
        PRINT *, 'Masse de la glace de mer seaice:', xmin, xmax  
     ELSE  
        tslab = 0.  
        seaice = 0.  
     ENDIF  
231    
232      ! Lecture de l'humidite de l'air juste au dessus du sol:      ! Lecture de l'humidite de l'air juste au dessus du sol:
233    
234      ierr = NF90_INQ_VARID(ncid, "QS", varid)      ierr = NF90_INQ_VARID(ncid, "QS", varid)
235      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
236         PRINT *, 'phyetat0: Le champ <QS> est absent'         PRINT *, 'phyetat0: Le champ <QS> est absent'
237         PRINT *, '          Mais je vais essayer de lire QS**'         PRINT *, ' Mais je vais essayer de lire QS**'
238         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
239            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
240               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
241               stop 1               stop 1
242            ENDIF            ENDIF
243            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
244            ierr = NF90_INQ_VARID(ncid, "QS"//str2, varid)            call NF95_INQ_VARID(ncid, "QS"//str2, varid)
245            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  
246            xmin = 1.0E+20            xmin = 1.0E+20
247            xmax = -1.0E+20            xmax = -1.0E+20
248            DO i = 1, klon            DO i = 1, klon
# Line 330  contains Line 253  contains
253         ENDDO         ENDDO
254      ELSE      ELSE
255         PRINT *, 'phyetat0: Le champ <QS> est present'         PRINT *, 'phyetat0: Le champ <QS> est present'
256         PRINT *, '          J ignore donc les autres humidites QS**'         PRINT *, ' J ignore donc les autres humidites QS**'
257         call nf95_get_var(ncid, varid, qsurf(:, 1))         call nf95_get_var(ncid, varid, qsurf(:, 1))
258         xmin = 1.0E+20         xmin = 1.0E+20
259         xmax = -1.0E+20         xmax = -1.0E+20
# Line 349  contains Line 272  contains
272      ! Eau dans le sol (pour le modele de sol "bucket")      ! Eau dans le sol (pour le modele de sol "bucket")
273    
274      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
275      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
276         call nf95_get_var(ncid, varid, qsol)         call nf95_get_var(ncid, varid, qsol)
277      else      else
278         PRINT *, 'phyetat0: Le champ <QSOL> est absent'         PRINT *, 'phyetat0: Le champ <QSOL> est absent'
279         PRINT *, '          Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
280         qsol = 0.         qsol = 0.
281      ENDIF      ENDIF
     xmin = 1.0E+20  
     xmax = -1.0E+20  
     DO i = 1, klon  
        xmin = MIN(qsol(i), xmin)  
        xmax = MAX(qsol(i), xmax)  
     ENDDO  
     PRINT *, 'Eau dans le sol (mm) <QSOL>', xmin, xmax  
282    
283      ! Lecture de neige au sol:      ! Lecture de neige au sol:
284    
285      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)
286      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
287         PRINT *, 'phyetat0: Le champ <SNOW> est absent'         PRINT *, 'phyetat0: Le champ <SNOW> est absent'
288         PRINT *, '          Mais je vais essayer de lire SNOW**'         PRINT *, ' Mais je vais essayer de lire SNOW**'
289         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
290            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
291               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
292               stop 1               stop 1
293            ENDIF            ENDIF
294            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
295            ierr = NF90_INQ_VARID(ncid, "SNOW"//str2, varid)            call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)
296            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  
297            xmin = 1.0E+20            xmin = 1.0E+20
298            xmax = -1.0E+20            xmax = -1.0E+20
299            DO i = 1, klon            DO i = 1, klon
# Line 396  contains Line 304  contains
304         ENDDO         ENDDO
305      ELSE      ELSE
306         PRINT *, 'phyetat0: Le champ <SNOW> est present'         PRINT *, 'phyetat0: Le champ <SNOW> est present'
307         PRINT *, '          J ignore donc les autres neiges SNOW**'         PRINT *, ' J ignore donc les autres neiges SNOW**'
308         call nf95_get_var(ncid, varid, snow(:, 1))         call nf95_get_var(ncid, varid, snow(:, 1))
309         xmin = 1.0E+20         xmin = 1.0E+20
310         xmax = -1.0E+20         xmax = -1.0E+20
# Line 417  contains Line 325  contains
325      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)
326      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
327         PRINT *, 'phyetat0: Le champ <ALBE> est absent'         PRINT *, 'phyetat0: Le champ <ALBE> est absent'
328         PRINT *, '          Mais je vais essayer de lire ALBE**'         PRINT *, ' Mais je vais essayer de lire ALBE**'
329         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
330            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
331               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
332               stop 1               stop 1
333            ENDIF            ENDIF
334            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
335            ierr = NF90_INQ_VARID(ncid, "ALBE"//str2, varid)            call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)
336            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  
337            xmin = 1.0E+20            xmin = 1.0E+20
338            xmax = -1.0E+20            xmax = -1.0E+20
339            DO i = 1, klon            DO i = 1, klon
# Line 444  contains Line 344  contains
344         ENDDO         ENDDO
345      ELSE      ELSE
346         PRINT *, 'phyetat0: Le champ <ALBE> est present'         PRINT *, 'phyetat0: Le champ <ALBE> est present'
347         PRINT *, '          J ignore donc les autres ALBE**'         PRINT *, ' J ignore donc les autres ALBE**'
348         call nf95_get_var(ncid, varid, albe(:, 1))         call nf95_get_var(ncid, varid, albe(:, 1))
349         xmin = 1.0E+20         xmin = 1.0E+20
350         xmax = -1.0E+20         xmax = -1.0E+20
# Line 465  contains Line 365  contains
365      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)
366      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
367         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'
368         !        PRINT *, '          Mais je vais essayer de lire ALBLW**'         ! PRINT *, ' Mais je vais essayer de lire ALBLW**'
369         PRINT *, '          Mais je vais prendre ALBE**'         PRINT *, ' Mais je vais prendre ALBE**'
370         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
371            DO i = 1, klon            DO i = 1, klon
372               alblw(i, nsrf) = albe(i, nsrf)               alblw(i, nsrf) = albe(i, nsrf)
# Line 474  contains Line 374  contains
374         ENDDO         ENDDO
375      ELSE      ELSE
376         PRINT *, 'phyetat0: Le champ <ALBLW> est present'         PRINT *, 'phyetat0: Le champ <ALBLW> est present'
377         PRINT *, '          J ignore donc les autres ALBLW**'         PRINT *, ' J ignore donc les autres ALBLW**'
378         call nf95_get_var(ncid, varid, alblw(:, 1))         call nf95_get_var(ncid, varid, alblw(:, 1))
379         xmin = 1.0E+20         xmin = 1.0E+20
380         xmax = -1.0E+20         xmax = -1.0E+20
# Line 490  contains Line 390  contains
390         ENDDO         ENDDO
391      ENDIF      ENDIF
392    
393      ! Lecture de evaporation:        ! Lecture de evaporation:
394    
395      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)
396      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
397         PRINT *, 'phyetat0: Le champ <EVAP> est absent'         PRINT *, 'phyetat0: Le champ <EVAP> est absent'
398         PRINT *, '          Mais je vais essayer de lire EVAP**'         PRINT *, ' Mais je vais essayer de lire EVAP**'
399         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
400            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
401               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
402               stop 1               stop 1
403            ENDIF            ENDIF
404            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
405            ierr = NF90_INQ_VARID(ncid, "EVAP"//str2, varid)            call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)
406            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  
407            xmin = 1.0E+20            xmin = 1.0E+20
408            xmax = -1.0E+20            xmax = -1.0E+20
409            DO i = 1, klon            DO i = 1, klon
# Line 522  contains Line 414  contains
414         ENDDO         ENDDO
415      ELSE      ELSE
416         PRINT *, 'phyetat0: Le champ <EVAP> est present'         PRINT *, 'phyetat0: Le champ <EVAP> est present'
417         PRINT *, '          J ignore donc les autres EVAP**'         PRINT *, ' J ignore donc les autres EVAP**'
418         call nf95_get_var(ncid, varid, evap(:, 1))         call nf95_get_var(ncid, varid, evap(:, 1))
419         xmin = 1.0E+20         xmin = 1.0E+20
420         xmax = -1.0E+20         xmax = -1.0E+20
# Line 540  contains Line 432  contains
432    
433      ! Lecture precipitation liquide:      ! Lecture precipitation liquide:
434    
435      ierr = NF90_INQ_VARID(ncid, "rain_f", varid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
436      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  
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
# Line 560  contains Line 444  contains
444    
445      ! Lecture precipitation solide:      ! Lecture precipitation solide:
446    
447      ierr = NF90_INQ_VARID(ncid, "snow_f", varid)      call NF95_INQ_VARID(ncid, "snow_f", varid)
448      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  
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
# Line 606  contains Line 482  contains
482      ELSE      ELSE
483         call nf95_get_var(ncid, varid, sollw)         call nf95_get_var(ncid, varid, sollw)
484      ENDIF      ENDIF
485      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  
486    
487      ! Lecture derive des flux:      ! Lecture derive des flux:
488    
# Line 634  contains Line 504  contains
504    
505      ! Lecture du rayonnement net au sol:      ! Lecture du rayonnement net au sol:
506    
507      ierr = NF90_INQ_VARID(ncid, "RADS", varid)      call NF95_INQ_VARID(ncid, "RADS", varid)
508      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  
509      xmin = 1.0E+20      xmin = 1.0E+20
510      xmax = -1.0E+20      xmax = -1.0E+20
511      DO i = 1, klon      DO i = 1, klon
# Line 657  contains Line 519  contains
519      ierr = NF90_INQ_VARID(ncid, "RUG", varid)      ierr = NF90_INQ_VARID(ncid, "RUG", varid)
520      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
521         PRINT *, 'phyetat0: Le champ <RUG> est absent'         PRINT *, 'phyetat0: Le champ <RUG> est absent'
522         PRINT *, '          Mais je vais essayer de lire RUG**'         PRINT *, ' Mais je vais essayer de lire RUG**'
523         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
524            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
525               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
526               stop 1               stop 1
527            ENDIF            ENDIF
528            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
529            ierr = NF90_INQ_VARID(ncid, "RUG"//str2, varid)            call NF95_INQ_VARID(ncid, "RUG"//str2, varid)
530            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  
531            xmin = 1.0E+20            xmin = 1.0E+20
532            xmax = -1.0E+20            xmax = -1.0E+20
533            DO i = 1, klon            DO i = 1, klon
# Line 684  contains Line 538  contains
538         ENDDO         ENDDO
539      ELSE      ELSE
540         PRINT *, 'phyetat0: Le champ <RUG> est present'         PRINT *, 'phyetat0: Le champ <RUG> est present'
541         PRINT *, '          J ignore donc les autres RUG**'         PRINT *, ' J ignore donc les autres RUG**'
542         call nf95_get_var(ncid, varid, frugs(:, 1))         call nf95_get_var(ncid, varid, frugs(:, 1))
543         xmin = 1.0E+20         xmin = 1.0E+20
544         xmax = -1.0E+20         xmax = -1.0E+20
# Line 705  contains Line 559  contains
559      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)
560      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
561         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
562         PRINT *, '          Mais je vais essayer de lire AGESNO**'         PRINT *, ' Mais je vais essayer de lire AGESNO**'
563         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
564            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
565               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
566               stop 1               stop 1
567            ENDIF            ENDIF
# Line 717  contains Line 571  contains
571               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
572               agesno = 50.0               agesno = 50.0
573            ENDIF            ENDIF
574            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  
575            xmin = 1.0E+20            xmin = 1.0E+20
576            xmax = -1.0E+20            xmax = -1.0E+20
577            DO i = 1, klon            DO i = 1, klon
# Line 732  contains Line 582  contains
582         ENDDO         ENDDO
583      ELSE      ELSE
584         PRINT *, 'phyetat0: Le champ <AGESNO> est present'         PRINT *, 'phyetat0: Le champ <AGESNO> est present'
585         PRINT *, '          J ignore donc les autres AGESNO**'         PRINT *, ' J ignore donc les autres AGESNO**'
586         call nf95_get_var(ncid, varid, agesno(:, 1))         call nf95_get_var(ncid, varid, agesno(:, 1))
587         xmin = 1.0E+20         xmin = 1.0E+20
588         xmax = -1.0E+20         xmax = -1.0E+20
# Line 748  contains Line 598  contains
598         ENDDO         ENDDO
599      ENDIF      ENDIF
600    
601      ierr = NF90_INQ_VARID(ncid, "ZMEA", varid)      call NF95_INQ_VARID(ncid, "ZMEA", varid)
602      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  
603      xmin = 1.0E+20      xmin = 1.0E+20
604      xmax = -1.0E+20      xmax = -1.0E+20
605      DO i = 1, klon      DO i = 1, klon
# Line 766  contains Line 608  contains
608      ENDDO      ENDDO
609      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
610    
611      ierr = NF90_INQ_VARID(ncid, "ZSTD", varid)      call NF95_INQ_VARID(ncid, "ZSTD", varid)
612      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  
613      xmin = 1.0E+20      xmin = 1.0E+20
614      xmax = -1.0E+20      xmax = -1.0E+20
615      DO i = 1, klon      DO i = 1, klon
# Line 784  contains Line 618  contains
618      ENDDO      ENDDO
619      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
620    
621      ierr = NF90_INQ_VARID(ncid, "ZSIG", varid)      call NF95_INQ_VARID(ncid, "ZSIG", varid)
622      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  
623      xmin = 1.0E+20      xmin = 1.0E+20
624      xmax = -1.0E+20      xmax = -1.0E+20
625      DO i = 1, klon      DO i = 1, klon
# Line 802  contains Line 628  contains
628      ENDDO      ENDDO
629      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
630    
631      ierr = NF90_INQ_VARID(ncid, "ZGAM", varid)      call NF95_INQ_VARID(ncid, "ZGAM", varid)
632      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  
633      xmin = 1.0E+20      xmin = 1.0E+20
634      xmax = -1.0E+20      xmax = -1.0E+20
635      DO i = 1, klon      DO i = 1, klon
# Line 820  contains Line 638  contains
638      ENDDO      ENDDO
639      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
640    
641      ierr = NF90_INQ_VARID(ncid, "ZTHE", varid)      call NF95_INQ_VARID(ncid, "ZTHE", varid)
642      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  
643      xmin = 1.0E+20      xmin = 1.0E+20
644      xmax = -1.0E+20      xmax = -1.0E+20
645      DO i = 1, klon      DO i = 1, klon
# Line 838  contains Line 648  contains
648      ENDDO      ENDDO
649      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
650    
651      ierr = NF90_INQ_VARID(ncid, "ZPIC", varid)      call NF95_INQ_VARID(ncid, "ZPIC", varid)
652      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  
653      xmin = 1.0E+20      xmin = 1.0E+20
654      xmax = -1.0E+20      xmax = -1.0E+20
655      DO i = 1, klon      DO i = 1, klon
# Line 856  contains Line 658  contains
658      ENDDO      ENDDO
659      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
660    
661      ierr = NF90_INQ_VARID(ncid, "ZVAL", varid)      call NF95_INQ_VARID(ncid, "ZVAL", varid)
662      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  
663      xmin = 1.0E+20      xmin = 1.0E+20
664      xmax = -1.0E+20      xmax = -1.0E+20
665      DO i = 1, klon      DO i = 1, klon
# Line 900  contains Line 694  contains
694         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
695         clwcon = 0.         clwcon = 0.
696      ELSE      ELSE
697         call nf95_get_var(ncid, varid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
698           clwcon(:, 2:) = 0.
699      ENDIF      ENDIF
700      xmin = 1.0E+20      xmin = 1.0E+20
701      xmax = -1.0E+20      xmax = -1.0E+20
# Line 914  contains Line 709  contains
709         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
710         rnebcon = 0.         rnebcon = 0.
711      ELSE      ELSE
712         call nf95_get_var(ncid, varid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
713           rnebcon(:, 2:) = 0.
714      ENDIF      ENDIF
715      xmin = 1.0E+20      xmin = 1.0E+20
716      xmax = -1.0E+20      xmax = -1.0E+20
# Line 930  contains Line 726  contains
726         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
727         ratqs = 0.         ratqs = 0.
728      ELSE      ELSE
729         call nf95_get_var(ncid, varid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
730           ratqs(:, 2:) = 0.
731      ENDIF      ENDIF
732      xmin = 1.0E+20      xmin = 1.0E+20
733      xmax = -1.0E+20      xmax = -1.0E+20
# Line 954  contains Line 751  contains
751      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
752      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
753    
754        call nf95_inq_varid(ncid, "sig1", varid)
755        call nf95_get_var(ncid, varid, sig1)
756    
757        call nf95_inq_varid(ncid, "w01", varid)
758        call nf95_get_var(ncid, varid, w01)
759    
760      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
761    
762    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0

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

  ViewVC Help
Powered by ViewVC 1.1.21