/[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/Sources/phylmd/phyetat0.f revision 134 by guez, Wed Apr 29 15:47:56 2015 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 indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
27        use netcdf, only: nf90_global, nf90_inq_varid, NF90_NOERR, &
28             NF90_NOWRITE
29        use netcdf95, only: nf95_close, nf95_get_att, nf95_get_var, &
30             nf95_inq_varid, nf95_inquire_variable, NF95_OPEN
31      USE temps, ONLY : itau_phy      USE temps, ONLY : itau_phy
     use netcdf, only: nf90_get_att, nf90_global, nf90_inq_varid, NF90_NOERR, &  
          nf90_get_var, NF90_NOWRITE  
     use netcdf95, only: handle_err, nf95_get_var, nf95_close, NF95_OPEN  
     use dimphy, only: zmasq, klev  
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, ndims
     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)      call nf95_get_att(ncid, nf90_global, "itau_phy", itau_phy)
     call handle_err("phyetat0 itau_phy", ierr, ncid, nf90_global)  
83    
84      ! Lecture des latitudes (coordonnees):      ! Lecture des latitudes (coordonnees):
85    
86      ierr = NF90_INQ_VARID(ncid, "latitude", varid)      call NF95_INQ_VARID(ncid, "latitude", varid)
87      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  
88    
89      ! Lecture des longitudes (coordonnees):      ! Lecture des longitudes (coordonnees):
90    
91      ierr = NF90_INQ_VARID(ncid, "longitude", varid)      call NF95_INQ_VARID(ncid, "longitude", varid)
92      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  
93    
94      ! Lecture du masque terre mer      ! Lecture du masque terre mer
95    
96      ierr = NF90_INQ_VARID(ncid, "masque", varid)      call NF95_INQ_VARID(ncid, "masque", varid)
97      IF (ierr ==  NF90_NOERR) THEN      call nf95_get_var(ncid, varid, zmasq)
98         call nf95_get_var(ncid, varid, zmasq)  
     else  
        PRINT *, 'phyetat0: Le champ <masque> est absent'  
        PRINT *, 'fichier startphy non compatible avec phyetat0'  
        !      stop 1  
     ENDIF  
99      ! Lecture des fractions pour chaque sous-surface      ! Lecture des fractions pour chaque sous-surface
100    
101      ! initialisation des sous-surfaces      ! initialisation des sous-surfaces
# Line 127  contains Line 105  contains
105      ! fraction de terre      ! fraction de terre
106    
107      ierr = NF90_INQ_VARID(ncid, "FTER", varid)      ierr = NF90_INQ_VARID(ncid, "FTER", varid)
108      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
109         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_ter))         call nf95_get_var(ncid, varid, pctsrf(:, is_ter))
110      else      else
111         PRINT *, 'phyetat0: Le champ <FTER> est absent'         PRINT *, 'phyetat0: Le champ <FTER> est absent'
        !$$$         stop 1  
112      ENDIF      ENDIF
113    
114      ! fraction de glace de terre      ! fraction de glace de terre
115    
116      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)
117      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
118         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_lic))         call nf95_get_var(ncid, varid, pctsrf(:, is_lic))
119      else      else
120         PRINT *, 'phyetat0: Le champ <FLIC> est absent'         PRINT *, 'phyetat0: Le champ <FLIC> est absent'
        !$$$         stop 1  
121      ENDIF      ENDIF
122    
123      ! fraction d'ocean      ! fraction d'ocean
124    
125      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)
126      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
127         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_oce))         call nf95_get_var(ncid, varid, pctsrf(:, is_oce))
128      else      else
129         PRINT *, 'phyetat0: Le champ <FOCE> est absent'         PRINT *, 'phyetat0: Le champ <FOCE> est absent'
        !$$$         stop 1  
130      ENDIF      ENDIF
131    
132      ! fraction glace de mer      ! fraction glace de mer
133    
134      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)
135      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
136         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_sic))         call nf95_get_var(ncid, varid, pctsrf(:, is_sic))
137      else      else
138         PRINT *, 'phyetat0: Le champ <FSIC> est absent'         PRINT *, 'phyetat0: Le champ <FSIC> est absent'
        !$$$         stop 1  
139      ENDIF      ENDIF
140    
141      !  Verification de l'adequation entre le masque et les sous-surfaces      ! Verification de l'adequation entre le masque et les sous-surfaces
142    
143      fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &      fractint = pctsrf(:, is_ter) + pctsrf(:, is_lic)
          + pctsrf(1 : klon, is_lic)  
144      DO i = 1 , klon      DO i = 1 , klon
145         IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN         IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN
146            WRITE(*, *) 'phyetat0: attention fraction terre pas ',  &            WRITE(*, *) 'phyetat0: attention fraction terre pas ', &
147                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
148                 , pctsrf(i, is_lic)                 , pctsrf(i, is_lic)
149         ENDIF         ENDIF
150      END DO      END DO
151      fractint(1 : klon) =  pctsrf(1 : klon, is_oce)  &      fractint = pctsrf(:, is_oce) + pctsrf(:, is_sic)
          + pctsrf(1 : klon, is_sic)  
152      DO i = 1 , klon      DO i = 1 , klon
153         IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN         IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN
154            WRITE(*, *) 'phyetat0 attention fraction ocean pas ',  &            WRITE(*, *) 'phyetat0 attention fraction ocean pas ', &
155                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
156                 , pctsrf(i, is_sic)                 , pctsrf(i, is_sic)
157         ENDIF         ENDIF
158      END DO      END DO
159    
160      ! Lecture des temperatures du sol:      ! Lecture des temperatures du sol:
161        call NF95_INQ_VARID(ncid, "TS", varid)
162      ierr = NF90_INQ_VARID(ncid, "TS", varid)      call nf95_inquire_variable(ncid, varid, ndims = ndims)
163      IF (ierr /= NF90_NOERR) THEN      if (ndims == 2) then
164         PRINT *, 'phyetat0 : Le champ <TS> est absent'         call NF95_GET_VAR(ncid, varid, tsol)
165         PRINT *, '          Mais je vais essayer de lire TS**'      else
166         DO nsrf = 1, nbsrf         print *, "Found only one surface type for soil temperature."
           IF (nsrf.GT.99) THEN  
              PRINT *, "Trop de sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str2, '(i2.2)') nsrf  
           ierr = NF90_INQ_VARID(ncid, "TS"//str2, varid)  
           IF (ierr /= NF90_NOERR) THEN  
              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  
           xmin = 1.0E+20  
           xmax = -1.0E+20  
           DO i = 1, klon  
              xmin = MIN(tsol(i, nsrf), xmin)  
              xmax = MAX(tsol(i, nsrf), xmax)  
           ENDDO  
           PRINT *, 'Temperature du sol TS**:', nsrf, xmin, xmax  
        ENDDO  
     ELSE  
        PRINT *, 'phyetat0: Le champ <TS> est present'  
        PRINT *, '          J ignore donc les autres temperatures TS**'  
167         call nf95_get_var(ncid, varid, tsol(:, 1))         call nf95_get_var(ncid, varid, tsol(:, 1))
168         xmin = 1.0E+20         tsol(:, 2:nbsrf) = spread(tsol(:, 1), dim = 2, ncopies = nbsrf - 1)
169         xmax = -1.0E+20      end if      
        DO i = 1, klon  
           xmin = MIN(tsol(i, 1), xmin)  
           xmax = MAX(tsol(i, 1), xmax)  
        ENDDO  
        PRINT *, 'Temperature du sol <TS>', xmin, xmax  
        DO nsrf = 2, nbsrf  
           DO i = 1, klon  
              tsol(i, nsrf) = tsol(i, 1)  
           ENDDO  
        ENDDO  
     ENDIF  
170    
171      ! Lecture des temperatures du sol profond:     ! Lecture des temperatures du sol profond:
172    
173      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
174         DO isoil=1, nsoilmx         DO isoil=1, nsoilmx
175            IF (isoil.GT.99 .AND. nsrf.GT.99) THEN            IF (isoil > 99 .AND. nsrf > 99) THEN
176               PRINT *, "Trop de couches ou sous-mailles"               PRINT *, "Trop de couches ou sous-mailles"
177               stop 1               stop 1
178            ENDIF            ENDIF
# Line 245  contains Line 180  contains
180            ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)            ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)
181            IF (ierr /= NF90_NOERR) THEN            IF (ierr /= NF90_NOERR) THEN
182               PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"               PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
183               PRINT *, "          Il prend donc la valeur de surface"               PRINT *, " Il prend donc la valeur de surface"
184               DO i=1, klon               DO i=1, klon
185                  tsoil(i, isoil, nsrf)=tsol(i, nsrf)                  tsoil(i, isoil, nsrf)=tsol(i, nsrf)
186               ENDDO               ENDDO
187            ELSE            ELSE
188               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  
189            ENDIF            ENDIF
190         ENDDO         ENDDO
191      ENDDO      ENDDO
192    
193      !IM "slab" ocean      !IM "slab" ocean
194        ! Lecture de tslab (pour slab ocean seulement):
195      ! Lecture de tslab (pour slab ocean seulement):            tslab = 0.
196        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  
197    
198      ! Lecture de l'humidite de l'air juste au dessus du sol:      ! Lecture de l'humidite de l'air juste au dessus du sol:
199    
200      ierr = NF90_INQ_VARID(ncid, "QS", varid)      ierr = NF90_INQ_VARID(ncid, "QS", varid)
201      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
202         PRINT *, 'phyetat0: Le champ <QS> est absent'         PRINT *, 'phyetat0: Le champ <QS> est absent'
203         PRINT *, '          Mais je vais essayer de lire QS**'         PRINT *, ' Mais je vais essayer de lire QS**'
204         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
205            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
206               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
207               stop 1               stop 1
208            ENDIF            ENDIF
209            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
210            ierr = NF90_INQ_VARID(ncid, "QS"//str2, varid)            call NF95_INQ_VARID(ncid, "QS"//str2, varid)
211            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  
212            xmin = 1.0E+20            xmin = 1.0E+20
213            xmax = -1.0E+20            xmax = -1.0E+20
214            DO i = 1, klon            DO i = 1, klon
# Line 330  contains Line 219  contains
219         ENDDO         ENDDO
220      ELSE      ELSE
221         PRINT *, 'phyetat0: Le champ <QS> est present'         PRINT *, 'phyetat0: Le champ <QS> est present'
222         PRINT *, '          J ignore donc les autres humidites QS**'         PRINT *, ' J ignore donc les autres humidites QS**'
223         call nf95_get_var(ncid, varid, qsurf(:, 1))         call nf95_get_var(ncid, varid, qsurf(:, 1))
224         xmin = 1.0E+20         xmin = 1.0E+20
225         xmax = -1.0E+20         xmax = -1.0E+20
# Line 349  contains Line 238  contains
238      ! Eau dans le sol (pour le modele de sol "bucket")      ! Eau dans le sol (pour le modele de sol "bucket")
239    
240      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
241      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
242         call nf95_get_var(ncid, varid, qsol)         call nf95_get_var(ncid, varid, qsol)
243      else      else
244         PRINT *, 'phyetat0: Le champ <QSOL> est absent'         PRINT *, 'phyetat0: Le champ <QSOL> est absent'
245         PRINT *, '          Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
246         qsol = 0.         qsol = 0.
247      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  
248    
249      ! Lecture de neige au sol:      ! Lecture de neige au sol:
250    
251      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)
252      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
253         PRINT *, 'phyetat0: Le champ <SNOW> est absent'         PRINT *, 'phyetat0: Le champ <SNOW> est absent'
254         PRINT *, '          Mais je vais essayer de lire SNOW**'         PRINT *, ' Mais je vais essayer de lire SNOW**'
255         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
256            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
257               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
258               stop 1               stop 1
259            ENDIF            ENDIF
260            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
261            ierr = NF90_INQ_VARID(ncid, "SNOW"//str2, varid)            call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)
262            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  
263            xmin = 1.0E+20            xmin = 1.0E+20
264            xmax = -1.0E+20            xmax = -1.0E+20
265            DO i = 1, klon            DO i = 1, klon
# Line 396  contains Line 270  contains
270         ENDDO         ENDDO
271      ELSE      ELSE
272         PRINT *, 'phyetat0: Le champ <SNOW> est present'         PRINT *, 'phyetat0: Le champ <SNOW> est present'
273         PRINT *, '          J ignore donc les autres neiges SNOW**'         PRINT *, ' J ignore donc les autres neiges SNOW**'
274         call nf95_get_var(ncid, varid, snow(:, 1))         call nf95_get_var(ncid, varid, snow(:, 1))
275         xmin = 1.0E+20         xmin = 1.0E+20
276         xmax = -1.0E+20         xmax = -1.0E+20
# Line 417  contains Line 291  contains
291      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)
292      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
293         PRINT *, 'phyetat0: Le champ <ALBE> est absent'         PRINT *, 'phyetat0: Le champ <ALBE> est absent'
294         PRINT *, '          Mais je vais essayer de lire ALBE**'         PRINT *, ' Mais je vais essayer de lire ALBE**'
295         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
296            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
297               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
298               stop 1               stop 1
299            ENDIF            ENDIF
300            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
301            ierr = NF90_INQ_VARID(ncid, "ALBE"//str2, varid)            call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)
302            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  
303            xmin = 1.0E+20            xmin = 1.0E+20
304            xmax = -1.0E+20            xmax = -1.0E+20
305            DO i = 1, klon            DO i = 1, klon
# Line 444  contains Line 310  contains
310         ENDDO         ENDDO
311      ELSE      ELSE
312         PRINT *, 'phyetat0: Le champ <ALBE> est present'         PRINT *, 'phyetat0: Le champ <ALBE> est present'
313         PRINT *, '          J ignore donc les autres ALBE**'         PRINT *, ' J ignore donc les autres ALBE**'
314         call nf95_get_var(ncid, varid, albe(:, 1))         call nf95_get_var(ncid, varid, albe(:, 1))
315         xmin = 1.0E+20         xmin = 1.0E+20
316         xmax = -1.0E+20         xmax = -1.0E+20
# Line 465  contains Line 331  contains
331      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)
332      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
333         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'
334         !        PRINT *, '          Mais je vais essayer de lire ALBLW**'         ! PRINT *, ' Mais je vais essayer de lire ALBLW**'
335         PRINT *, '          Mais je vais prendre ALBE**'         PRINT *, ' Mais je vais prendre ALBE**'
336         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
337            DO i = 1, klon            DO i = 1, klon
338               alblw(i, nsrf) = albe(i, nsrf)               alblw(i, nsrf) = albe(i, nsrf)
# Line 474  contains Line 340  contains
340         ENDDO         ENDDO
341      ELSE      ELSE
342         PRINT *, 'phyetat0: Le champ <ALBLW> est present'         PRINT *, 'phyetat0: Le champ <ALBLW> est present'
343         PRINT *, '          J ignore donc les autres ALBLW**'         PRINT *, ' J ignore donc les autres ALBLW**'
344         call nf95_get_var(ncid, varid, alblw(:, 1))         call nf95_get_var(ncid, varid, alblw(:, 1))
345         xmin = 1.0E+20         xmin = 1.0E+20
346         xmax = -1.0E+20         xmax = -1.0E+20
# Line 490  contains Line 356  contains
356         ENDDO         ENDDO
357      ENDIF      ENDIF
358    
359      ! Lecture de evaporation:        ! Lecture de evaporation:
360    
361      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)
362      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
363         PRINT *, 'phyetat0: Le champ <EVAP> est absent'         PRINT *, 'phyetat0: Le champ <EVAP> est absent'
364         PRINT *, '          Mais je vais essayer de lire EVAP**'         PRINT *, ' Mais je vais essayer de lire EVAP**'
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, "EVAP"//str2, varid)            call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)
372            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  
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 522  contains Line 380  contains
380         ENDDO         ENDDO
381      ELSE      ELSE
382         PRINT *, 'phyetat0: Le champ <EVAP> est present'         PRINT *, 'phyetat0: Le champ <EVAP> est present'
383         PRINT *, '          J ignore donc les autres EVAP**'         PRINT *, ' J ignore donc les autres EVAP**'
384         call nf95_get_var(ncid, varid, evap(:, 1))         call nf95_get_var(ncid, varid, evap(:, 1))
385         xmin = 1.0E+20         xmin = 1.0E+20
386         xmax = -1.0E+20         xmax = -1.0E+20
# Line 540  contains Line 398  contains
398    
399      ! Lecture precipitation liquide:      ! Lecture precipitation liquide:
400    
401      ierr = NF90_INQ_VARID(ncid, "rain_f", varid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
402      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  
     xmin = 1.0E+20  
     xmax = -1.0E+20  
     DO i = 1, klon  
        xmin = MIN(rain_fall(i), xmin)  
        xmax = MAX(rain_fall(i), xmax)  
     ENDDO  
     PRINT *, 'Precipitation liquide rain_f:', xmin, xmax  
403    
404      ! Lecture precipitation solide:      ! Lecture precipitation solide:
405    
406      ierr = NF90_INQ_VARID(ncid, "snow_f", varid)      call NF95_INQ_VARID(ncid, "snow_f", varid)
407      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  
408      xmin = 1.0E+20      xmin = 1.0E+20
409      xmax = -1.0E+20      xmax = -1.0E+20
410      DO i = 1, klon      DO i = 1, klon
# Line 606  contains Line 441  contains
441      ELSE      ELSE
442         call nf95_get_var(ncid, varid, sollw)         call nf95_get_var(ncid, varid, sollw)
443      ENDIF      ENDIF
444      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  
445    
446      ! Lecture derive des flux:      ! Lecture derive des flux:
447    
# Line 634  contains Line 463  contains
463    
464      ! Lecture du rayonnement net au sol:      ! Lecture du rayonnement net au sol:
465    
466      ierr = NF90_INQ_VARID(ncid, "RADS", varid)      call NF95_INQ_VARID(ncid, "RADS", varid)
467      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  
468      xmin = 1.0E+20      xmin = 1.0E+20
469      xmax = -1.0E+20      xmax = -1.0E+20
470      DO i = 1, klon      DO i = 1, klon
# Line 657  contains Line 478  contains
478      ierr = NF90_INQ_VARID(ncid, "RUG", varid)      ierr = NF90_INQ_VARID(ncid, "RUG", varid)
479      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
480         PRINT *, 'phyetat0: Le champ <RUG> est absent'         PRINT *, 'phyetat0: Le champ <RUG> est absent'
481         PRINT *, '          Mais je vais essayer de lire RUG**'         PRINT *, ' Mais je vais essayer de lire RUG**'
482         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
483            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
484               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
485               stop 1               stop 1
486            ENDIF            ENDIF
487            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
488            ierr = NF90_INQ_VARID(ncid, "RUG"//str2, varid)            call NF95_INQ_VARID(ncid, "RUG"//str2, varid)
489            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  
490            xmin = 1.0E+20            xmin = 1.0E+20
491            xmax = -1.0E+20            xmax = -1.0E+20
492            DO i = 1, klon            DO i = 1, klon
# Line 684  contains Line 497  contains
497         ENDDO         ENDDO
498      ELSE      ELSE
499         PRINT *, 'phyetat0: Le champ <RUG> est present'         PRINT *, 'phyetat0: Le champ <RUG> est present'
500         PRINT *, '          J ignore donc les autres RUG**'         PRINT *, ' J ignore donc les autres RUG**'
501         call nf95_get_var(ncid, varid, frugs(:, 1))         call nf95_get_var(ncid, varid, frugs(:, 1))
502         xmin = 1.0E+20         xmin = 1.0E+20
503         xmax = -1.0E+20         xmax = -1.0E+20
# Line 705  contains Line 518  contains
518      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)
519      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
520         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
521         PRINT *, '          Mais je vais essayer de lire AGESNO**'         PRINT *, ' Mais je vais essayer de lire AGESNO**'
522         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
523            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
524               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
525               stop 1               stop 1
526            ENDIF            ENDIF
# Line 717  contains Line 530  contains
530               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
531               agesno = 50.0               agesno = 50.0
532            ENDIF            ENDIF
533            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  
534            xmin = 1.0E+20            xmin = 1.0E+20
535            xmax = -1.0E+20            xmax = -1.0E+20
536            DO i = 1, klon            DO i = 1, klon
# Line 732  contains Line 541  contains
541         ENDDO         ENDDO
542      ELSE      ELSE
543         PRINT *, 'phyetat0: Le champ <AGESNO> est present'         PRINT *, 'phyetat0: Le champ <AGESNO> est present'
544         PRINT *, '          J ignore donc les autres AGESNO**'         PRINT *, ' J ignore donc les autres AGESNO**'
545         call nf95_get_var(ncid, varid, agesno(:, 1))         call nf95_get_var(ncid, varid, agesno(:, 1))
546         xmin = 1.0E+20         xmin = 1.0E+20
547         xmax = -1.0E+20         xmax = -1.0E+20
# Line 748  contains Line 557  contains
557         ENDDO         ENDDO
558      ENDIF      ENDIF
559    
560      ierr = NF90_INQ_VARID(ncid, "ZMEA", varid)      call NF95_INQ_VARID(ncid, "ZMEA", varid)
561      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  
562      xmin = 1.0E+20      xmin = 1.0E+20
563      xmax = -1.0E+20      xmax = -1.0E+20
564      DO i = 1, klon      DO i = 1, klon
# Line 766  contains Line 567  contains
567      ENDDO      ENDDO
568      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
569    
570      ierr = NF90_INQ_VARID(ncid, "ZSTD", varid)      call NF95_INQ_VARID(ncid, "ZSTD", varid)
571      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  
572      xmin = 1.0E+20      xmin = 1.0E+20
573      xmax = -1.0E+20      xmax = -1.0E+20
574      DO i = 1, klon      DO i = 1, klon
# Line 784  contains Line 577  contains
577      ENDDO      ENDDO
578      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
579    
580      ierr = NF90_INQ_VARID(ncid, "ZSIG", varid)      call NF95_INQ_VARID(ncid, "ZSIG", varid)
581      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  
582      xmin = 1.0E+20      xmin = 1.0E+20
583      xmax = -1.0E+20      xmax = -1.0E+20
584      DO i = 1, klon      DO i = 1, klon
# Line 802  contains Line 587  contains
587      ENDDO      ENDDO
588      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
589    
590      ierr = NF90_INQ_VARID(ncid, "ZGAM", varid)      call NF95_INQ_VARID(ncid, "ZGAM", varid)
591      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  
592      xmin = 1.0E+20      xmin = 1.0E+20
593      xmax = -1.0E+20      xmax = -1.0E+20
594      DO i = 1, klon      DO i = 1, klon
# Line 820  contains Line 597  contains
597      ENDDO      ENDDO
598      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
599    
600      ierr = NF90_INQ_VARID(ncid, "ZTHE", varid)      call NF95_INQ_VARID(ncid, "ZTHE", varid)
601      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  
602      xmin = 1.0E+20      xmin = 1.0E+20
603      xmax = -1.0E+20      xmax = -1.0E+20
604      DO i = 1, klon      DO i = 1, klon
# Line 838  contains Line 607  contains
607      ENDDO      ENDDO
608      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
609    
610      ierr = NF90_INQ_VARID(ncid, "ZPIC", varid)      call NF95_INQ_VARID(ncid, "ZPIC", varid)
611      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  
612      xmin = 1.0E+20      xmin = 1.0E+20
613      xmax = -1.0E+20      xmax = -1.0E+20
614      DO i = 1, klon      DO i = 1, klon
# Line 856  contains Line 617  contains
617      ENDDO      ENDDO
618      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
619    
620      ierr = NF90_INQ_VARID(ncid, "ZVAL", varid)      call NF95_INQ_VARID(ncid, "ZVAL", varid)
621      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  
622      xmin = 1.0E+20      xmin = 1.0E+20
623      xmax = -1.0E+20      xmax = -1.0E+20
624      DO i = 1, klon      DO i = 1, klon
# Line 900  contains Line 653  contains
653         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
654         clwcon = 0.         clwcon = 0.
655      ELSE      ELSE
656         call nf95_get_var(ncid, varid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
657           clwcon(:, 2:) = 0.
658      ENDIF      ENDIF
659      xmin = 1.0E+20      xmin = 1.0E+20
660      xmax = -1.0E+20      xmax = -1.0E+20
# Line 914  contains Line 668  contains
668         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
669         rnebcon = 0.         rnebcon = 0.
670      ELSE      ELSE
671         call nf95_get_var(ncid, varid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
672           rnebcon(:, 2:) = 0.
673      ENDIF      ENDIF
674      xmin = 1.0E+20      xmin = 1.0E+20
675      xmax = -1.0E+20      xmax = -1.0E+20
# Line 930  contains Line 685  contains
685         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
686         ratqs = 0.         ratqs = 0.
687      ELSE      ELSE
688         call nf95_get_var(ncid, varid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
689           ratqs(:, 2:) = 0.
690      ENDIF      ENDIF
691      xmin = 1.0E+20      xmin = 1.0E+20
692      xmax = -1.0E+20      xmax = -1.0E+20
# Line 954  contains Line 710  contains
710      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
711      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
712    
713        call nf95_inq_varid(ncid, "sig1", varid)
714        call nf95_get_var(ncid, varid, sig1)
715    
716        call nf95_inq_varid(ncid, "w01", varid)
717        call nf95_get_var(ncid, varid, w01)
718    
719      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
720    
721    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0

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

  ViewVC Help
Powered by ViewVC 1.1.21