/[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 138 by guez, Fri May 22 23:13:19 2015 UTC
# Line 4  module phyetat0_m Line 4  module phyetat0_m
4    
5    IMPLICIT none    IMPLICIT none
6    
7    REAL, save:: rlat(klon), rlon(klon) ! latitude and longitude, in degrees    REAL, save:: rlat(klon), rlon(klon)
8      ! latitude and longitude of a point of the scalar grid identified
9      ! by a simple index, in degrees
10    
11    private klon    private klon
12    
13  contains  contains
14    
15    SUBROUTINE phyetat0(fichnom, pctsrf, tsol, tsoil, ocean, tslab, seaice, &    SUBROUTINE phyetat0(pctsrf, tsol, tsoil, tslab, seaice, qsurf, qsol, &
16         qsurf, qsol, snow, albe, alblw, evap, rain_fall, snow_fall, solsw, &         snow, albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, &
17         sollw, fder, radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, &         radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
18         zpic, zval, t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, &         t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, &
19         run_off_lic_0)         sig1, w01)
20    
21      ! 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
22      ! Author: Z.X. Li (LMD/CNRS)      ! Author: Z.X. Li (LMD/CNRS)
23      ! Date: 19930818      ! Date: 1993/08/18
24      ! Objet : Lecture de l'état initial pour la physique      ! Objet : lecture de l'état initial pour la physique
25    
26      USE indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf      use dimphy, only: zmasq, klev
27      USE dimsoil, ONLY : nsoilmx      USE dimsoil, ONLY : nsoilmx
28        USE indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
29        use netcdf, only: nf90_global, nf90_inq_varid, NF90_NOERR, &
30             NF90_NOWRITE
31        use netcdf95, only: nf95_close, nf95_get_att, nf95_get_var, &
32             nf95_inq_varid, nf95_inquire_variable, NF95_OPEN
33      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  
34    
35      CHARACTER(len=*), intent(in):: fichnom      REAL pctsrf(klon, nbsrf)
36      REAL tsol(klon, nbsrf)      REAL tsol(klon, nbsrf)
37      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
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, intent(out):: qsol(:) ! (klon)
41      REAL snow(klon, nbsrf)      REAL snow(klon, nbsrf)
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, ndims
     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      call NF95_OPEN("startphy.nc", NF90_NOWRITE, ncid)
     call NF95_OPEN(fichnom, NF90_NOWRITE, ncid)  
83    
84      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)  
85    
86      ! Lecture des latitudes (coordonnees):      ! Lecture des latitudes (coordonnees):
87    
88      ierr = NF90_INQ_VARID(ncid, "latitude", varid)      call NF95_INQ_VARID(ncid, "latitude", varid)
89      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  
90    
91      ! Lecture des longitudes (coordonnees):      ! Lecture des longitudes (coordonnees):
92    
93      ierr = NF90_INQ_VARID(ncid, "longitude", varid)      call NF95_INQ_VARID(ncid, "longitude", varid)
94      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  
95    
96      ! Lecture du masque terre mer      ! Lecture du masque terre mer
97    
98      ierr = NF90_INQ_VARID(ncid, "masque", varid)      call NF95_INQ_VARID(ncid, "masque", varid)
99      IF (ierr ==  NF90_NOERR) THEN      call nf95_get_var(ncid, varid, zmasq)
100         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  
101      ! Lecture des fractions pour chaque sous-surface      ! Lecture des fractions pour chaque sous-surface
102    
103      ! initialisation des sous-surfaces      ! initialisation des sous-surfaces
# Line 127  contains Line 107  contains
107      ! fraction de terre      ! fraction de terre
108    
109      ierr = NF90_INQ_VARID(ncid, "FTER", varid)      ierr = NF90_INQ_VARID(ncid, "FTER", varid)
110      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
111         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_ter))         call nf95_get_var(ncid, varid, pctsrf(:, is_ter))
112      else      else
113         PRINT *, 'phyetat0: Le champ <FTER> est absent'         PRINT *, 'phyetat0: Le champ <FTER> est absent'
        !$$$         stop 1  
114      ENDIF      ENDIF
115    
116      ! fraction de glace de terre      ! fraction de glace de terre
117    
118      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)
119      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
120         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_lic))         call nf95_get_var(ncid, varid, pctsrf(:, is_lic))
121      else      else
122         PRINT *, 'phyetat0: Le champ <FLIC> est absent'         PRINT *, 'phyetat0: Le champ <FLIC> est absent'
        !$$$         stop 1  
123      ENDIF      ENDIF
124    
125      ! fraction d'ocean      ! fraction d'ocean
126    
127      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)
128      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
129         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_oce))         call nf95_get_var(ncid, varid, pctsrf(:, is_oce))
130      else      else
131         PRINT *, 'phyetat0: Le champ <FOCE> est absent'         PRINT *, 'phyetat0: Le champ <FOCE> est absent'
        !$$$         stop 1  
132      ENDIF      ENDIF
133    
134      ! fraction glace de mer      ! fraction glace de mer
135    
136      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)
137      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
138         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_sic))         call nf95_get_var(ncid, varid, pctsrf(:, is_sic))
139      else      else
140         PRINT *, 'phyetat0: Le champ <FSIC> est absent'         PRINT *, 'phyetat0: Le champ <FSIC> est absent'
        !$$$         stop 1  
141      ENDIF      ENDIF
142    
143      !  Verification de l'adequation entre le masque et les sous-surfaces      ! Verification de l'adequation entre le masque et les sous-surfaces
144    
145      fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &      fractint = pctsrf(:, is_ter) + pctsrf(:, is_lic)
          + pctsrf(1 : klon, is_lic)  
146      DO i = 1 , klon      DO i = 1 , klon
147         IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN         IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN
148            WRITE(*, *) 'phyetat0: attention fraction terre pas ',  &            WRITE(*, *) 'phyetat0: attention fraction terre pas ', &
149                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
150                 , pctsrf(i, is_lic)                 , pctsrf(i, is_lic)
151         ENDIF         ENDIF
152      END DO      END DO
153      fractint(1 : klon) =  pctsrf(1 : klon, is_oce)  &      fractint = pctsrf(:, is_oce) + pctsrf(:, is_sic)
          + pctsrf(1 : klon, is_sic)  
154      DO i = 1 , klon      DO i = 1 , klon
155         IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN         IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN
156            WRITE(*, *) 'phyetat0 attention fraction ocean pas ',  &            WRITE(*, *) 'phyetat0 attention fraction ocean pas ', &
157                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
158                 , pctsrf(i, is_sic)                 , pctsrf(i, is_sic)
159         ENDIF         ENDIF
160      END DO      END DO
161    
162      ! Lecture des temperatures du sol:      ! Lecture des temperatures du sol:
163        call NF95_INQ_VARID(ncid, "TS", varid)
164      ierr = NF90_INQ_VARID(ncid, "TS", varid)      call nf95_inquire_variable(ncid, varid, ndims = ndims)
165      IF (ierr /= NF90_NOERR) THEN      if (ndims == 2) then
166         PRINT *, 'phyetat0 : Le champ <TS> est absent'         call NF95_GET_VAR(ncid, varid, tsol)
167         PRINT *, '          Mais je vais essayer de lire TS**'      else
168         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**'  
169         call nf95_get_var(ncid, varid, tsol(:, 1))         call nf95_get_var(ncid, varid, tsol(:, 1))
170         xmin = 1.0E+20         tsol(:, 2:nbsrf) = spread(tsol(:, 1), dim = 2, ncopies = nbsrf - 1)
171         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  
172    
173      ! Lecture des temperatures du sol profond:     ! Lecture des temperatures du sol profond:
174    
175      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
176         DO isoil=1, nsoilmx         DO isoil=1, nsoilmx
177            IF (isoil.GT.99 .AND. nsrf.GT.99) THEN            IF (isoil > 99 .AND. nsrf > 99) THEN
178               PRINT *, "Trop de couches ou sous-mailles"               PRINT *, "Trop de couches ou sous-mailles"
179               stop 1               stop 1
180            ENDIF            ENDIF
# Line 245  contains Line 182  contains
182            ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)            ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)
183            IF (ierr /= NF90_NOERR) THEN            IF (ierr /= NF90_NOERR) THEN
184               PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"               PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
185               PRINT *, "          Il prend donc la valeur de surface"               PRINT *, " Il prend donc la valeur de surface"
186               DO i=1, klon               DO i=1, klon
187                  tsoil(i, isoil, nsrf)=tsol(i, nsrf)                  tsoil(i, isoil, nsrf)=tsol(i, nsrf)
188               ENDDO               ENDDO
189            ELSE            ELSE
190               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  
191            ENDIF            ENDIF
192         ENDDO         ENDDO
193      ENDDO      ENDDO
194    
195      !IM "slab" ocean      !IM "slab" ocean
196        ! Lecture de tslab (pour slab ocean seulement):
197      ! Lecture de tslab (pour slab ocean seulement):            tslab = 0.
198        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  
199    
200      ! Lecture de l'humidite de l'air juste au dessus du sol:      ! Lecture de l'humidite de l'air juste au dessus du sol:
201    
202      ierr = NF90_INQ_VARID(ncid, "QS", varid)      ierr = NF90_INQ_VARID(ncid, "QS", varid)
203      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
204         PRINT *, 'phyetat0: Le champ <QS> est absent'         PRINT *, 'phyetat0: Le champ <QS> est absent'
205         PRINT *, '          Mais je vais essayer de lire QS**'         PRINT *, ' Mais je vais essayer de lire QS**'
206         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
207            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
208               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
209               stop 1               stop 1
210            ENDIF            ENDIF
211            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
212            ierr = NF90_INQ_VARID(ncid, "QS"//str2, varid)            call NF95_INQ_VARID(ncid, "QS"//str2, varid)
213            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  
214            xmin = 1.0E+20            xmin = 1.0E+20
215            xmax = -1.0E+20            xmax = -1.0E+20
216            DO i = 1, klon            DO i = 1, klon
# Line 330  contains Line 221  contains
221         ENDDO         ENDDO
222      ELSE      ELSE
223         PRINT *, 'phyetat0: Le champ <QS> est present'         PRINT *, 'phyetat0: Le champ <QS> est present'
224         PRINT *, '          J ignore donc les autres humidites QS**'         PRINT *, ' J ignore donc les autres humidites QS**'
225         call nf95_get_var(ncid, varid, qsurf(:, 1))         call nf95_get_var(ncid, varid, qsurf(:, 1))
226         xmin = 1.0E+20         xmin = 1.0E+20
227         xmax = -1.0E+20         xmax = -1.0E+20
# Line 349  contains Line 240  contains
240      ! Eau dans le sol (pour le modele de sol "bucket")      ! Eau dans le sol (pour le modele de sol "bucket")
241    
242      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
243      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
244         call nf95_get_var(ncid, varid, qsol)         call nf95_get_var(ncid, varid, qsol)
245      else      else
246         PRINT *, 'phyetat0: Le champ <QSOL> est absent'         PRINT *, 'phyetat0: Le champ <QSOL> est absent'
247         PRINT *, '          Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
248         qsol = 0.         qsol = 0.
249      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  
250    
251      ! Lecture de neige au sol:      ! Lecture de neige au sol:
252    
253      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)
254      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
255         PRINT *, 'phyetat0: Le champ <SNOW> est absent'         PRINT *, 'phyetat0: Le champ <SNOW> est absent'
256         PRINT *, '          Mais je vais essayer de lire SNOW**'         PRINT *, ' Mais je vais essayer de lire SNOW**'
257         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
258            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
259               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
260               stop 1               stop 1
261            ENDIF            ENDIF
262            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
263            ierr = NF90_INQ_VARID(ncid, "SNOW"//str2, varid)            call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)
264            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  
265            xmin = 1.0E+20            xmin = 1.0E+20
266            xmax = -1.0E+20            xmax = -1.0E+20
267            DO i = 1, klon            DO i = 1, klon
# Line 396  contains Line 272  contains
272         ENDDO         ENDDO
273      ELSE      ELSE
274         PRINT *, 'phyetat0: Le champ <SNOW> est present'         PRINT *, 'phyetat0: Le champ <SNOW> est present'
275         PRINT *, '          J ignore donc les autres neiges SNOW**'         PRINT *, ' J ignore donc les autres neiges SNOW**'
276         call nf95_get_var(ncid, varid, snow(:, 1))         call nf95_get_var(ncid, varid, snow(:, 1))
277         xmin = 1.0E+20         xmin = 1.0E+20
278         xmax = -1.0E+20         xmax = -1.0E+20
# Line 417  contains Line 293  contains
293      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)
294      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
295         PRINT *, 'phyetat0: Le champ <ALBE> est absent'         PRINT *, 'phyetat0: Le champ <ALBE> est absent'
296         PRINT *, '          Mais je vais essayer de lire ALBE**'         PRINT *, ' Mais je vais essayer de lire ALBE**'
297         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
298            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
299               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
300               stop 1               stop 1
301            ENDIF            ENDIF
302            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
303            ierr = NF90_INQ_VARID(ncid, "ALBE"//str2, varid)            call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)
304            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  
305            xmin = 1.0E+20            xmin = 1.0E+20
306            xmax = -1.0E+20            xmax = -1.0E+20
307            DO i = 1, klon            DO i = 1, klon
# Line 444  contains Line 312  contains
312         ENDDO         ENDDO
313      ELSE      ELSE
314         PRINT *, 'phyetat0: Le champ <ALBE> est present'         PRINT *, 'phyetat0: Le champ <ALBE> est present'
315         PRINT *, '          J ignore donc les autres ALBE**'         PRINT *, ' J ignore donc les autres ALBE**'
316         call nf95_get_var(ncid, varid, albe(:, 1))         call nf95_get_var(ncid, varid, albe(:, 1))
317         xmin = 1.0E+20         xmin = 1.0E+20
318         xmax = -1.0E+20         xmax = -1.0E+20
# Line 465  contains Line 333  contains
333      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)
334      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
335         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'
336         !        PRINT *, '          Mais je vais essayer de lire ALBLW**'         ! PRINT *, ' Mais je vais essayer de lire ALBLW**'
337         PRINT *, '          Mais je vais prendre ALBE**'         PRINT *, ' Mais je vais prendre ALBE**'
338         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
339            DO i = 1, klon            DO i = 1, klon
340               alblw(i, nsrf) = albe(i, nsrf)               alblw(i, nsrf) = albe(i, nsrf)
# Line 474  contains Line 342  contains
342         ENDDO         ENDDO
343      ELSE      ELSE
344         PRINT *, 'phyetat0: Le champ <ALBLW> est present'         PRINT *, 'phyetat0: Le champ <ALBLW> est present'
345         PRINT *, '          J ignore donc les autres ALBLW**'         PRINT *, ' J ignore donc les autres ALBLW**'
346         call nf95_get_var(ncid, varid, alblw(:, 1))         call nf95_get_var(ncid, varid, alblw(:, 1))
347         xmin = 1.0E+20         xmin = 1.0E+20
348         xmax = -1.0E+20         xmax = -1.0E+20
# Line 490  contains Line 358  contains
358         ENDDO         ENDDO
359      ENDIF      ENDIF
360    
361      ! Lecture de evaporation:        ! Lecture de evaporation:
362    
363      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)
364      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
365         PRINT *, 'phyetat0: Le champ <EVAP> est absent'         PRINT *, 'phyetat0: Le champ <EVAP> est absent'
366         PRINT *, '          Mais je vais essayer de lire EVAP**'         PRINT *, ' Mais je vais essayer de lire EVAP**'
367         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
368            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
369               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
370               stop 1               stop 1
371            ENDIF            ENDIF
372            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
373            ierr = NF90_INQ_VARID(ncid, "EVAP"//str2, varid)            call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)
374            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  
375            xmin = 1.0E+20            xmin = 1.0E+20
376            xmax = -1.0E+20            xmax = -1.0E+20
377            DO i = 1, klon            DO i = 1, klon
# Line 522  contains Line 382  contains
382         ENDDO         ENDDO
383      ELSE      ELSE
384         PRINT *, 'phyetat0: Le champ <EVAP> est present'         PRINT *, 'phyetat0: Le champ <EVAP> est present'
385         PRINT *, '          J ignore donc les autres EVAP**'         PRINT *, ' J ignore donc les autres EVAP**'
386         call nf95_get_var(ncid, varid, evap(:, 1))         call nf95_get_var(ncid, varid, evap(:, 1))
387         xmin = 1.0E+20         xmin = 1.0E+20
388         xmax = -1.0E+20         xmax = -1.0E+20
# Line 540  contains Line 400  contains
400    
401      ! Lecture precipitation liquide:      ! Lecture precipitation liquide:
402    
403      ierr = NF90_INQ_VARID(ncid, "rain_f", varid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
404      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  
405    
406      ! Lecture precipitation solide:      ! Lecture precipitation solide:
407    
408      ierr = NF90_INQ_VARID(ncid, "snow_f", varid)      call NF95_INQ_VARID(ncid, "snow_f", varid)
409      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  
410      xmin = 1.0E+20      xmin = 1.0E+20
411      xmax = -1.0E+20      xmax = -1.0E+20
412      DO i = 1, klon      DO i = 1, klon
# Line 606  contains Line 443  contains
443      ELSE      ELSE
444         call nf95_get_var(ncid, varid, sollw)         call nf95_get_var(ncid, varid, sollw)
445      ENDIF      ENDIF
446      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  
447    
448      ! Lecture derive des flux:      ! Lecture derive des flux:
449    
# Line 634  contains Line 465  contains
465    
466      ! Lecture du rayonnement net au sol:      ! Lecture du rayonnement net au sol:
467    
468      ierr = NF90_INQ_VARID(ncid, "RADS", varid)      call NF95_INQ_VARID(ncid, "RADS", varid)
469      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  
470      xmin = 1.0E+20      xmin = 1.0E+20
471      xmax = -1.0E+20      xmax = -1.0E+20
472      DO i = 1, klon      DO i = 1, klon
# Line 657  contains Line 480  contains
480      ierr = NF90_INQ_VARID(ncid, "RUG", varid)      ierr = NF90_INQ_VARID(ncid, "RUG", varid)
481      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
482         PRINT *, 'phyetat0: Le champ <RUG> est absent'         PRINT *, 'phyetat0: Le champ <RUG> est absent'
483         PRINT *, '          Mais je vais essayer de lire RUG**'         PRINT *, ' Mais je vais essayer de lire RUG**'
484         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
485            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
486               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
487               stop 1               stop 1
488            ENDIF            ENDIF
489            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
490            ierr = NF90_INQ_VARID(ncid, "RUG"//str2, varid)            call NF95_INQ_VARID(ncid, "RUG"//str2, varid)
491            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  
492            xmin = 1.0E+20            xmin = 1.0E+20
493            xmax = -1.0E+20            xmax = -1.0E+20
494            DO i = 1, klon            DO i = 1, klon
# Line 684  contains Line 499  contains
499         ENDDO         ENDDO
500      ELSE      ELSE
501         PRINT *, 'phyetat0: Le champ <RUG> est present'         PRINT *, 'phyetat0: Le champ <RUG> est present'
502         PRINT *, '          J ignore donc les autres RUG**'         PRINT *, ' J ignore donc les autres RUG**'
503         call nf95_get_var(ncid, varid, frugs(:, 1))         call nf95_get_var(ncid, varid, frugs(:, 1))
504         xmin = 1.0E+20         xmin = 1.0E+20
505         xmax = -1.0E+20         xmax = -1.0E+20
# Line 705  contains Line 520  contains
520      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)
521      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
522         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
523         PRINT *, '          Mais je vais essayer de lire AGESNO**'         PRINT *, ' Mais je vais essayer de lire AGESNO**'
524         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
525            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
526               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
527               stop 1               stop 1
528            ENDIF            ENDIF
# Line 717  contains Line 532  contains
532               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
533               agesno = 50.0               agesno = 50.0
534            ENDIF            ENDIF
535            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  
536            xmin = 1.0E+20            xmin = 1.0E+20
537            xmax = -1.0E+20            xmax = -1.0E+20
538            DO i = 1, klon            DO i = 1, klon
# Line 732  contains Line 543  contains
543         ENDDO         ENDDO
544      ELSE      ELSE
545         PRINT *, 'phyetat0: Le champ <AGESNO> est present'         PRINT *, 'phyetat0: Le champ <AGESNO> est present'
546         PRINT *, '          J ignore donc les autres AGESNO**'         PRINT *, ' J ignore donc les autres AGESNO**'
547         call nf95_get_var(ncid, varid, agesno(:, 1))         call nf95_get_var(ncid, varid, agesno(:, 1))
548         xmin = 1.0E+20         xmin = 1.0E+20
549         xmax = -1.0E+20         xmax = -1.0E+20
# Line 748  contains Line 559  contains
559         ENDDO         ENDDO
560      ENDIF      ENDIF
561    
562      ierr = NF90_INQ_VARID(ncid, "ZMEA", varid)      call NF95_INQ_VARID(ncid, "ZMEA", varid)
563      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  
564      xmin = 1.0E+20      xmin = 1.0E+20
565      xmax = -1.0E+20      xmax = -1.0E+20
566      DO i = 1, klon      DO i = 1, klon
# Line 766  contains Line 569  contains
569      ENDDO      ENDDO
570      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
571    
572      ierr = NF90_INQ_VARID(ncid, "ZSTD", varid)      call NF95_INQ_VARID(ncid, "ZSTD", varid)
573      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  
574      xmin = 1.0E+20      xmin = 1.0E+20
575      xmax = -1.0E+20      xmax = -1.0E+20
576      DO i = 1, klon      DO i = 1, klon
# Line 784  contains Line 579  contains
579      ENDDO      ENDDO
580      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
581    
582      ierr = NF90_INQ_VARID(ncid, "ZSIG", varid)      call NF95_INQ_VARID(ncid, "ZSIG", varid)
583      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  
584      xmin = 1.0E+20      xmin = 1.0E+20
585      xmax = -1.0E+20      xmax = -1.0E+20
586      DO i = 1, klon      DO i = 1, klon
# Line 802  contains Line 589  contains
589      ENDDO      ENDDO
590      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
591    
592      ierr = NF90_INQ_VARID(ncid, "ZGAM", varid)      call NF95_INQ_VARID(ncid, "ZGAM", varid)
593      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  
594      xmin = 1.0E+20      xmin = 1.0E+20
595      xmax = -1.0E+20      xmax = -1.0E+20
596      DO i = 1, klon      DO i = 1, klon
# Line 820  contains Line 599  contains
599      ENDDO      ENDDO
600      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
601    
602      ierr = NF90_INQ_VARID(ncid, "ZTHE", varid)      call NF95_INQ_VARID(ncid, "ZTHE", varid)
603      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  
604      xmin = 1.0E+20      xmin = 1.0E+20
605      xmax = -1.0E+20      xmax = -1.0E+20
606      DO i = 1, klon      DO i = 1, klon
# Line 838  contains Line 609  contains
609      ENDDO      ENDDO
610      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
611    
612      ierr = NF90_INQ_VARID(ncid, "ZPIC", varid)      call NF95_INQ_VARID(ncid, "ZPIC", varid)
613      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  
614      xmin = 1.0E+20      xmin = 1.0E+20
615      xmax = -1.0E+20      xmax = -1.0E+20
616      DO i = 1, klon      DO i = 1, klon
# Line 856  contains Line 619  contains
619      ENDDO      ENDDO
620      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
621    
622      ierr = NF90_INQ_VARID(ncid, "ZVAL", varid)      call NF95_INQ_VARID(ncid, "ZVAL", varid)
623      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  
624      xmin = 1.0E+20      xmin = 1.0E+20
625      xmax = -1.0E+20      xmax = -1.0E+20
626      DO i = 1, klon      DO i = 1, klon
# Line 900  contains Line 655  contains
655         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
656         clwcon = 0.         clwcon = 0.
657      ELSE      ELSE
658         call nf95_get_var(ncid, varid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
659           clwcon(:, 2:) = 0.
660      ENDIF      ENDIF
661      xmin = 1.0E+20      xmin = 1.0E+20
662      xmax = -1.0E+20      xmax = -1.0E+20
# Line 914  contains Line 670  contains
670         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
671         rnebcon = 0.         rnebcon = 0.
672      ELSE      ELSE
673         call nf95_get_var(ncid, varid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
674           rnebcon(:, 2:) = 0.
675      ENDIF      ENDIF
676      xmin = 1.0E+20      xmin = 1.0E+20
677      xmax = -1.0E+20      xmax = -1.0E+20
# Line 930  contains Line 687  contains
687         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
688         ratqs = 0.         ratqs = 0.
689      ELSE      ELSE
690         call nf95_get_var(ncid, varid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
691           ratqs(:, 2:) = 0.
692      ENDIF      ENDIF
693      xmin = 1.0E+20      xmin = 1.0E+20
694      xmax = -1.0E+20      xmax = -1.0E+20
# Line 954  contains Line 712  contains
712      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
713      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
714    
715        call nf95_inq_varid(ncid, "sig1", varid)
716        call nf95_get_var(ncid, varid, sig1)
717    
718        call nf95_inq_varid(ncid, "w01", varid)
719        call nf95_get_var(ncid, varid, w01)
720    
721      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
722    
723    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0

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

  ViewVC Help
Powered by ViewVC 1.1.21