/[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 13 by guez, Fri Jul 25 19:59:34 2008 UTC trunk/Sources/phylmd/phyetat0.f revision 156 by guez, Thu Jul 16 17:39:10 2015 UTC
# Line 1  Line 1 
1  module phyetat0_m  module phyetat0_m
2    
3    use dimphy, only: klon, klev, zmasq    use dimphy, only: klon
4    
5    IMPLICIT none    IMPLICIT none
6    
7    REAL, save:: rlat(klon), rlon(klon)    REAL, save:: rlat(klon), rlon(klon)
8    ! latitude et longitude pour chaque point, in degrees    ! latitude and longitude of a point of the scalar grid identified
9      ! by a simple index, in degrees
10    
11    private klon, klev, zmasq    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, &         snow, albe, evap, rain_fall, snow_fall, solsw, sollw, fder, &
17         albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, &         radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
18         fder,radsol,frugs,agesno, &         t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, &
19         zmea,zstd,zsig,zgam,zthe,zpic,zval, &         sig1, w01)
20         t_ancien,q_ancien,ancien_ok, rnebcon, ratqs,clwcon, &  
21         run_off_lic_0)      ! From phylmd/phyetat0.F, version 1.4 2005/06/03 10:03:07
22        ! Author: Z.X. Li (LMD/CNRS)
23      ! From phylmd/phyetat0.F,v 1.4 2005/06/03 10:03:07      ! Date: 1993/08/18
24      ! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818      ! Objet : lecture de l'état initial pour la physique
     ! Objet: Lecture de l'etat 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  
     use netcdf95, only: handle_err  
   
     include "netcdf.inc"  
34    
35      CHARACTER(len=*) 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)
     !IM "slab" 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)
43      REAL alblw(klon,nbsrf)      REAL evap(klon, nbsrf)
44      REAL evap(klon,nbsrf)      REAL, intent(out):: rain_fall(klon)
     REAL radsol(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 frugs(klon,nbsrf)      REAL radsol(klon)
50      REAL agesno(klon,nbsrf)      REAL frugs(klon, nbsrf)
51        REAL agesno(klon, nbsrf)
52      REAL zmea(klon)      REAL zmea(klon)
53      REAL, intent(out):: zstd(klon)      REAL, intent(out):: zstd(klon)
54      REAL, intent(out):: zsig(klon)      REAL, intent(out):: zsig(klon)
# Line 57  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)
59      REAL pctsrf(klon, nbsrf)      REAL t_ancien(klon, klev), q_ancien(klon, klev)
60      REAL fractint(klon)      LOGICAL, intent(out):: ancien_ok
61        real rnebcon(klon, klev), ratqs(klon, klev), clwcon(klon, klev)
62      REAL run_off_lic_0(klon)      REAL run_off_lic_0(klon)
63        real, intent(out):: sig1(klon, klev) ! section adiabatic updraft
64    
65      REAL t_ancien(klon,klev), q_ancien(klon,klev)      real, intent(out):: w01(klon, klev)
66      real rnebcon(klon,klev),clwcon(klon,klev),ratqs(klon,klev)      ! vertical velocity within adiabatic updraft
     LOGICAL ancien_ok  
   
     CHARACTER(len=*), intent(in):: ocean  
67    
68        ! Local:
69        REAL fractint(klon)
70      REAL xmin, xmax      REAL xmin, xmax
71        INTEGER ncid, varid, ndims
72      INTEGER nid, nvarid      INTEGER ierr, i
     INTEGER ierr, i, nsrf, isoil  
     CHARACTER*7 str7  
     CHARACTER*2 str2  
73    
74      !---------------------------------------------------------------      !---------------------------------------------------------------
75    
76      print *, "Call sequence information: phyetat0"      print *, "Call sequence information: phyetat0"
77    
78      ! Ouvrir le fichier contenant l'etat initial:      ! Fichier contenant l'état initial :
79        call NF95_OPEN("startphy.nc", NF90_NOWRITE, ncid)
80    
81      print *, 'fichnom = ', fichnom      call nf95_get_att(ncid, nf90_global, "itau_phy", itau_phy)
     ierr = NF_OPEN (fichnom, NF_NOWRITE,nid)  
     IF (ierr.NE.NF_NOERR) THEN  
        write(6,*)' Pb d''ouverture du fichier '//fichnom  
        write(6,*)' ierr = ', ierr  
        STOP 1  
     ENDIF  
   
     ierr = nf90_get_att(nid, nf90_global, "itau_phy", itau_phy)  
     call handle_err("phyetat0 itau_phy", ierr, nid, nf90_global)  
82    
83      ! Lecture des latitudes (coordonnees):      ! Lecture des latitudes (coordonnees):
84    
85      ierr = NF_INQ_VARID (nid, "latitude", nvarid)      call NF95_INQ_VARID(ncid, "latitude", varid)
86      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, rlat)
        PRINT*, 'phyetat0: Le champ <latitude> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, rlat)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <latitude>'  
        stop 1  
     ENDIF  
87    
88      ! Lecture des longitudes (coordonnees):      ! Lecture des longitudes (coordonnees):
89    
90      ierr = NF_INQ_VARID (nid, "longitude", nvarid)      call NF95_INQ_VARID(ncid, "longitude", varid)
91      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, rlon)
        PRINT*, 'phyetat0: Le champ <longitude> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, rlon)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <latitude>'  
        stop 1  
     ENDIF  
   
92    
93      ! Lecture du masque terre mer      ! Lecture du masque terre mer
94    
95      ierr = NF_INQ_VARID (nid, "masque", nvarid)      call NF95_INQ_VARID(ncid, "masque", varid)
96      IF (ierr .EQ.  NF_NOERR) THEN      call nf95_get_var(ncid, varid, zmasq)
97         ierr = NF_GET_VAR_REAL(nid, nvarid, zmasq)  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, 'phyetat0: Lecture echouee pour <masque>'  
           stop 1  
        ENDIF  
     else  
        PRINT*, 'phyetat0: Le champ <masque> est absent'  
        PRINT*, 'fichier startphy non compatible avec phyetat0'  
        !      stop 1  
     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 140  contains Line 103  contains
103    
104      ! fraction de terre      ! fraction de terre
105    
106      ierr = NF_INQ_VARID (nid, "FTER", nvarid)      ierr = NF90_INQ_VARID(ncid, "FTER", varid)
107      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
108         ierr = NF_GET_VAR_REAL(nid, nvarid, pctsrf(1 : klon,is_ter))         call nf95_get_var(ncid, varid, pctsrf(:, is_ter))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, 'phyetat0: Lecture echouee pour <FTER>'  
           stop 1  
        ENDIF  
109      else      else
110         PRINT*, 'phyetat0: Le champ <FTER> est absent'         PRINT *, 'phyetat0: Le champ <FTER> est absent'
        !$$$         stop 1  
111      ENDIF      ENDIF
112    
113      ! fraction de glace de terre      ! fraction de glace de terre
114    
115      ierr = NF_INQ_VARID (nid, "FLIC", nvarid)      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)
116      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
117         ierr = NF_GET_VAR_REAL(nid, nvarid, pctsrf(1 : klon,is_lic))         call nf95_get_var(ncid, varid, pctsrf(:, is_lic))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, 'phyetat0: Lecture echouee pour <FLIC>'  
           stop 1  
        ENDIF  
118      else      else
119         PRINT*, 'phyetat0: Le champ <FLIC> est absent'         PRINT *, 'phyetat0: Le champ <FLIC> est absent'
        !$$$         stop 1  
120      ENDIF      ENDIF
121    
122      ! fraction d'ocean      ! fraction d'ocean
123    
124      ierr = NF_INQ_VARID (nid, "FOCE", nvarid)      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)
125      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
126         ierr = NF_GET_VAR_REAL(nid, nvarid, pctsrf(1 : klon,is_oce))         call nf95_get_var(ncid, varid, pctsrf(:, is_oce))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, 'phyetat0: Lecture echouee pour <FOCE>'  
           stop 1  
        ENDIF  
127      else      else
128         PRINT*, 'phyetat0: Le champ <FOCE> est absent'         PRINT *, 'phyetat0: Le champ <FOCE> est absent'
        !$$$         stop 1  
129      ENDIF      ENDIF
130    
131      ! fraction glace de mer      ! fraction glace de mer
132    
133      ierr = NF_INQ_VARID (nid, "FSIC", nvarid)      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)
134      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
135         ierr = NF_GET_VAR_REAL(nid, nvarid, pctsrf(1 : klon, is_sic))         call nf95_get_var(ncid, varid, pctsrf(:, is_sic))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, 'phyetat0: Lecture echouee pour <FSIC>'  
           stop 1  
        ENDIF  
136      else      else
137         PRINT*, 'phyetat0: Le champ <FSIC> est absent'         PRINT *, 'phyetat0: Le champ <FSIC> est absent'
        !$$$         stop 1  
138      ENDIF      ENDIF
139    
140      !  Verification de l'adequation entre le masque et les sous-surfaces      ! Verification de l'adequation entre le masque et les sous-surfaces
141    
142      fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &      fractint = pctsrf(:, is_ter) + pctsrf(:, is_lic)
          + pctsrf(1 : klon, is_lic)  
143      DO i = 1 , klon      DO i = 1 , klon
144         IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN         IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN
145            WRITE(*,*) 'phyetat0: attention fraction terre pas ',  &            WRITE(*, *) 'phyetat0: attention fraction terre pas ', &
146                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
147                 ,pctsrf(i, is_lic)                 , pctsrf(i, is_lic)
148         ENDIF         ENDIF
149      END DO      END DO
150      fractint (1 : klon) =  pctsrf(1 : klon, is_oce)  &      fractint = pctsrf(:, is_oce) + pctsrf(:, is_sic)
          + pctsrf(1 : klon, is_sic)  
151      DO i = 1 , klon      DO i = 1 , klon
152         IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN         IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN
153            WRITE(*,*) 'phyetat0 attention fraction ocean pas ',  &            WRITE(*, *) 'phyetat0 attention fraction ocean pas ', &
154                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
155                 ,pctsrf(i, is_sic)                 , pctsrf(i, is_sic)
156         ENDIF         ENDIF
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 = NF_INQ_VARID (nid, "TS", nvarid)      call nf95_inquire_variable(ncid, varid, ndims = ndims)
162      IF (ierr.NE.NF_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."
166            IF (nsrf.GT.99) THEN         call nf95_get_var(ncid, varid, tsol(:, 1))
167               PRINT*, "Trop de sous-mailles"         tsol(:, 2:nbsrf) = spread(tsol(:, 1), dim = 2, ncopies = nbsrf - 1)
168               stop 1      end if
           ENDIF  
           WRITE(str2,'(i2.2)') nsrf  
           ierr = NF_INQ_VARID (nid, "TS"//str2, nvarid)  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Le champ <TS"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, tsol(1,nsrf))  
           IF (ierr.NE.NF_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**'  
        ierr = NF_GET_VAR_REAL(nid, nvarid, tsol(1,1))  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <TS>"  
           stop 1  
        ENDIF  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        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.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 = NF_INQ_VARID (nid, 'Tsoil'//str7, nvarid)  
           IF (ierr.NE.NF_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 = NF_GET_VAR_REAL(nid, nvarid, tsoil(1,isoil,nsrf))  
              IF (ierr.NE.NF_NOERR) THEN  
                 PRINT*, "Lecture echouee pour <Tsoil"//str7//">"  
                 stop 1  
              ENDIF  
           ENDIF  
        ENDDO  
     ENDDO  
174    
175      !IM "slab" ocean      !IM "slab" ocean
176        ! Lecture de tslab (pour slab ocean seulement):
177      ! Lecture de tslab (pour slab ocean seulement):            tslab = 0.
178        seaice = 0.
     IF (ocean .eq. 'slab  ') then  
        ierr = NF_INQ_VARID (nid, "TSLAB", nvarid)  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Le champ <TSLAB> est absent"  
           stop 1  
        ENDIF  
        ierr = NF_GET_VAR_REAL(nid, nvarid, tslab)  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <TSLAB>"  
           stop 1  
        ENDIF  
        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 = NF_INQ_VARID (nid, "SEAICE", nvarid)  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Le champ <SEAICE> est absent"  
           stop 1  
        ENDIF  
        ierr = NF_GET_VAR_REAL(nid, nvarid, seaice)  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <SEAICE>"  
           stop 1  
        ENDIF  
        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 = NF_INQ_VARID (nid, "QS", nvarid)      call NF95_INQ_VARID(ncid, "QS", varid)
183      IF (ierr.NE.NF_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.GT.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  
           ierr = NF_INQ_VARID (nid, "QS"//str2, nvarid)  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Le champ <QS"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, qsurf(1,nsrf))  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Lecture echouee pour <QS"//str2//">"  
              stop 1  
           ENDIF  
           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**'  
        ierr = NF_GET_VAR_REAL(nid, nvarid, qsurf(1,1))  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <QS>"  
           stop 1  
        ENDIF  
        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    
194      ierr = NF_INQ_VARID (nid, "QSOL", nvarid)      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
195      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
196         ierr = NF_GET_VAR_REAL(nid, nvarid, qsol)         call nf95_get_var(ncid, varid, qsol)
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, 'phyetat0: Lecture echouee pour <QSOL>'  
           stop 1  
        ENDIF  
197      else      else
198         PRINT*, 'phyetat0: Le champ <QSOL> est absent'         PRINT *, 'phyetat0: Le champ <QSOL> est absent'
199         PRINT*, '          Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
200         qsol(:)=0.         qsol = 0.
        !$$$         stop 1  
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 = NF_INQ_VARID (nid, "SNOW", nvarid)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Le champ <SNOW> est absent'  
        PRINT*, '          Mais je vais essayer de lire SNOW**'  
        DO nsrf = 1, nbsrf  
           IF (nsrf.GT.99) THEN  
              PRINT*, "Trop de sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str2,'(i2.2)') nsrf  
           ierr = NF_INQ_VARID (nid, "SNOW"//str2, nvarid)  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Le champ <SNOW"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, snow(1,nsrf))  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Lecture echouee pour <SNOW"//str2//">"  
              stop 1  
           ENDIF  
           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**'  
        ierr = NF_GET_VAR_REAL(nid, nvarid, snow(1,1))  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <SNOW>"  
           stop 1  
        ENDIF  
        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 = NF_INQ_VARID (nid, "ALBE", nvarid)      call NF95_INQ_VARID(ncid, "ALBE", varid)
218      IF (ierr.NE.NF_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.GT.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  
           ierr = NF_INQ_VARID (nid, "ALBE"//str2, nvarid)  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Le champ <ALBE"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, albe(1,nsrf))  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Lecture echouee pour <ALBE"//str2//">"  
              stop 1  
           ENDIF  
           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**'  
        ierr = NF_GET_VAR_REAL(nid, nvarid, albe(1,1))  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <ALBE>"  
           stop 1  
        ENDIF  
        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 = NF_INQ_VARID (nid, "ALBLW", nvarid)  
     IF (ierr.NE.NF_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**'  
        ierr = NF_GET_VAR_REAL(nid, nvarid, alblw(1,1))  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <ALBLW>"  
           stop 1  
        ENDIF  
        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:    
   
     ierr = NF_INQ_VARID (nid, "EVAP", nvarid)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Le champ <EVAP> est absent'  
        PRINT*, '          Mais je vais essayer de lire EVAP**'  
        DO nsrf = 1, nbsrf  
           IF (nsrf.GT.99) THEN  
              PRINT*, "Trop de sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str2,'(i2.2)') nsrf  
           ierr = NF_INQ_VARID (nid, "EVAP"//str2, nvarid)  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Le champ <EVAP"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, evap(1,nsrf))  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Lecture echouee pour <EVAP"//str2//">"  
              stop 1  
           ENDIF  
           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**'  
        ierr = NF_GET_VAR_REAL(nid, nvarid, evap(1,1))  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <EVAP>"  
           stop 1  
        ENDIF  
        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  
226    
227      ! Lecture precipitation liquide:      ! Lecture de evaporation:
228    
229      ierr = NF_INQ_VARID (nid, "rain_f", nvarid)      call NF95_INQ_VARID(ncid, "EVAP", varid)
230      IF (ierr.NE.NF_NOERR) THEN      call nf95_get_var(ncid, varid, evap)
        PRINT*, 'phyetat0: Le champ <rain_f> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, rain_fall)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <rain_f>'  
        stop 1  
     ENDIF  
231      xmin = 1.0E+20      xmin = 1.0E+20
232      xmax = -1.0E+20      xmax = -1.0E+20
233      DO i = 1, klon      DO i = 1, klon
234         xmin = MIN(rain_fall(i),xmin)         xmin = MIN(evap(i, 1), xmin)
235         xmax = MAX(rain_fall(i),xmax)         xmax = MAX(evap(i, 1), xmax)
236      ENDDO      ENDDO
237      PRINT*,'Precipitation liquide rain_f:', xmin, xmax      PRINT *, 'Evap du sol <EVAP>', xmin, xmax
238    
239        ! Lecture precipitation liquide:
240    
241        call NF95_INQ_VARID(ncid, "rain_f", varid)
242        call NF95_GET_VAR(ncid, varid, rain_fall)
243    
244      ! Lecture precipitation solide:      ! Lecture precipitation solide:
245    
246      ierr = NF_INQ_VARID (nid, "snow_f", nvarid)      call NF95_INQ_VARID(ncid, "snow_f", varid)
247      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, snow_fall)
        PRINT*, 'phyetat0: Le champ <snow_f> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, snow_fall)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <snow_f>'  
        stop 1  
     ENDIF  
248      xmin = 1.0E+20      xmin = 1.0E+20
249      xmax = -1.0E+20      xmax = -1.0E+20
250      DO i = 1, klon      DO i = 1, klon
251         xmin = MIN(snow_fall(i),xmin)         xmin = MIN(snow_fall(i), xmin)
252         xmax = MAX(snow_fall(i),xmax)         xmax = MAX(snow_fall(i), xmax)
253      ENDDO      ENDDO
254      PRINT*,'Precipitation solide snow_f:', xmin, xmax      PRINT *, 'Precipitation solide snow_f:', xmin, xmax
255    
256      ! Lecture rayonnement solaire au sol:      ! Lecture rayonnement solaire au sol:
257    
258      ierr = NF_INQ_VARID (nid, "solsw", nvarid)      ierr = NF90_INQ_VARID(ncid, "solsw", varid)
259      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
260         PRINT*, 'phyetat0: Le champ <solsw> est absent'         PRINT *, 'phyetat0: Le champ <solsw> est absent'
261         PRINT*, 'mis a zero'         PRINT *, 'mis a zero'
262         solsw = 0.         solsw = 0.
263      ELSE      ELSE
264         ierr = NF_GET_VAR_REAL(nid, nvarid, solsw)         call nf95_get_var(ncid, varid, solsw)
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, 'phyetat0: Lecture echouee pour <solsw>'  
           stop 1  
        ENDIF  
265      ENDIF      ENDIF
266      xmin = 1.0E+20      xmin = 1.0E+20
267      xmax = -1.0E+20      xmax = -1.0E+20
268      DO i = 1, klon      DO i = 1, klon
269         xmin = MIN(solsw(i),xmin)         xmin = MIN(solsw(i), xmin)
270         xmax = MAX(solsw(i),xmax)         xmax = MAX(solsw(i), xmax)
271      ENDDO      ENDDO
272      PRINT*,'Rayonnement solaire au sol solsw:', xmin, xmax      PRINT *, 'Rayonnement solaire au sol solsw:', xmin, xmax
273    
274      ! Lecture rayonnement IF au sol:      ! Lecture rayonnement IF au sol:
275    
276      ierr = NF_INQ_VARID (nid, "sollw", nvarid)      ierr = NF90_INQ_VARID(ncid, "sollw", varid)
277      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
278         PRINT*, 'phyetat0: Le champ <sollw> est absent'         PRINT *, 'phyetat0: Le champ <sollw> est absent'
279         PRINT*, 'mis a zero'         PRINT *, 'mis a zero'
280         sollw = 0.         sollw = 0.
281      ELSE      ELSE
282         ierr = NF_GET_VAR_REAL(nid, nvarid, sollw)         call nf95_get_var(ncid, varid, sollw)
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, 'phyetat0: Lecture echouee pour <sollw>'  
           stop 1  
        ENDIF  
283      ENDIF      ENDIF
284      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  
   
285    
286      ! Lecture derive des flux:      ! Lecture derive des flux:
287    
288      ierr = NF_INQ_VARID (nid, "fder", nvarid)      ierr = NF90_INQ_VARID(ncid, "fder", varid)
289      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
290         PRINT*, 'phyetat0: Le champ <fder> est absent'         PRINT *, 'phyetat0: Le champ <fder> est absent'
291         PRINT*, 'mis a zero'         PRINT *, 'mis a zero'
292         fder = 0.         fder = 0.
293      ELSE      ELSE
294         ierr = NF_GET_VAR_REAL(nid, nvarid, fder)         call nf95_get_var(ncid, varid, fder)
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, 'phyetat0: Lecture echouee pour <fder>'  
           stop 1  
        ENDIF  
295      ENDIF      ENDIF
296      xmin = 1.0E+20      xmin = 1.0E+20
297      xmax = -1.0E+20      xmax = -1.0E+20
298      DO i = 1, klon      DO i = 1, klon
299         xmin = MIN(fder(i),xmin)         xmin = MIN(fder(i), xmin)
300         xmax = MAX(fder(i),xmax)         xmax = MAX(fder(i), xmax)
301      ENDDO      ENDDO
302      PRINT*,'Derive des flux fder:', xmin, xmax      PRINT *, 'Derive des flux fder:', xmin, xmax
   
303    
304      ! Lecture du rayonnement net au sol:      ! Lecture du rayonnement net au sol:
305    
306      ierr = NF_INQ_VARID (nid, "RADS", nvarid)      call NF95_INQ_VARID(ncid, "RADS", varid)
307      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, radsol)
        PRINT*, 'phyetat0: Le champ <RADS> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, radsol)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <RADS>'  
        stop 1  
     ENDIF  
308      xmin = 1.0E+20      xmin = 1.0E+20
309      xmax = -1.0E+20      xmax = -1.0E+20
310      DO i = 1, klon      DO i = 1, klon
311         xmin = MIN(radsol(i),xmin)         xmin = MIN(radsol(i), xmin)
312         xmax = MAX(radsol(i),xmax)         xmax = MAX(radsol(i), xmax)
313      ENDDO      ENDDO
314      PRINT*,'Rayonnement net au sol radsol:', xmin, xmax      PRINT *, 'Rayonnement net au sol radsol:', xmin, xmax
315    
316      ! Lecture de la longueur de rugosite      ! Lecture de la longueur de rugosite
317    
318        call NF95_INQ_VARID(ncid, "RUG", varid)
319      ierr = NF_INQ_VARID (nid, "RUG", nvarid)      call nf95_get_var(ncid, varid, frugs)
320      IF (ierr.NE.NF_NOERR) THEN      xmin = 1.0E+20
321         PRINT*, 'phyetat0: Le champ <RUG> est absent'      xmax = -1.0E+20
322         PRINT*, '          Mais je vais essayer de lire RUG**'      DO i = 1, klon
323         DO nsrf = 1, nbsrf         xmin = MIN(frugs(i, 1), xmin)
324            IF (nsrf.GT.99) THEN         xmax = MAX(frugs(i, 1), xmax)
325               PRINT*, "Trop de sous-mailles"      ENDDO
326               stop 1      PRINT *, 'rugosite <RUG>', xmin, xmax
           ENDIF  
           WRITE(str2,'(i2.2)') nsrf  
           ierr = NF_INQ_VARID (nid, "RUG"//str2, nvarid)  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Le champ <RUG"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, frugs(1,nsrf))  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Lecture echouee pour <RUG"//str2//">"  
              stop 1  
           ENDIF  
           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**'  
        ierr = NF_GET_VAR_REAL(nid, nvarid, frugs(1,1))  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <RUG>"  
           stop 1  
        ENDIF  
        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 = NF_INQ_VARID (nid, "AGESNO", nvarid)      call NF95_INQ_VARID(ncid, "AGESNO", varid)
331      IF (ierr.NE.NF_NOERR) THEN      call nf95_get_var(ncid, varid, agesno)
        PRINT*, 'phyetat0: Le champ <AGESNO> est absent'  
        PRINT*, '          Mais je vais essayer de lire AGESNO**'  
        DO nsrf = 1, nbsrf  
           IF (nsrf.GT.99) THEN  
              PRINT*, "Trop de sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str2,'(i2.2)') nsrf  
           ierr = NF_INQ_VARID (nid, "AGESNO"//str2, nvarid)  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Le champ <AGESNO"//str2//"> est absent"  
              agesno = 50.0  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, agesno(1,nsrf))  
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Lecture echouee pour <AGESNO"//str2//">"  
              stop 1  
           ENDIF  
           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**'  
        ierr = NF_GET_VAR_REAL(nid, nvarid, agesno(1,1))  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <AGESNO>"  
           stop 1  
        ENDIF  
        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  
   
   
     ierr = NF_INQ_VARID (nid, "ZMEA", nvarid)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Le champ <ZMEA> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zmea)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <ZMEA>'  
        stop 1  
     ENDIF  
332      xmin = 1.0E+20      xmin = 1.0E+20
333      xmax = -1.0E+20      xmax = -1.0E+20
334      DO i = 1, klon      DO i = 1, klon
335         xmin = MIN(zmea(i),xmin)         xmin = MIN(agesno(i, 1), xmin)
336         xmax = MAX(zmea(i),xmax)         xmax = MAX(agesno(i, 1), xmax)
337      ENDDO      ENDDO
338      PRINT*,'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax      PRINT *, 'Age de la neige <AGESNO>', xmin, xmax
   
339    
340      ierr = NF_INQ_VARID (nid, "ZSTD", nvarid)      call NF95_INQ_VARID(ncid, "ZMEA", varid)
341      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zmea)
        PRINT*, 'phyetat0: Le champ <ZSTD> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zstd)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <ZSTD>'  
        stop 1  
     ENDIF  
342      xmin = 1.0E+20      xmin = 1.0E+20
343      xmax = -1.0E+20      xmax = -1.0E+20
344      DO i = 1, klon      DO i = 1, klon
345         xmin = MIN(zstd(i),xmin)         xmin = MIN(zmea(i), xmin)
346         xmax = MAX(zstd(i),xmax)         xmax = MAX(zmea(i), xmax)
347      ENDDO      ENDDO
348      PRINT*,'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
349    
350        call NF95_INQ_VARID(ncid, "ZSTD", varid)
351      ierr = NF_INQ_VARID (nid, "ZSIG", nvarid)      call NF95_GET_VAR(ncid, varid, zstd)
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Le champ <ZSIG> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zsig)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <ZSIG>'  
        stop 1  
     ENDIF  
352      xmin = 1.0E+20      xmin = 1.0E+20
353      xmax = -1.0E+20      xmax = -1.0E+20
354      DO i = 1, klon      DO i = 1, klon
355         xmin = MIN(zsig(i),xmin)         xmin = MIN(zstd(i), xmin)
356         xmax = MAX(zsig(i),xmax)         xmax = MAX(zstd(i), xmax)
357      ENDDO      ENDDO
358      PRINT*,'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
   
359    
360      ierr = NF_INQ_VARID (nid, "ZGAM", nvarid)      call NF95_INQ_VARID(ncid, "ZSIG", varid)
361      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zsig)
        PRINT*, 'phyetat0: Le champ <ZGAM> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zgam)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <ZGAM>'  
        stop 1  
     ENDIF  
362      xmin = 1.0E+20      xmin = 1.0E+20
363      xmax = -1.0E+20      xmax = -1.0E+20
364      DO i = 1, klon      DO i = 1, klon
365         xmin = MIN(zgam(i),xmin)         xmin = MIN(zsig(i), xmin)
366         xmax = MAX(zgam(i),xmax)         xmax = MAX(zsig(i), xmax)
367      ENDDO      ENDDO
368      PRINT*,'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
   
369    
370      ierr = NF_INQ_VARID (nid, "ZTHE", nvarid)      call NF95_INQ_VARID(ncid, "ZGAM", varid)
371      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zgam)
        PRINT*, 'phyetat0: Le champ <ZTHE> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zthe)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <ZTHE>'  
        stop 1  
     ENDIF  
372      xmin = 1.0E+20      xmin = 1.0E+20
373      xmax = -1.0E+20      xmax = -1.0E+20
374      DO i = 1, klon      DO i = 1, klon
375         xmin = MIN(zthe(i),xmin)         xmin = MIN(zgam(i), xmin)
376         xmax = MAX(zthe(i),xmax)         xmax = MAX(zgam(i), xmax)
377      ENDDO      ENDDO
378      PRINT*,'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
379    
380        call NF95_INQ_VARID(ncid, "ZTHE", varid)
381        call NF95_GET_VAR(ncid, varid, zthe)
382        xmin = 1.0E+20
383        xmax = -1.0E+20
384        DO i = 1, klon
385           xmin = MIN(zthe(i), xmin)
386           xmax = MAX(zthe(i), xmax)
387        ENDDO
388        PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
389    
390      ierr = NF_INQ_VARID (nid, "ZPIC", nvarid)      call NF95_INQ_VARID(ncid, "ZPIC", varid)
391      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zpic)
        PRINT*, 'phyetat0: Le champ <ZPIC> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zpic)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <ZPIC>'  
        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
395         xmin = MIN(zpic(i),xmin)         xmin = MIN(zpic(i), xmin)
396         xmax = MAX(zpic(i),xmax)         xmax = MAX(zpic(i), xmax)
397      ENDDO      ENDDO
398      PRINT*,'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
399    
400      ierr = NF_INQ_VARID (nid, "ZVAL", nvarid)      call NF95_INQ_VARID(ncid, "ZVAL", varid)
401      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zval)
        PRINT*, 'phyetat0: Le champ <ZVAL> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zval)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, 'phyetat0: Lecture echouee pour <ZVAL>'  
        stop 1  
     ENDIF  
402      xmin = 1.0E+20      xmin = 1.0E+20
403      xmax = -1.0E+20      xmax = -1.0E+20
404      DO i = 1, klon      DO i = 1, klon
405         xmin = MIN(zval(i),xmin)         xmin = MIN(zval(i), xmin)
406         xmax = MAX(zval(i),xmax)         xmax = MAX(zval(i), xmax)
407      ENDDO      ENDDO
408      PRINT*,'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
409    
410      ancien_ok = .TRUE.      ancien_ok = .TRUE.
411    
412      ierr = NF_INQ_VARID (nid, "TANCIEN", nvarid)      ierr = NF90_INQ_VARID(ncid, "TANCIEN", varid)
413      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
414         PRINT*, "phyetat0: Le champ <TANCIEN> est absent"         PRINT *, "phyetat0: Le champ <TANCIEN> est absent"
415         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
416         ancien_ok = .FALSE.         ancien_ok = .FALSE.
417      ELSE      ELSE
418         ierr = NF_GET_VAR_REAL(nid, nvarid, t_ancien)         call nf95_get_var(ncid, varid, t_ancien)
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <TANCIEN>"  
           stop 1  
        ENDIF  
419      ENDIF      ENDIF
420    
421      ierr = NF_INQ_VARID (nid, "QANCIEN", nvarid)      ierr = NF90_INQ_VARID(ncid, "QANCIEN", varid)
422      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
423         PRINT*, "phyetat0: Le champ <QANCIEN> est absent"         PRINT *, "phyetat0: Le champ <QANCIEN> est absent"
424         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
425         ancien_ok = .FALSE.         ancien_ok = .FALSE.
426      ELSE      ELSE
427         ierr = NF_GET_VAR_REAL(nid, nvarid, q_ancien)         call nf95_get_var(ncid, varid, q_ancien)
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <QANCIEN>"  
           stop 1  
        ENDIF  
428      ENDIF      ENDIF
429    
430      ierr = NF_INQ_VARID (nid, "CLWCON", nvarid)      ierr = NF90_INQ_VARID(ncid, "CLWCON", varid)
431      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
432         PRINT*, "phyetat0: Le champ CLWCON est absent"         PRINT *, "phyetat0: Le champ CLWCON est absent"
433         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
434         clwcon = 0.         clwcon = 0.
435      ELSE      ELSE
436         ierr = NF_GET_VAR_REAL(nid, nvarid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
437         IF (ierr.NE.NF_NOERR) THEN         clwcon(:, 2:) = 0.
           PRINT*, "phyetat0: Lecture echouee pour <CLWCON>"  
           stop 1  
        ENDIF  
438      ENDIF      ENDIF
439      xmin = 1.0E+20      xmin = 1.0E+20
440      xmax = -1.0E+20      xmax = -1.0E+20
441      xmin = MINval(clwcon)      xmin = MINval(clwcon)
442      xmax = MAXval(clwcon)      xmax = MAXval(clwcon)
443      PRINT*,'Eau liquide convective (ecart-type) clwcon:', xmin, xmax      PRINT *, 'Eau liquide convective (ecart-type) clwcon:', xmin, xmax
444    
445      ierr = NF_INQ_VARID (nid, "RNEBCON", nvarid)      ierr = NF90_INQ_VARID(ncid, "RNEBCON", varid)
446      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
447         PRINT*, "phyetat0: Le champ RNEBCON est absent"         PRINT *, "phyetat0: Le champ RNEBCON est absent"
448         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
449         rnebcon = 0.         rnebcon = 0.
450      ELSE      ELSE
451         ierr = NF_GET_VAR_REAL(nid, nvarid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
452         IF (ierr.NE.NF_NOERR) THEN         rnebcon(:, 2:) = 0.
           PRINT*, "phyetat0: Lecture echouee pour <RNEBCON>"  
           stop 1  
        ENDIF  
453      ENDIF      ENDIF
454      xmin = 1.0E+20      xmin = 1.0E+20
455      xmax = -1.0E+20      xmax = -1.0E+20
456      xmin = MINval(rnebcon)      xmin = MINval(rnebcon)
457      xmax = MAXval(rnebcon)      xmax = MAXval(rnebcon)
458      PRINT*,'Nebulosite convective (ecart-type) rnebcon:', xmin, xmax      PRINT *, 'Nebulosite convective (ecart-type) rnebcon:', xmin, xmax
   
   
     ierr = NF_INQ_VARID (nid, "QANCIEN", nvarid)  
     IF (ierr.NE.NF_NOERR) THEN  
        PRINT*, "phyetat0: Le champ <QANCIEN> est absent"  
        PRINT*, "Depart legerement fausse. Mais je continue"  
        ancien_ok = .FALSE.  
     ELSE  
        ierr = NF_GET_VAR_REAL(nid, nvarid, q_ancien)  
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <QANCIEN>"  
           stop 1  
        ENDIF  
     ENDIF  
459    
460      ! Lecture ratqs      ! Lecture ratqs
461    
462      ierr = NF_INQ_VARID (nid, "RATQS", nvarid)      ierr = NF90_INQ_VARID(ncid, "RATQS", varid)
463      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
464         PRINT*, "phyetat0: Le champ <RATQS> est absent"         PRINT *, "phyetat0: Le champ <RATQS> est absent"
465         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
466         ratqs = 0.         ratqs = 0.
467      ELSE      ELSE
468         ierr = NF_GET_VAR_REAL(nid, nvarid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
469         IF (ierr.NE.NF_NOERR) THEN         ratqs(:, 2:) = 0.
           PRINT*, "phyetat0: Lecture echouee pour <RATQS>"  
           stop 1  
        ENDIF  
470      ENDIF      ENDIF
471      xmin = 1.0E+20      xmin = 1.0E+20
472      xmax = -1.0E+20      xmax = -1.0E+20
473      xmin = MINval(ratqs)      xmin = MINval(ratqs)
474      xmax = MAXval(ratqs)      xmax = MAXval(ratqs)
475      PRINT*,'(ecart-type) ratqs:', xmin, xmax      PRINT *, '(ecart-type) ratqs:', xmin, xmax
476    
477      ! Lecture run_off_lic_0      ! Lecture run_off_lic_0
478    
479      ierr = NF_INQ_VARID (nid, "RUNOFFLIC0", nvarid)      ierr = NF90_INQ_VARID(ncid, "RUNOFFLIC0", varid)
480      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
481         PRINT*, "phyetat0: Le champ <RUNOFFLIC0> est absent"         PRINT *, "phyetat0: Le champ <RUNOFFLIC0> est absent"
482         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
483         run_off_lic_0 = 0.         run_off_lic_0 = 0.
484      ELSE      ELSE
485         ierr = NF_GET_VAR_REAL(nid, nvarid, run_off_lic_0)         call nf95_get_var(ncid, varid, run_off_lic_0)
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <RUNOFFLIC0>"  
           stop 1  
        ENDIF  
486      ENDIF      ENDIF
487      xmin = 1.0E+20      xmin = 1.0E+20
488      xmax = -1.0E+20      xmax = -1.0E+20
489      xmin = MINval(run_off_lic_0)      xmin = MINval(run_off_lic_0)
490      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
491      PRINT*,'(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
492    
493        call nf95_inq_varid(ncid, "sig1", varid)
494        call nf95_get_var(ncid, varid, sig1)
495    
496      ! Fermer le fichier:      call nf95_inq_varid(ncid, "w01", varid)
497        call nf95_get_var(ncid, varid, w01)
498    
499      ierr = NF_CLOSE(nid)      call NF95_CLOSE(ncid)
500    
501    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0
502    

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

  ViewVC Help
Powered by ViewVC 1.1.21