/[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 155 by guez, Wed Jul 8 17:03:45 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, 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)
     REAL alblw(klon, nbsrf)  
43      REAL evap(klon, nbsrf)      REAL evap(klon, nbsrf)
44      REAL radsol(klon)      REAL, intent(out):: rain_fall(klon)
     REAL rain_fall(klon)  
45      REAL snow_fall(klon)      REAL snow_fall(klon)
     REAL sollw(klon)  
46      real solsw(klon)      real solsw(klon)
47        REAL, intent(out):: sollw(klon)
48      real fder(klon)      real fder(klon)
49        REAL radsol(klon)
50      REAL frugs(klon, nbsrf)      REAL frugs(klon, nbsrf)
51      REAL agesno(klon, nbsrf)      REAL agesno(klon, nbsrf)
52      REAL zmea(klon)      REAL zmea(klon)
# Line 54  contains Line 56  contains
56      REAL zthe(klon)      REAL zthe(klon)
57      REAL zpic(klon)      REAL zpic(klon)
58      REAL zval(klon)      REAL zval(klon)
     REAL pctsrf(klon, nbsrf)  
     REAL fractint(klon)  
     REAL run_off_lic_0(klon)  
   
59      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)  
60      LOGICAL, intent(out):: ancien_ok      LOGICAL, intent(out):: ancien_ok
61        real rnebcon(klon, klev), ratqs(klon, klev), clwcon(klon, klev)
62        REAL run_off_lic_0(klon)
63        real, intent(out):: sig1(klon, klev) ! section adiabatic updraft
64    
65      CHARACTER(len=*), intent(in):: ocean      real, intent(out):: w01(klon, klev)
66        ! vertical velocity within adiabatic updraft
67    
68        ! Local:
69        REAL fractint(klon)
70      REAL xmin, xmax      REAL xmin, xmax
71        INTEGER ncid, varid, ndims
72      INTEGER ncid, varid      INTEGER ierr, i, nsrf
73      INTEGER ierr, i, nsrf, isoil      CHARACTER(len=2) str2
     CHARACTER*7 str7  
     CHARACTER*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      call NF95_INQ_VARID(ncid, 'Tsoil', varid)
174         DO isoil=1, nsoilmx      call NF95_GET_VAR(ncid, varid, tsoil)
           IF (isoil.GT.99 .AND. nsrf.GT.99) THEN  
              PRINT *, "Trop de couches ou sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str7, '(i2.2, "srf", i2.2)') isoil, nsrf  
           ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)  
           IF (ierr /= NF90_NOERR) THEN  
              PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"  
              PRINT *, "          Il prend donc la valeur de surface"  
              DO i=1, klon  
                 tsoil(i, isoil, nsrf)=tsol(i, nsrf)  
              ENDDO  
           ELSE  
              ierr = NF90_GET_VAR(ncid, varid, tsoil(1, isoil, nsrf))  
              IF (ierr /= NF90_NOERR) THEN  
                 PRINT *, "Lecture echouee pour <Tsoil"//str7//">"  
                 stop 1  
              ENDIF  
           ENDIF  
        ENDDO  
     ENDDO  
175    
176      !IM "slab" ocean      !IM "slab" ocean
177        ! Lecture de tslab (pour slab ocean seulement):
178      ! Lecture de tslab (pour slab ocean seulement):            tslab = 0.
179        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  
180    
181      ! Lecture de l'humidite de l'air juste au dessus du sol:      ! Lecture de l'humidite de l'air juste au dessus du sol:
182    
183      ierr = NF90_INQ_VARID(ncid, "QS", varid)      ierr = NF90_INQ_VARID(ncid, "QS", varid)
184      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
185         PRINT *, 'phyetat0: Le champ <QS> est absent'         PRINT *, 'phyetat0: Le champ <QS> est absent'
186         PRINT *, '          Mais je vais essayer de lire QS**'         PRINT *, ' Mais je vais essayer de lire QS**'
187         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
188            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
189               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
190               stop 1               stop 1
191            ENDIF            ENDIF
192            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
193            ierr = NF90_INQ_VARID(ncid, "QS"//str2, varid)            call NF95_INQ_VARID(ncid, "QS"//str2, varid)
194            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  
195            xmin = 1.0E+20            xmin = 1.0E+20
196            xmax = -1.0E+20            xmax = -1.0E+20
197            DO i = 1, klon            DO i = 1, klon
# Line 330  contains Line 202  contains
202         ENDDO         ENDDO
203      ELSE      ELSE
204         PRINT *, 'phyetat0: Le champ <QS> est present'         PRINT *, 'phyetat0: Le champ <QS> est present'
205         PRINT *, '          J ignore donc les autres humidites QS**'         PRINT *, ' J ignore donc les autres humidites QS**'
206         call nf95_get_var(ncid, varid, qsurf(:, 1))         call nf95_get_var(ncid, varid, qsurf(:, 1))
207         xmin = 1.0E+20         xmin = 1.0E+20
208         xmax = -1.0E+20         xmax = -1.0E+20
# Line 349  contains Line 221  contains
221      ! Eau dans le sol (pour le modele de sol "bucket")      ! Eau dans le sol (pour le modele de sol "bucket")
222    
223      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
224      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
225         call nf95_get_var(ncid, varid, qsol)         call nf95_get_var(ncid, varid, qsol)
226      else      else
227         PRINT *, 'phyetat0: Le champ <QSOL> est absent'         PRINT *, 'phyetat0: Le champ <QSOL> est absent'
228         PRINT *, '          Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
229         qsol = 0.         qsol = 0.
230      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  
231    
232      ! Lecture de neige au sol:      ! Lecture de neige au sol:
233    
234      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)
235      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
236         PRINT *, 'phyetat0: Le champ <SNOW> est absent'         PRINT *, 'phyetat0: Le champ <SNOW> est absent'
237         PRINT *, '          Mais je vais essayer de lire SNOW**'         PRINT *, ' Mais je vais essayer de lire SNOW**'
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, "SNOW"//str2, varid)            call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)
245            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  
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 396  contains Line 253  contains
253         ENDDO         ENDDO
254      ELSE      ELSE
255         PRINT *, 'phyetat0: Le champ <SNOW> est present'         PRINT *, 'phyetat0: Le champ <SNOW> est present'
256         PRINT *, '          J ignore donc les autres neiges SNOW**'         PRINT *, ' J ignore donc les autres neiges SNOW**'
257         call nf95_get_var(ncid, varid, snow(:, 1))         call nf95_get_var(ncid, varid, snow(:, 1))
258         xmin = 1.0E+20         xmin = 1.0E+20
259         xmax = -1.0E+20         xmax = -1.0E+20
# Line 417  contains Line 274  contains
274      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)
275      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
276         PRINT *, 'phyetat0: Le champ <ALBE> est absent'         PRINT *, 'phyetat0: Le champ <ALBE> est absent'
277         PRINT *, '          Mais je vais essayer de lire ALBE**'         PRINT *, ' Mais je vais essayer de lire ALBE**'
278         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
279            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
280               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
281               stop 1               stop 1
282            ENDIF            ENDIF
283            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
284            ierr = NF90_INQ_VARID(ncid, "ALBE"//str2, varid)            call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)
285            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  
286            xmin = 1.0E+20            xmin = 1.0E+20
287            xmax = -1.0E+20            xmax = -1.0E+20
288            DO i = 1, klon            DO i = 1, klon
# Line 444  contains Line 293  contains
293         ENDDO         ENDDO
294      ELSE      ELSE
295         PRINT *, 'phyetat0: Le champ <ALBE> est present'         PRINT *, 'phyetat0: Le champ <ALBE> est present'
296         PRINT *, '          J ignore donc les autres ALBE**'         PRINT *, ' J ignore donc les autres ALBE**'
297         call nf95_get_var(ncid, varid, albe(:, 1))         call nf95_get_var(ncid, varid, albe(:, 1))
298         xmin = 1.0E+20         xmin = 1.0E+20
299         xmax = -1.0E+20         xmax = -1.0E+20
# Line 460  contains Line 309  contains
309         ENDDO         ENDDO
310      ENDIF      ENDIF
311    
312      ! Lecture de albedo au sol LW:      ! Lecture de evaporation:
   
     ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Le champ <ALBLW> est absent'  
        !        PRINT *, '          Mais je vais essayer de lire ALBLW**'  
        PRINT *, '          Mais je vais prendre ALBE**'  
        DO nsrf = 1, nbsrf  
           DO i = 1, klon  
              alblw(i, nsrf) = albe(i, nsrf)  
           ENDDO  
        ENDDO  
     ELSE  
        PRINT *, 'phyetat0: Le champ <ALBLW> est present'  
        PRINT *, '          J ignore donc les autres ALBLW**'  
        call nf95_get_var(ncid, varid, alblw(:, 1))  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(alblw(i, 1), xmin)  
           xmax = MAX(alblw(i, 1), xmax)  
        ENDDO  
        PRINT *, 'Neige du sol <ALBLW>', xmin, xmax  
        DO nsrf = 2, nbsrf  
           DO i = 1, klon  
              alblw(i, nsrf) = alblw(i, 1)  
           ENDDO  
        ENDDO  
     ENDIF  
   
     ! Lecture de evaporation:    
313    
314      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)
315      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
316         PRINT *, 'phyetat0: Le champ <EVAP> est absent'         PRINT *, 'phyetat0: Le champ <EVAP> est absent'
317         PRINT *, '          Mais je vais essayer de lire EVAP**'         PRINT *, ' Mais je vais essayer de lire EVAP**'
318         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
319            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
320               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
321               stop 1               stop 1
322            ENDIF            ENDIF
323            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
324            ierr = NF90_INQ_VARID(ncid, "EVAP"//str2, varid)            call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)
325            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  
326            xmin = 1.0E+20            xmin = 1.0E+20
327            xmax = -1.0E+20            xmax = -1.0E+20
328            DO i = 1, klon            DO i = 1, klon
# Line 522  contains Line 333  contains
333         ENDDO         ENDDO
334      ELSE      ELSE
335         PRINT *, 'phyetat0: Le champ <EVAP> est present'         PRINT *, 'phyetat0: Le champ <EVAP> est present'
336         PRINT *, '          J ignore donc les autres EVAP**'         PRINT *, ' J ignore donc les autres EVAP**'
337         call nf95_get_var(ncid, varid, evap(:, 1))         call nf95_get_var(ncid, varid, evap(:, 1))
338         xmin = 1.0E+20         xmin = 1.0E+20
339         xmax = -1.0E+20         xmax = -1.0E+20
# Line 540  contains Line 351  contains
351    
352      ! Lecture precipitation liquide:      ! Lecture precipitation liquide:
353    
354      ierr = NF90_INQ_VARID(ncid, "rain_f", varid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
355      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  
356    
357      ! Lecture precipitation solide:      ! Lecture precipitation solide:
358    
359      ierr = NF90_INQ_VARID(ncid, "snow_f", varid)      call NF95_INQ_VARID(ncid, "snow_f", varid)
360      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  
361      xmin = 1.0E+20      xmin = 1.0E+20
362      xmax = -1.0E+20      xmax = -1.0E+20
363      DO i = 1, klon      DO i = 1, klon
# Line 606  contains Line 394  contains
394      ELSE      ELSE
395         call nf95_get_var(ncid, varid, sollw)         call nf95_get_var(ncid, varid, sollw)
396      ENDIF      ENDIF
397      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  
398    
399      ! Lecture derive des flux:      ! Lecture derive des flux:
400    
# Line 634  contains Line 416  contains
416    
417      ! Lecture du rayonnement net au sol:      ! Lecture du rayonnement net au sol:
418    
419      ierr = NF90_INQ_VARID(ncid, "RADS", varid)      call NF95_INQ_VARID(ncid, "RADS", varid)
420      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  
421      xmin = 1.0E+20      xmin = 1.0E+20
422      xmax = -1.0E+20      xmax = -1.0E+20
423      DO i = 1, klon      DO i = 1, klon
# Line 657  contains Line 431  contains
431      ierr = NF90_INQ_VARID(ncid, "RUG", varid)      ierr = NF90_INQ_VARID(ncid, "RUG", varid)
432      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
433         PRINT *, 'phyetat0: Le champ <RUG> est absent'         PRINT *, 'phyetat0: Le champ <RUG> est absent'
434         PRINT *, '          Mais je vais essayer de lire RUG**'         PRINT *, ' Mais je vais essayer de lire RUG**'
435         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
436            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
437               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
438               stop 1               stop 1
439            ENDIF            ENDIF
440            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
441            ierr = NF90_INQ_VARID(ncid, "RUG"//str2, varid)            call NF95_INQ_VARID(ncid, "RUG"//str2, varid)
442            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  
443            xmin = 1.0E+20            xmin = 1.0E+20
444            xmax = -1.0E+20            xmax = -1.0E+20
445            DO i = 1, klon            DO i = 1, klon
# Line 684  contains Line 450  contains
450         ENDDO         ENDDO
451      ELSE      ELSE
452         PRINT *, 'phyetat0: Le champ <RUG> est present'         PRINT *, 'phyetat0: Le champ <RUG> est present'
453         PRINT *, '          J ignore donc les autres RUG**'         PRINT *, ' J ignore donc les autres RUG**'
454         call nf95_get_var(ncid, varid, frugs(:, 1))         call nf95_get_var(ncid, varid, frugs(:, 1))
455         xmin = 1.0E+20         xmin = 1.0E+20
456         xmax = -1.0E+20         xmax = -1.0E+20
# Line 705  contains Line 471  contains
471      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)
472      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
473         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
474         PRINT *, '          Mais je vais essayer de lire AGESNO**'         PRINT *, ' Mais je vais essayer de lire AGESNO**'
475         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
476            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
477               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
478               stop 1               stop 1
479            ENDIF            ENDIF
# Line 717  contains Line 483  contains
483               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
484               agesno = 50.0               agesno = 50.0
485            ENDIF            ENDIF
486            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  
487            xmin = 1.0E+20            xmin = 1.0E+20
488            xmax = -1.0E+20            xmax = -1.0E+20
489            DO i = 1, klon            DO i = 1, klon
# Line 732  contains Line 494  contains
494         ENDDO         ENDDO
495      ELSE      ELSE
496         PRINT *, 'phyetat0: Le champ <AGESNO> est present'         PRINT *, 'phyetat0: Le champ <AGESNO> est present'
497         PRINT *, '          J ignore donc les autres AGESNO**'         PRINT *, ' J ignore donc les autres AGESNO**'
498         call nf95_get_var(ncid, varid, agesno(:, 1))         call nf95_get_var(ncid, varid, agesno(:, 1))
499         xmin = 1.0E+20         xmin = 1.0E+20
500         xmax = -1.0E+20         xmax = -1.0E+20
# Line 748  contains Line 510  contains
510         ENDDO         ENDDO
511      ENDIF      ENDIF
512    
513      ierr = NF90_INQ_VARID(ncid, "ZMEA", varid)      call NF95_INQ_VARID(ncid, "ZMEA", varid)
514      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  
515      xmin = 1.0E+20      xmin = 1.0E+20
516      xmax = -1.0E+20      xmax = -1.0E+20
517      DO i = 1, klon      DO i = 1, klon
# Line 766  contains Line 520  contains
520      ENDDO      ENDDO
521      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
522    
523      ierr = NF90_INQ_VARID(ncid, "ZSTD", varid)      call NF95_INQ_VARID(ncid, "ZSTD", varid)
524      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  
525      xmin = 1.0E+20      xmin = 1.0E+20
526      xmax = -1.0E+20      xmax = -1.0E+20
527      DO i = 1, klon      DO i = 1, klon
# Line 784  contains Line 530  contains
530      ENDDO      ENDDO
531      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
532    
533      ierr = NF90_INQ_VARID(ncid, "ZSIG", varid)      call NF95_INQ_VARID(ncid, "ZSIG", varid)
534      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  
535      xmin = 1.0E+20      xmin = 1.0E+20
536      xmax = -1.0E+20      xmax = -1.0E+20
537      DO i = 1, klon      DO i = 1, klon
# Line 802  contains Line 540  contains
540      ENDDO      ENDDO
541      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
542    
543      ierr = NF90_INQ_VARID(ncid, "ZGAM", varid)      call NF95_INQ_VARID(ncid, "ZGAM", varid)
544      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  
545      xmin = 1.0E+20      xmin = 1.0E+20
546      xmax = -1.0E+20      xmax = -1.0E+20
547      DO i = 1, klon      DO i = 1, klon
# Line 820  contains Line 550  contains
550      ENDDO      ENDDO
551      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
552    
553      ierr = NF90_INQ_VARID(ncid, "ZTHE", varid)      call NF95_INQ_VARID(ncid, "ZTHE", varid)
554      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  
555      xmin = 1.0E+20      xmin = 1.0E+20
556      xmax = -1.0E+20      xmax = -1.0E+20
557      DO i = 1, klon      DO i = 1, klon
# Line 838  contains Line 560  contains
560      ENDDO      ENDDO
561      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
562    
563      ierr = NF90_INQ_VARID(ncid, "ZPIC", varid)      call NF95_INQ_VARID(ncid, "ZPIC", varid)
564      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  
565      xmin = 1.0E+20      xmin = 1.0E+20
566      xmax = -1.0E+20      xmax = -1.0E+20
567      DO i = 1, klon      DO i = 1, klon
# Line 856  contains Line 570  contains
570      ENDDO      ENDDO
571      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
572    
573      ierr = NF90_INQ_VARID(ncid, "ZVAL", varid)      call NF95_INQ_VARID(ncid, "ZVAL", varid)
574      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  
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 900  contains Line 606  contains
606         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
607         clwcon = 0.         clwcon = 0.
608      ELSE      ELSE
609         call nf95_get_var(ncid, varid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
610           clwcon(:, 2:) = 0.
611      ENDIF      ENDIF
612      xmin = 1.0E+20      xmin = 1.0E+20
613      xmax = -1.0E+20      xmax = -1.0E+20
# Line 914  contains Line 621  contains
621         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
622         rnebcon = 0.         rnebcon = 0.
623      ELSE      ELSE
624         call nf95_get_var(ncid, varid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
625           rnebcon(:, 2:) = 0.
626      ENDIF      ENDIF
627      xmin = 1.0E+20      xmin = 1.0E+20
628      xmax = -1.0E+20      xmax = -1.0E+20
# Line 930  contains Line 638  contains
638         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
639         ratqs = 0.         ratqs = 0.
640      ELSE      ELSE
641         call nf95_get_var(ncid, varid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
642           ratqs(:, 2:) = 0.
643      ENDIF      ENDIF
644      xmin = 1.0E+20      xmin = 1.0E+20
645      xmax = -1.0E+20      xmax = -1.0E+20
# Line 954  contains Line 663  contains
663      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
664      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
665    
666        call nf95_inq_varid(ncid, "sig1", varid)
667        call nf95_get_var(ncid, varid, sig1)
668    
669        call nf95_inq_varid(ncid, "w01", varid)
670        call nf95_get_var(ncid, varid, w01)
671    
672      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
673    
674    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0

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

  ViewVC Help
Powered by ViewVC 1.1.21