/[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 72 by guez, Tue Jul 23 13:00:07 2013 UTC trunk/Sources/phylmd/phyetat0.f revision 156 by guez, Thu Jul 16 17:39:10 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)         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)
# Line 24  contains Line 26  contains
26      use dimphy, only: zmasq, klev      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      USE indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
29      use netcdf, only: nf90_get_att, nf90_global, nf90_inq_varid, NF90_NOERR, &      use netcdf, only: nf90_global, nf90_inq_varid, NF90_NOERR, &
30           NF90_NOWRITE           NF90_NOWRITE
31      use netcdf95, only: handle_err, nf95_get_var, nf95_close, NF95_OPEN, &      use netcdf95, only: nf95_close, nf95_get_att, nf95_get_var, &
32           nf95_inq_varid           nf95_inq_varid, nf95_inquire_variable, NF95_OPEN
33      USE temps, ONLY : itau_phy      USE temps, ONLY : itau_phy
34    
     CHARACTER(len=*), intent(in):: fichnom  
35      REAL pctsrf(klon, nbsrf)      REAL pctsrf(klon, nbsrf)
36      REAL tsol(klon, nbsrf)      REAL tsol(klon, nbsrf)
37      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
     CHARACTER(len=*), intent(in):: ocean  
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, intent(out):: rain_fall(klon)      REAL, intent(out):: rain_fall(klon)
45      REAL snow_fall(klon)      REAL snow_fall(klon)
# Line 69  contains Line 68  contains
68      ! Local:      ! Local:
69      REAL fractint(klon)      REAL fractint(klon)
70      REAL xmin, xmax      REAL xmin, xmax
71      INTEGER ncid, varid      INTEGER ncid, varid, ndims
72      INTEGER ierr, i, nsrf, isoil      INTEGER ierr, i
     CHARACTER(len=7) str7  
     CHARACTER(len=2) str2  
73    
74      !---------------------------------------------------------------      !---------------------------------------------------------------
75    
76      print *, "Call sequence information: phyetat0"      print *, "Call sequence information: phyetat0"
77    
78      ! Fichier contenant l'état initial :      ! Fichier contenant l'état initial :
79      print *, 'fichnom = ', fichnom      call NF95_OPEN("startphy.nc", NF90_NOWRITE, ncid)
     call NF95_OPEN(fichnom, NF90_NOWRITE, ncid)  
80    
81      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)  
82    
83      ! Lecture des latitudes (coordonnees):      ! Lecture des latitudes (coordonnees):
84    
# Line 97  contains Line 92  contains
92    
93      ! Lecture du masque terre mer      ! Lecture du masque terre mer
94    
95      ierr = NF90_INQ_VARID(ncid, "masque", varid)      call NF95_INQ_VARID(ncid, "masque", varid)
96      IF (ierr == NF90_NOERR) THEN      call nf95_get_var(ncid, varid, zmasq)
97         call nf95_get_var(ncid, varid, zmasq)  
     else  
        PRINT *, 'phyetat0: Le champ <masque> est absent'  
        PRINT *, 'fichier startphy non compatible avec phyetat0'  
     ENDIF  
98      ! Lecture des fractions pour chaque sous-surface      ! Lecture des fractions pour chaque sous-surface
99    
100      ! initialisation des sous-surfaces      ! initialisation des sous-surfaces
# Line 166  contains Line 157  contains
157      END DO      END DO
158    
159      ! Lecture des temperatures du sol:      ! Lecture des temperatures du sol:
160        call NF95_INQ_VARID(ncid, "TS", varid)
161      ierr = NF90_INQ_VARID(ncid, "TS", varid)      call nf95_inquire_variable(ncid, varid, ndims = ndims)
162      IF (ierr /= NF90_NOERR) THEN      if (ndims == 2) then
163         PRINT *, 'phyetat0 : Le champ <TS> est absent'         call NF95_GET_VAR(ncid, varid, tsol)
164         PRINT *, ' Mais je vais essayer de lire TS**'      else
165         DO nsrf = 1, nbsrf         print *, "Found only one surface type for soil temperature."
           IF (nsrf > 99) THEN  
              PRINT *, "Trop de sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str2, '(i2.2)') nsrf  
           call NF95_INQ_VARID(ncid, "TS"//str2, varid)  
           call NF95_GET_VAR(ncid, varid, tsol(:, nsrf))  
           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**'  
166         call nf95_get_var(ncid, varid, tsol(:, 1))         call nf95_get_var(ncid, varid, tsol(:, 1))
167         xmin = 1.0E+20         tsol(:, 2:nbsrf) = spread(tsol(:, 1), dim = 2, ncopies = nbsrf - 1)
168         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  
169    
170      ! Lecture des temperatures du sol profond:      ! Lecture des temperatures du sol profond:
171    
172      DO nsrf = 1, nbsrf      call NF95_INQ_VARID(ncid, 'Tsoil', varid)
173         DO isoil=1, nsoilmx      call NF95_GET_VAR(ncid, varid, tsoil)
           IF (isoil > 99 .AND. nsrf > 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  
              call NF95_GET_VAR(ncid, varid, tsoil(:, isoil, nsrf))  
           ENDIF  
        ENDDO  
     ENDDO  
174    
175      !IM "slab" ocean      !IM "slab" ocean
   
176      ! Lecture de tslab (pour slab ocean seulement):      ! Lecture de tslab (pour slab ocean seulement):
177        tslab = 0.
178      IF (ocean .eq. 'slab ') then      seaice = 0.
        call NF95_INQ_VARID(ncid, "TSLAB", varid)  
        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):  
   
        call NF95_INQ_VARID(ncid, "SEAICE", varid)  
        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  
179    
180      ! Lecture de l'humidite de l'air juste au dessus du sol:      ! Lecture de l'humidite de l'air juste au dessus du sol:
181    
182      ierr = NF90_INQ_VARID(ncid, "QS", varid)      call NF95_INQ_VARID(ncid, "QS", varid)
183      IF (ierr /= NF90_NOERR) THEN      call nf95_get_var(ncid, varid, qsurf)
184         PRINT *, 'phyetat0: Le champ <QS> est absent'      xmin = 1.0E+20
185         PRINT *, ' Mais je vais essayer de lire QS**'      xmax = -1.0E+20
186         DO nsrf = 1, nbsrf      DO i = 1, klon
187            IF (nsrf > 99) THEN         xmin = MIN(qsurf(i, 1), xmin)
188               PRINT *, "Trop de sous-mailles"         xmax = MAX(qsurf(i, 1), xmax)
189               stop 1      ENDDO
190            ENDIF      PRINT *, 'Humidite pres du sol <QS>', xmin, xmax
           WRITE(str2, '(i2.2)') nsrf  
           call NF95_INQ_VARID(ncid, "QS"//str2, varid)  
           call NF95_GET_VAR(ncid, varid, qsurf(:, nsrf))  
           xmin = 1.0E+20  
           xmax = -1.0E+20  
           DO i = 1, klon  
              xmin = MIN(qsurf(i, nsrf), xmin)  
              xmax = MAX(qsurf(i, nsrf), xmax)  
           ENDDO  
           PRINT *, 'Humidite pres du sol QS**:', nsrf, xmin, xmax  
        ENDDO  
     ELSE  
        PRINT *, 'phyetat0: Le champ <QS> est present'  
        PRINT *, ' J ignore donc les autres humidites QS**'  
        call nf95_get_var(ncid, varid, qsurf(:, 1))  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(qsurf(i, 1), xmin)  
           xmax = MAX(qsurf(i, 1), xmax)  
        ENDDO  
        PRINT *, 'Humidite pres du sol <QS>', xmin, xmax  
        DO nsrf = 2, nbsrf  
           DO i = 1, klon  
              qsurf(i, nsrf) = qsurf(i, 1)  
           ENDDO  
        ENDDO  
     ENDIF  
191    
192      ! Eau dans le sol (pour le modele de sol "bucket")      ! Eau dans le sol (pour le modele de sol "bucket")
193    
# Line 308  contains Line 199  contains
199         PRINT *, ' Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
200         qsol = 0.         qsol = 0.
201      ENDIF      ENDIF
202    
203        ! Lecture de neige au sol:
204    
205        call NF95_INQ_VARID(ncid, "SNOW", varid)
206        call nf95_get_var(ncid, varid, snow)
207      xmin = 1.0E+20      xmin = 1.0E+20
208      xmax = -1.0E+20      xmax = -1.0E+20
209      DO i = 1, klon      DO i = 1, klon
210         xmin = MIN(qsol(i), xmin)         xmin = MIN(snow(i, 1), xmin)
211         xmax = MAX(qsol(i), xmax)         xmax = MAX(snow(i, 1), xmax)
212      ENDDO      ENDDO
213      PRINT *, 'Eau dans le sol (mm) <QSOL>', xmin, xmax      PRINT *, 'Neige du sol <SNOW>', xmin, xmax
   
     ! Lecture de neige au sol:  
   
     ierr = NF90_INQ_VARID(ncid, "SNOW", varid)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Le champ <SNOW> est absent'  
        PRINT *, ' Mais je vais essayer de lire SNOW**'  
        DO nsrf = 1, nbsrf  
           IF (nsrf > 99) THEN  
              PRINT *, "Trop de sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str2, '(i2.2)') nsrf  
           call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)  
           call NF95_GET_VAR(ncid, varid, snow(:, nsrf))  
           xmin = 1.0E+20  
           xmax = -1.0E+20  
           DO i = 1, klon  
              xmin = MIN(snow(i, nsrf), xmin)  
              xmax = MAX(snow(i, nsrf), xmax)  
           ENDDO  
           PRINT *, 'Neige du sol SNOW**:', nsrf, xmin, xmax  
        ENDDO  
     ELSE  
        PRINT *, 'phyetat0: Le champ <SNOW> est present'  
        PRINT *, ' J ignore donc les autres neiges SNOW**'  
        call nf95_get_var(ncid, varid, snow(:, 1))  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(snow(i, 1), xmin)  
           xmax = MAX(snow(i, 1), xmax)  
        ENDDO  
        PRINT *, 'Neige du sol <SNOW>', xmin, xmax  
        DO nsrf = 2, nbsrf  
           DO i = 1, klon  
              snow(i, nsrf) = snow(i, 1)  
           ENDDO  
        ENDDO  
     ENDIF  
214    
215      ! Lecture de albedo au sol:      ! Lecture de albedo au sol:
216    
217      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)      call NF95_INQ_VARID(ncid, "ALBE", varid)
218      IF (ierr /= NF90_NOERR) THEN      call nf95_get_var(ncid, varid, albe)
219         PRINT *, 'phyetat0: Le champ <ALBE> est absent'      xmin = 1.0E+20
220         PRINT *, ' Mais je vais essayer de lire ALBE**'      xmax = -1.0E+20
221         DO nsrf = 1, nbsrf      DO i = 1, klon
222            IF (nsrf > 99) THEN         xmin = MIN(albe(i, 1), xmin)
223               PRINT *, "Trop de sous-mailles"         xmax = MAX(albe(i, 1), xmax)
224               stop 1      ENDDO
225            ENDIF      PRINT *, 'Neige du sol <ALBE>', xmin, xmax
           WRITE(str2, '(i2.2)') nsrf  
           call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)  
           call NF95_GET_VAR(ncid, varid, albe(:, nsrf))  
           xmin = 1.0E+20  
           xmax = -1.0E+20  
           DO i = 1, klon  
              xmin = MIN(albe(i, nsrf), xmin)  
              xmax = MAX(albe(i, nsrf), xmax)  
           ENDDO  
           PRINT *, 'Albedo du sol ALBE**:', nsrf, xmin, xmax  
        ENDDO  
     ELSE  
        PRINT *, 'phyetat0: Le champ <ALBE> est present'  
        PRINT *, ' J ignore donc les autres ALBE**'  
        call nf95_get_var(ncid, varid, albe(:, 1))  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(albe(i, 1), xmin)  
           xmax = MAX(albe(i, 1), xmax)  
        ENDDO  
        PRINT *, 'Neige du sol <ALBE>', xmin, xmax  
        DO nsrf = 2, nbsrf  
           DO i = 1, klon  
              albe(i, nsrf) = albe(i, 1)  
           ENDDO  
        ENDDO  
     ENDIF  
   
     ! Lecture de albedo au sol LW:  
   
     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  
226    
227      ! Lecture de evaporation:      ! Lecture de evaporation:
228    
229      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)      call NF95_INQ_VARID(ncid, "EVAP", varid)
230      IF (ierr /= NF90_NOERR) THEN      call nf95_get_var(ncid, varid, evap)
231         PRINT *, 'phyetat0: Le champ <EVAP> est absent'      xmin = 1.0E+20
232         PRINT *, ' Mais je vais essayer de lire EVAP**'      xmax = -1.0E+20
233         DO nsrf = 1, nbsrf      DO i = 1, klon
234            IF (nsrf > 99) THEN         xmin = MIN(evap(i, 1), xmin)
235               PRINT *, "Trop de sous-mailles"         xmax = MAX(evap(i, 1), xmax)
236               stop 1      ENDDO
237            ENDIF      PRINT *, 'Evap du sol <EVAP>', xmin, xmax
           WRITE(str2, '(i2.2)') nsrf  
           call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)  
           call NF95_GET_VAR(ncid, varid, evap(:, nsrf))  
           xmin = 1.0E+20  
           xmax = -1.0E+20  
           DO i = 1, klon  
              xmin = MIN(evap(i, nsrf), xmin)  
              xmax = MAX(evap(i, nsrf), xmax)  
           ENDDO  
           PRINT *, 'evap du sol EVAP**:', nsrf, xmin, xmax  
        ENDDO  
     ELSE  
        PRINT *, 'phyetat0: Le champ <EVAP> est present'  
        PRINT *, ' J ignore donc les autres EVAP**'  
        call nf95_get_var(ncid, varid, evap(:, 1))  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(evap(i, 1), xmin)  
           xmax = MAX(evap(i, 1), xmax)  
        ENDDO  
        PRINT *, 'Evap du sol <EVAP>', xmin, xmax  
        DO nsrf = 2, nbsrf  
           DO i = 1, klon  
              evap(i, nsrf) = evap(i, 1)  
           ENDDO  
        ENDDO  
     ENDIF  
238    
239      ! Lecture precipitation liquide:      ! Lecture precipitation liquide:
240    
241      call NF95_INQ_VARID(ncid, "rain_f", varid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
242      call NF95_GET_VAR(ncid, varid, rain_fall)      call NF95_GET_VAR(ncid, varid, rain_fall)
     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  
243    
244      ! Lecture precipitation solide:      ! Lecture precipitation solide:
245    
# Line 552  contains Line 315  contains
315    
316      ! Lecture de la longueur de rugosite      ! Lecture de la longueur de rugosite
317    
318      ierr = NF90_INQ_VARID(ncid, "RUG", varid)      call NF95_INQ_VARID(ncid, "RUG", varid)
319      IF (ierr /= NF90_NOERR) THEN      call nf95_get_var(ncid, varid, frugs)
320         PRINT *, 'phyetat0: Le champ <RUG> est absent'      xmin = 1.0E+20
321         PRINT *, ' Mais je vais essayer de lire RUG**'      xmax = -1.0E+20
322         DO nsrf = 1, nbsrf      DO i = 1, klon
323            IF (nsrf > 99) THEN         xmin = MIN(frugs(i, 1), xmin)
324               PRINT *, "Trop de sous-mailles"         xmax = MAX(frugs(i, 1), xmax)
325               stop 1      ENDDO
326            ENDIF      PRINT *, 'rugosite <RUG>', xmin, xmax
           WRITE(str2, '(i2.2)') nsrf  
           call NF95_INQ_VARID(ncid, "RUG"//str2, varid)  
           call NF95_GET_VAR(ncid, varid, frugs(:, nsrf))  
           xmin = 1.0E+20  
           xmax = -1.0E+20  
           DO i = 1, klon  
              xmin = MIN(frugs(i, nsrf), xmin)  
              xmax = MAX(frugs(i, nsrf), xmax)  
           ENDDO  
           PRINT *, 'rugosite du sol RUG**:', nsrf, xmin, xmax  
        ENDDO  
     ELSE  
        PRINT *, 'phyetat0: Le champ <RUG> est present'  
        PRINT *, ' J ignore donc les autres RUG**'  
        call nf95_get_var(ncid, varid, frugs(:, 1))  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(frugs(i, 1), xmin)  
           xmax = MAX(frugs(i, 1), xmax)  
        ENDDO  
        PRINT *, 'rugosite <RUG>', xmin, xmax  
        DO nsrf = 2, nbsrf  
           DO i = 1, klon  
              frugs(i, nsrf) = frugs(i, 1)  
           ENDDO  
        ENDDO  
     ENDIF  
327    
328      ! Lecture de l'age de la neige:      ! Lecture de l'age de la neige:
329    
330      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)      call NF95_INQ_VARID(ncid, "AGESNO", varid)
331      IF (ierr /= NF90_NOERR) THEN      call nf95_get_var(ncid, varid, agesno)
332         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'      xmin = 1.0E+20
333         PRINT *, ' Mais je vais essayer de lire AGESNO**'      xmax = -1.0E+20
334         DO nsrf = 1, nbsrf      DO i = 1, klon
335            IF (nsrf > 99) THEN         xmin = MIN(agesno(i, 1), xmin)
336               PRINT *, "Trop de sous-mailles"         xmax = MAX(agesno(i, 1), xmax)
337               stop 1      ENDDO
338            ENDIF      PRINT *, 'Age de la neige <AGESNO>', xmin, xmax
           WRITE(str2, '(i2.2)') nsrf  
           ierr = NF90_INQ_VARID(ncid, "AGESNO"//str2, varid)  
           IF (ierr /= NF90_NOERR) THEN  
              PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"  
              agesno = 50.0  
           ENDIF  
           call NF95_GET_VAR(ncid, varid, agesno(:, nsrf))  
           xmin = 1.0E+20  
           xmax = -1.0E+20  
           DO i = 1, klon  
              xmin = MIN(agesno(i, nsrf), xmin)  
              xmax = MAX(agesno(i, nsrf), xmax)  
           ENDDO  
           PRINT *, 'Age de la neige AGESNO**:', nsrf, xmin, xmax  
        ENDDO  
     ELSE  
        PRINT *, 'phyetat0: Le champ <AGESNO> est present'  
        PRINT *, ' J ignore donc les autres AGESNO**'  
        call nf95_get_var(ncid, varid, agesno(:, 1))  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(agesno(i, 1), xmin)  
           xmax = MAX(agesno(i, 1), xmax)  
        ENDDO  
        PRINT *, 'Age de la neige <AGESNO>', xmin, xmax  
        DO nsrf = 2, nbsrf  
           DO i = 1, klon  
              agesno(i, nsrf) = agesno(i, 1)  
           ENDDO  
        ENDDO  
     ENDIF  
339    
340      call NF95_INQ_VARID(ncid, "ZMEA", varid)      call NF95_INQ_VARID(ncid, "ZMEA", varid)
341      call NF95_GET_VAR(ncid, varid, zmea)      call NF95_GET_VAR(ncid, varid, zmea)

Legend:
Removed from v.72  
changed lines
  Added in v.156

  ViewVC Help
Powered by ViewVC 1.1.21