/[lmdze]/trunk/phylmd/phyetat0.f90
ViewVC logotype

Diff of /trunk/phylmd/phyetat0.f90

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 140 by guez, Fri Jun 5 18:58:06 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
73      INTEGER ncid, varid      INTEGER ierr, i, nsrf
74      INTEGER ierr, i, nsrf, isoil      CHARACTER(len=2) str2
     CHARACTER*7 str7  
     CHARACTER*2 str2  
75    
76      !---------------------------------------------------------------      !---------------------------------------------------------------
77    
78      print *, "Call sequence information: phyetat0"      print *, "Call sequence information: phyetat0"
79    
80      ! Ouvrir le fichier contenant l'etat initial:      ! Fichier contenant l'état initial :
81      print *, 'fichnom = ', fichnom      call NF95_OPEN("startphy.nc", NF90_NOWRITE, ncid)
     call NF95_OPEN(fichnom, NF90_NOWRITE, ncid)  
82    
83      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)  
84    
85      ! Lecture des latitudes (coordonnees):      ! Lecture des latitudes (coordonnees):
86    
87      ierr = NF90_INQ_VARID(ncid, "latitude", varid)      call NF95_INQ_VARID(ncid, "latitude", varid)
88      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, rlat)
        PRINT *, 'phyetat0: Le champ <latitude> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, rlat)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <latitude>'  
        stop 1  
     ENDIF  
89    
90      ! Lecture des longitudes (coordonnees):      ! Lecture des longitudes (coordonnees):
91    
92      ierr = NF90_INQ_VARID(ncid, "longitude", varid)      call NF95_INQ_VARID(ncid, "longitude", varid)
93      IF (ierr /= NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, rlon)
        PRINT *, 'phyetat0: Le champ <longitude> est absent'  
        stop 1  
     ENDIF  
     ierr = NF90_GET_VAR(ncid, varid, rlon)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <latitude>'  
        stop 1  
     ENDIF  
94    
95      ! Lecture du masque terre mer      ! Lecture du masque terre mer
96    
97      ierr = NF90_INQ_VARID(ncid, "masque", varid)      call NF95_INQ_VARID(ncid, "masque", varid)
98      IF (ierr ==  NF90_NOERR) THEN      call nf95_get_var(ncid, varid, zmasq)
99         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  
100      ! Lecture des fractions pour chaque sous-surface      ! Lecture des fractions pour chaque sous-surface
101    
102      ! initialisation des sous-surfaces      ! initialisation des sous-surfaces
# Line 127  contains Line 106  contains
106      ! fraction de terre      ! fraction de terre
107    
108      ierr = NF90_INQ_VARID(ncid, "FTER", varid)      ierr = NF90_INQ_VARID(ncid, "FTER", varid)
109      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
110         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_ter))         call nf95_get_var(ncid, varid, pctsrf(:, is_ter))
111      else      else
112         PRINT *, 'phyetat0: Le champ <FTER> est absent'         PRINT *, 'phyetat0: Le champ <FTER> est absent'
        !$$$         stop 1  
113      ENDIF      ENDIF
114    
115      ! fraction de glace de terre      ! fraction de glace de terre
116    
117      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)
118      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
119         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_lic))         call nf95_get_var(ncid, varid, pctsrf(:, is_lic))
120      else      else
121         PRINT *, 'phyetat0: Le champ <FLIC> est absent'         PRINT *, 'phyetat0: Le champ <FLIC> est absent'
        !$$$         stop 1  
122      ENDIF      ENDIF
123    
124      ! fraction d'ocean      ! fraction d'ocean
125    
126      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)
127      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
128         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_oce))         call nf95_get_var(ncid, varid, pctsrf(:, is_oce))
129      else      else
130         PRINT *, 'phyetat0: Le champ <FOCE> est absent'         PRINT *, 'phyetat0: Le champ <FOCE> est absent'
        !$$$         stop 1  
131      ENDIF      ENDIF
132    
133      ! fraction glace de mer      ! fraction glace de mer
134    
135      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)
136      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
137         call nf95_get_var(ncid, varid, pctsrf(1 : klon, is_sic))         call nf95_get_var(ncid, varid, pctsrf(:, is_sic))
138      else      else
139         PRINT *, 'phyetat0: Le champ <FSIC> est absent'         PRINT *, 'phyetat0: Le champ <FSIC> est absent'
        !$$$         stop 1  
140      ENDIF      ENDIF
141    
142      !  Verification de l'adequation entre le masque et les sous-surfaces      ! Verification de l'adequation entre le masque et les sous-surfaces
143    
144      fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &      fractint = pctsrf(:, is_ter) + pctsrf(:, is_lic)
          + pctsrf(1 : klon, is_lic)  
145      DO i = 1 , klon      DO i = 1 , klon
146         IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN         IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN
147            WRITE(*, *) 'phyetat0: attention fraction terre pas ',  &            WRITE(*, *) 'phyetat0: attention fraction terre pas ', &
148                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
149                 , pctsrf(i, is_lic)                 , pctsrf(i, is_lic)
150         ENDIF         ENDIF
151      END DO      END DO
152      fractint(1 : klon) =  pctsrf(1 : klon, is_oce)  &      fractint = pctsrf(:, is_oce) + pctsrf(:, is_sic)
          + pctsrf(1 : klon, is_sic)  
153      DO i = 1 , klon      DO i = 1 , klon
154         IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN         IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN
155            WRITE(*, *) 'phyetat0 attention fraction ocean pas ',  &            WRITE(*, *) 'phyetat0 attention fraction ocean pas ', &
156                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
157                 , pctsrf(i, is_sic)                 , pctsrf(i, is_sic)
158         ENDIF         ENDIF
159      END DO      END DO
160    
161      ! Lecture des temperatures du sol:      ! Lecture des temperatures du sol:
162        call NF95_INQ_VARID(ncid, "TS", varid)
163      ierr = NF90_INQ_VARID(ncid, "TS", varid)      call nf95_inquire_variable(ncid, varid, ndims = ndims)
164      IF (ierr /= NF90_NOERR) THEN      if (ndims == 2) then
165         PRINT *, 'phyetat0 : Le champ <TS> est absent'         call NF95_GET_VAR(ncid, varid, tsol)
166         PRINT *, '          Mais je vais essayer de lire TS**'      else
167         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**'  
168         call nf95_get_var(ncid, varid, tsol(:, 1))         call nf95_get_var(ncid, varid, tsol(:, 1))
169         xmin = 1.0E+20         tsol(:, 2:nbsrf) = spread(tsol(:, 1), dim = 2, ncopies = nbsrf - 1)
170         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  
171    
172      ! Lecture des temperatures du sol profond:     ! Lecture des temperatures du sol profond:
173    
174      DO nsrf = 1, nbsrf      call NF95_INQ_VARID(ncid, 'Tsoil', varid)
175         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  
176    
177      !IM "slab" ocean      !IM "slab" ocean
178        ! Lecture de tslab (pour slab ocean seulement):
179      ! Lecture de tslab (pour slab ocean seulement):            tslab = 0.
180        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  
181    
182      ! Lecture de l'humidite de l'air juste au dessus du sol:      ! Lecture de l'humidite de l'air juste au dessus du sol:
183    
184      ierr = NF90_INQ_VARID(ncid, "QS", varid)      ierr = NF90_INQ_VARID(ncid, "QS", varid)
185      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
186         PRINT *, 'phyetat0: Le champ <QS> est absent'         PRINT *, 'phyetat0: Le champ <QS> est absent'
187         PRINT *, '          Mais je vais essayer de lire QS**'         PRINT *, ' Mais je vais essayer de lire QS**'
188         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
189            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
190               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
191               stop 1               stop 1
192            ENDIF            ENDIF
193            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
194            ierr = NF90_INQ_VARID(ncid, "QS"//str2, varid)            call NF95_INQ_VARID(ncid, "QS"//str2, varid)
195            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  
196            xmin = 1.0E+20            xmin = 1.0E+20
197            xmax = -1.0E+20            xmax = -1.0E+20
198            DO i = 1, klon            DO i = 1, klon
# Line 330  contains Line 203  contains
203         ENDDO         ENDDO
204      ELSE      ELSE
205         PRINT *, 'phyetat0: Le champ <QS> est present'         PRINT *, 'phyetat0: Le champ <QS> est present'
206         PRINT *, '          J ignore donc les autres humidites QS**'         PRINT *, ' J ignore donc les autres humidites QS**'
207         call nf95_get_var(ncid, varid, qsurf(:, 1))         call nf95_get_var(ncid, varid, qsurf(:, 1))
208         xmin = 1.0E+20         xmin = 1.0E+20
209         xmax = -1.0E+20         xmax = -1.0E+20
# Line 349  contains Line 222  contains
222      ! Eau dans le sol (pour le modele de sol "bucket")      ! Eau dans le sol (pour le modele de sol "bucket")
223    
224      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
225      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
226         call nf95_get_var(ncid, varid, qsol)         call nf95_get_var(ncid, varid, qsol)
227      else      else
228         PRINT *, 'phyetat0: Le champ <QSOL> est absent'         PRINT *, 'phyetat0: Le champ <QSOL> est absent'
229         PRINT *, '          Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
230         qsol = 0.         qsol = 0.
231      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  
232    
233      ! Lecture de neige au sol:      ! Lecture de neige au sol:
234    
235      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)
236      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
237         PRINT *, 'phyetat0: Le champ <SNOW> est absent'         PRINT *, 'phyetat0: Le champ <SNOW> est absent'
238         PRINT *, '          Mais je vais essayer de lire SNOW**'         PRINT *, ' Mais je vais essayer de lire SNOW**'
239         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
240            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
241               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
242               stop 1               stop 1
243            ENDIF            ENDIF
244            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
245            ierr = NF90_INQ_VARID(ncid, "SNOW"//str2, varid)            call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)
246            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  
247            xmin = 1.0E+20            xmin = 1.0E+20
248            xmax = -1.0E+20            xmax = -1.0E+20
249            DO i = 1, klon            DO i = 1, klon
# Line 396  contains Line 254  contains
254         ENDDO         ENDDO
255      ELSE      ELSE
256         PRINT *, 'phyetat0: Le champ <SNOW> est present'         PRINT *, 'phyetat0: Le champ <SNOW> est present'
257         PRINT *, '          J ignore donc les autres neiges SNOW**'         PRINT *, ' J ignore donc les autres neiges SNOW**'
258         call nf95_get_var(ncid, varid, snow(:, 1))         call nf95_get_var(ncid, varid, snow(:, 1))
259         xmin = 1.0E+20         xmin = 1.0E+20
260         xmax = -1.0E+20         xmax = -1.0E+20
# Line 417  contains Line 275  contains
275      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)
276      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
277         PRINT *, 'phyetat0: Le champ <ALBE> est absent'         PRINT *, 'phyetat0: Le champ <ALBE> est absent'
278         PRINT *, '          Mais je vais essayer de lire ALBE**'         PRINT *, ' Mais je vais essayer de lire ALBE**'
279         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
280            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
281               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
282               stop 1               stop 1
283            ENDIF            ENDIF
284            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
285            ierr = NF90_INQ_VARID(ncid, "ALBE"//str2, varid)            call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)
286            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  
287            xmin = 1.0E+20            xmin = 1.0E+20
288            xmax = -1.0E+20            xmax = -1.0E+20
289            DO i = 1, klon            DO i = 1, klon
# Line 444  contains Line 294  contains
294         ENDDO         ENDDO
295      ELSE      ELSE
296         PRINT *, 'phyetat0: Le champ <ALBE> est present'         PRINT *, 'phyetat0: Le champ <ALBE> est present'
297         PRINT *, '          J ignore donc les autres ALBE**'         PRINT *, ' J ignore donc les autres ALBE**'
298         call nf95_get_var(ncid, varid, albe(:, 1))         call nf95_get_var(ncid, varid, albe(:, 1))
299         xmin = 1.0E+20         xmin = 1.0E+20
300         xmax = -1.0E+20         xmax = -1.0E+20
# Line 465  contains Line 315  contains
315      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)
316      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
317         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'
318         !        PRINT *, '          Mais je vais essayer de lire ALBLW**'         ! PRINT *, ' Mais je vais essayer de lire ALBLW**'
319         PRINT *, '          Mais je vais prendre ALBE**'         PRINT *, ' Mais je vais prendre ALBE**'
320         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
321            DO i = 1, klon            DO i = 1, klon
322               alblw(i, nsrf) = albe(i, nsrf)               alblw(i, nsrf) = albe(i, nsrf)
# Line 474  contains Line 324  contains
324         ENDDO         ENDDO
325      ELSE      ELSE
326         PRINT *, 'phyetat0: Le champ <ALBLW> est present'         PRINT *, 'phyetat0: Le champ <ALBLW> est present'
327         PRINT *, '          J ignore donc les autres ALBLW**'         PRINT *, ' J ignore donc les autres ALBLW**'
328         call nf95_get_var(ncid, varid, alblw(:, 1))         call nf95_get_var(ncid, varid, alblw(:, 1))
329         xmin = 1.0E+20         xmin = 1.0E+20
330         xmax = -1.0E+20         xmax = -1.0E+20
# Line 490  contains Line 340  contains
340         ENDDO         ENDDO
341      ENDIF      ENDIF
342    
343      ! Lecture de evaporation:        ! Lecture de evaporation:
344    
345      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)
346      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
347         PRINT *, 'phyetat0: Le champ <EVAP> est absent'         PRINT *, 'phyetat0: Le champ <EVAP> est absent'
348         PRINT *, '          Mais je vais essayer de lire EVAP**'         PRINT *, ' Mais je vais essayer de lire EVAP**'
349         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
350            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
351               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
352               stop 1               stop 1
353            ENDIF            ENDIF
354            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
355            ierr = NF90_INQ_VARID(ncid, "EVAP"//str2, varid)            call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)
356            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  
357            xmin = 1.0E+20            xmin = 1.0E+20
358            xmax = -1.0E+20            xmax = -1.0E+20
359            DO i = 1, klon            DO i = 1, klon
# Line 522  contains Line 364  contains
364         ENDDO         ENDDO
365      ELSE      ELSE
366         PRINT *, 'phyetat0: Le champ <EVAP> est present'         PRINT *, 'phyetat0: Le champ <EVAP> est present'
367         PRINT *, '          J ignore donc les autres EVAP**'         PRINT *, ' J ignore donc les autres EVAP**'
368         call nf95_get_var(ncid, varid, evap(:, 1))         call nf95_get_var(ncid, varid, evap(:, 1))
369         xmin = 1.0E+20         xmin = 1.0E+20
370         xmax = -1.0E+20         xmax = -1.0E+20
# Line 540  contains Line 382  contains
382    
383      ! Lecture precipitation liquide:      ! Lecture precipitation liquide:
384    
385      ierr = NF90_INQ_VARID(ncid, "rain_f", varid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
386      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  
387    
388      ! Lecture precipitation solide:      ! Lecture precipitation solide:
389    
390      ierr = NF90_INQ_VARID(ncid, "snow_f", varid)      call NF95_INQ_VARID(ncid, "snow_f", varid)
391      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  
392      xmin = 1.0E+20      xmin = 1.0E+20
393      xmax = -1.0E+20      xmax = -1.0E+20
394      DO i = 1, klon      DO i = 1, klon
# Line 606  contains Line 425  contains
425      ELSE      ELSE
426         call nf95_get_var(ncid, varid, sollw)         call nf95_get_var(ncid, varid, sollw)
427      ENDIF      ENDIF
428      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  
429    
430      ! Lecture derive des flux:      ! Lecture derive des flux:
431    
# Line 634  contains Line 447  contains
447    
448      ! Lecture du rayonnement net au sol:      ! Lecture du rayonnement net au sol:
449    
450      ierr = NF90_INQ_VARID(ncid, "RADS", varid)      call NF95_INQ_VARID(ncid, "RADS", varid)
451      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  
452      xmin = 1.0E+20      xmin = 1.0E+20
453      xmax = -1.0E+20      xmax = -1.0E+20
454      DO i = 1, klon      DO i = 1, klon
# Line 657  contains Line 462  contains
462      ierr = NF90_INQ_VARID(ncid, "RUG", varid)      ierr = NF90_INQ_VARID(ncid, "RUG", varid)
463      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
464         PRINT *, 'phyetat0: Le champ <RUG> est absent'         PRINT *, 'phyetat0: Le champ <RUG> est absent'
465         PRINT *, '          Mais je vais essayer de lire RUG**'         PRINT *, ' Mais je vais essayer de lire RUG**'
466         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
467            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
468               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
469               stop 1               stop 1
470            ENDIF            ENDIF
471            WRITE(str2, '(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
472            ierr = NF90_INQ_VARID(ncid, "RUG"//str2, varid)            call NF95_INQ_VARID(ncid, "RUG"//str2, varid)
473            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  
474            xmin = 1.0E+20            xmin = 1.0E+20
475            xmax = -1.0E+20            xmax = -1.0E+20
476            DO i = 1, klon            DO i = 1, klon
# Line 684  contains Line 481  contains
481         ENDDO         ENDDO
482      ELSE      ELSE
483         PRINT *, 'phyetat0: Le champ <RUG> est present'         PRINT *, 'phyetat0: Le champ <RUG> est present'
484         PRINT *, '          J ignore donc les autres RUG**'         PRINT *, ' J ignore donc les autres RUG**'
485         call nf95_get_var(ncid, varid, frugs(:, 1))         call nf95_get_var(ncid, varid, frugs(:, 1))
486         xmin = 1.0E+20         xmin = 1.0E+20
487         xmax = -1.0E+20         xmax = -1.0E+20
# Line 705  contains Line 502  contains
502      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)
503      IF (ierr /= NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
504         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
505         PRINT *, '          Mais je vais essayer de lire AGESNO**'         PRINT *, ' Mais je vais essayer de lire AGESNO**'
506         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
507            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
508               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
509               stop 1               stop 1
510            ENDIF            ENDIF
# Line 717  contains Line 514  contains
514               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
515               agesno = 50.0               agesno = 50.0
516            ENDIF            ENDIF
517            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  
518            xmin = 1.0E+20            xmin = 1.0E+20
519            xmax = -1.0E+20            xmax = -1.0E+20
520            DO i = 1, klon            DO i = 1, klon
# Line 732  contains Line 525  contains
525         ENDDO         ENDDO
526      ELSE      ELSE
527         PRINT *, 'phyetat0: Le champ <AGESNO> est present'         PRINT *, 'phyetat0: Le champ <AGESNO> est present'
528         PRINT *, '          J ignore donc les autres AGESNO**'         PRINT *, ' J ignore donc les autres AGESNO**'
529         call nf95_get_var(ncid, varid, agesno(:, 1))         call nf95_get_var(ncid, varid, agesno(:, 1))
530         xmin = 1.0E+20         xmin = 1.0E+20
531         xmax = -1.0E+20         xmax = -1.0E+20
# Line 748  contains Line 541  contains
541         ENDDO         ENDDO
542      ENDIF      ENDIF
543    
544      ierr = NF90_INQ_VARID(ncid, "ZMEA", varid)      call NF95_INQ_VARID(ncid, "ZMEA", varid)
545      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  
546      xmin = 1.0E+20      xmin = 1.0E+20
547      xmax = -1.0E+20      xmax = -1.0E+20
548      DO i = 1, klon      DO i = 1, klon
# Line 766  contains Line 551  contains
551      ENDDO      ENDDO
552      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
553    
554      ierr = NF90_INQ_VARID(ncid, "ZSTD", varid)      call NF95_INQ_VARID(ncid, "ZSTD", varid)
555      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  
556      xmin = 1.0E+20      xmin = 1.0E+20
557      xmax = -1.0E+20      xmax = -1.0E+20
558      DO i = 1, klon      DO i = 1, klon
# Line 784  contains Line 561  contains
561      ENDDO      ENDDO
562      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
563    
564      ierr = NF90_INQ_VARID(ncid, "ZSIG", varid)      call NF95_INQ_VARID(ncid, "ZSIG", varid)
565      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  
566      xmin = 1.0E+20      xmin = 1.0E+20
567      xmax = -1.0E+20      xmax = -1.0E+20
568      DO i = 1, klon      DO i = 1, klon
# Line 802  contains Line 571  contains
571      ENDDO      ENDDO
572      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
573    
574      ierr = NF90_INQ_VARID(ncid, "ZGAM", varid)      call NF95_INQ_VARID(ncid, "ZGAM", varid)
575      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  
576      xmin = 1.0E+20      xmin = 1.0E+20
577      xmax = -1.0E+20      xmax = -1.0E+20
578      DO i = 1, klon      DO i = 1, klon
# Line 820  contains Line 581  contains
581      ENDDO      ENDDO
582      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
583    
584      ierr = NF90_INQ_VARID(ncid, "ZTHE", varid)      call NF95_INQ_VARID(ncid, "ZTHE", varid)
585      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  
586      xmin = 1.0E+20      xmin = 1.0E+20
587      xmax = -1.0E+20      xmax = -1.0E+20
588      DO i = 1, klon      DO i = 1, klon
# Line 838  contains Line 591  contains
591      ENDDO      ENDDO
592      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
593    
594      ierr = NF90_INQ_VARID(ncid, "ZPIC", varid)      call NF95_INQ_VARID(ncid, "ZPIC", varid)
595      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  
596      xmin = 1.0E+20      xmin = 1.0E+20
597      xmax = -1.0E+20      xmax = -1.0E+20
598      DO i = 1, klon      DO i = 1, klon
# Line 856  contains Line 601  contains
601      ENDDO      ENDDO
602      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
603    
604      ierr = NF90_INQ_VARID(ncid, "ZVAL", varid)      call NF95_INQ_VARID(ncid, "ZVAL", varid)
605      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  
606      xmin = 1.0E+20      xmin = 1.0E+20
607      xmax = -1.0E+20      xmax = -1.0E+20
608      DO i = 1, klon      DO i = 1, klon
# Line 900  contains Line 637  contains
637         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
638         clwcon = 0.         clwcon = 0.
639      ELSE      ELSE
640         call nf95_get_var(ncid, varid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
641           clwcon(:, 2:) = 0.
642      ENDIF      ENDIF
643      xmin = 1.0E+20      xmin = 1.0E+20
644      xmax = -1.0E+20      xmax = -1.0E+20
# Line 914  contains Line 652  contains
652         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
653         rnebcon = 0.         rnebcon = 0.
654      ELSE      ELSE
655         call nf95_get_var(ncid, varid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
656           rnebcon(:, 2:) = 0.
657      ENDIF      ENDIF
658      xmin = 1.0E+20      xmin = 1.0E+20
659      xmax = -1.0E+20      xmax = -1.0E+20
# Line 930  contains Line 669  contains
669         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
670         ratqs = 0.         ratqs = 0.
671      ELSE      ELSE
672         call nf95_get_var(ncid, varid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
673           ratqs(:, 2:) = 0.
674      ENDIF      ENDIF
675      xmin = 1.0E+20      xmin = 1.0E+20
676      xmax = -1.0E+20      xmax = -1.0E+20
# Line 954  contains Line 694  contains
694      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
695      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
696    
697        call nf95_inq_varid(ncid, "sig1", varid)
698        call nf95_get_var(ncid, varid, sig1)
699    
700        call nf95_inq_varid(ncid, "w01", varid)
701        call nf95_get_var(ncid, varid, w01)
702    
703      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
704    
705    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0

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

  ViewVC Help
Powered by ViewVC 1.1.21