/[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 43 by guez, Fri Apr 8 12:43:31 2011 UTC trunk/Sources/phylmd/phyetat0.f revision 155 by guez, Wed Jul 8 17:03:45 2015 UTC
# Line 4  module phyetat0_m Line 4  module phyetat0_m
4    
5    IMPLICIT none    IMPLICIT none
6    
7    REAL, save:: rlat(klon), rlon(klon) ! latitude and longitude, in degrees    REAL, save:: rlat(klon), rlon(klon)
8      ! latitude and longitude of a point of the scalar grid identified
9      ! by a simple index, in degrees
10    
11    private klon    private klon
12    
13  contains  contains
14    
15    SUBROUTINE phyetat0(fichnom, pctsrf, tsol,tsoil, ocean, tslab,seaice, &    SUBROUTINE phyetat0(pctsrf, tsol, tsoil, tslab, seaice, qsurf, qsol, &
16         qsurf,qsol,snow, &         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, nf90_inq_varid, NF90_NOERR  
     use netcdf95, only: handle_err, nf95_get_var  
     use dimphy, only: zmasq, klev  
   
     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, nsrf
73      INTEGER ierr, i, nsrf, isoil      CHARACTER(len=2) str2
     CHARACTER*7 str7  
     CHARACTER*2 str2  
74    
75      !---------------------------------------------------------------      !---------------------------------------------------------------
76    
77      print *, "Call sequence information: phyetat0"      print *, "Call sequence information: phyetat0"
78    
79      ! Ouvrir le fichier contenant l'etat initial:      ! Fichier contenant l'état initial :
80        call NF95_OPEN("startphy.nc", NF90_NOWRITE, ncid)
     print *, 'fichnom = ', fichnom  
     ierr = NF_OPEN (fichnom, NF_NOWRITE,nid)  
     IF (ierr.NE.NF90_NOERR) THEN  
        write(6,*)' Pb d''ouverture du fichier '//fichnom  
        write(6,*)' ierr = ', ierr  
        STOP 1  
     ENDIF  
81    
82      ierr = nf90_get_att(nid, nf90_global, "itau_phy", itau_phy)      call nf95_get_att(ncid, nf90_global, "itau_phy", itau_phy)
     call handle_err("phyetat0 itau_phy", ierr, nid, nf90_global)  
83    
84      ! Lecture des latitudes (coordonnees):      ! Lecture des latitudes (coordonnees):
85    
86      ierr = NF90_INQ_VARID (nid, "latitude", nvarid)      call NF95_INQ_VARID(ncid, "latitude", varid)
87      IF (ierr.NE.NF90_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.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <latitude>'  
        stop 1  
     ENDIF  
88    
89      ! Lecture des longitudes (coordonnees):      ! Lecture des longitudes (coordonnees):
90    
91      ierr = NF90_INQ_VARID (nid, "longitude", nvarid)      call NF95_INQ_VARID(ncid, "longitude", varid)
92      IF (ierr.NE.NF90_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.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <latitude>'  
        stop 1  
     ENDIF  
   
93    
94      ! Lecture du masque terre mer      ! Lecture du masque terre mer
95    
96      ierr = NF90_INQ_VARID (nid, "masque", nvarid)      call NF95_INQ_VARID(ncid, "masque", varid)
97      IF (ierr ==  NF90_NOERR) THEN      call nf95_get_var(ncid, varid, zmasq)
98         call nf95_get_var(nid, nvarid, zmasq)  
     else  
        PRINT *, 'phyetat0: Le champ <masque> est absent'  
        PRINT *, 'fichier startphy non compatible avec phyetat0'  
        !      stop 1  
     ENDIF  
99      ! Lecture des fractions pour chaque sous-surface      ! Lecture des fractions pour chaque sous-surface
100    
101      ! initialisation des sous-surfaces      ! initialisation des sous-surfaces
# Line 136  contains Line 104  contains
104    
105      ! fraction de terre      ! fraction de terre
106    
107      ierr = NF90_INQ_VARID (nid, "FTER", nvarid)      ierr = NF90_INQ_VARID(ncid, "FTER", varid)
108      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
109         call nf95_get_var(nid, nvarid, pctsrf(1 : klon,is_ter))         call nf95_get_var(ncid, varid, pctsrf(:, is_ter))
110      else      else
111         PRINT *, 'phyetat0: Le champ <FTER> est absent'         PRINT *, 'phyetat0: Le champ <FTER> est absent'
        !$$$         stop 1  
112      ENDIF      ENDIF
113    
114      ! fraction de glace de terre      ! fraction de glace de terre
115    
116      ierr = NF90_INQ_VARID (nid, "FLIC", nvarid)      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)
117      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
118         call nf95_get_var(nid, nvarid, pctsrf(1 : klon,is_lic))         call nf95_get_var(ncid, varid, pctsrf(:, is_lic))
119      else      else
120         PRINT *, 'phyetat0: Le champ <FLIC> est absent'         PRINT *, 'phyetat0: Le champ <FLIC> est absent'
        !$$$         stop 1  
121      ENDIF      ENDIF
122    
123      ! fraction d'ocean      ! fraction d'ocean
124    
125      ierr = NF90_INQ_VARID (nid, "FOCE", nvarid)      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)
126      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
127         call nf95_get_var(nid, nvarid, pctsrf(1 : klon,is_oce))         call nf95_get_var(ncid, varid, pctsrf(:, is_oce))
128      else      else
129         PRINT *, 'phyetat0: Le champ <FOCE> est absent'         PRINT *, 'phyetat0: Le champ <FOCE> est absent'
        !$$$         stop 1  
130      ENDIF      ENDIF
131    
132      ! fraction glace de mer      ! fraction glace de mer
133    
134      ierr = NF90_INQ_VARID (nid, "FSIC", nvarid)      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)
135      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
136         call nf95_get_var(nid, nvarid, pctsrf(1 : klon, is_sic))         call nf95_get_var(ncid, varid, pctsrf(:, is_sic))
137      else      else
138         PRINT *, 'phyetat0: Le champ <FSIC> est absent'         PRINT *, 'phyetat0: Le champ <FSIC> est absent'
        !$$$         stop 1  
139      ENDIF      ENDIF
140    
141      !  Verification de l'adequation entre le masque et les sous-surfaces      ! Verification de l'adequation entre le masque et les sous-surfaces
142    
143      fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &      fractint = pctsrf(:, is_ter) + pctsrf(:, is_lic)
          + pctsrf(1 : klon, is_lic)  
144      DO i = 1 , klon      DO i = 1 , klon
145         IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN         IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN
146            WRITE(*,*) 'phyetat0: attention fraction terre pas ',  &            WRITE(*, *) 'phyetat0: attention fraction terre pas ', &
147                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
148                 ,pctsrf(i, is_lic)                 , pctsrf(i, is_lic)
149         ENDIF         ENDIF
150      END DO      END DO
151      fractint (1 : klon) =  pctsrf(1 : klon, is_oce)  &      fractint = pctsrf(:, is_oce) + pctsrf(:, is_sic)
          + pctsrf(1 : klon, is_sic)  
152      DO i = 1 , klon      DO i = 1 , klon
153         IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN         IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN
154            WRITE(*,*) 'phyetat0 attention fraction ocean pas ',  &            WRITE(*, *) 'phyetat0 attention fraction ocean pas ', &
155                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
156                 ,pctsrf(i, is_sic)                 , pctsrf(i, is_sic)
157         ENDIF         ENDIF
158      END DO      END DO
159    
160      ! Lecture des temperatures du sol:      ! Lecture des temperatures du sol:
161        call NF95_INQ_VARID(ncid, "TS", varid)
162        call nf95_inquire_variable(ncid, varid, ndims = ndims)
163        if (ndims == 2) then
164           call NF95_GET_VAR(ncid, varid, tsol)
165        else
166           print *, "Found only one surface type for soil temperature."
167           call nf95_get_var(ncid, varid, tsol(:, 1))
168           tsol(:, 2:nbsrf) = spread(tsol(:, 1), dim = 2, ncopies = nbsrf - 1)
169        end if      
170    
171      ierr = NF90_INQ_VARID (nid, "TS", nvarid)     ! Lecture des temperatures du sol profond:
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Le champ <TS> est absent'  
        PRINT *, '          Mais je vais essayer de lire TS**'  
        DO nsrf = 1, nbsrf  
           IF (nsrf.GT.99) THEN  
              PRINT *, "Trop de sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str2,'(i2.2)') nsrf  
           ierr = NF90_INQ_VARID (nid, "TS"//str2, nvarid)  
           IF (ierr.NE.NF90_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.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**'  
        call nf95_get_var(nid, nvarid, tsol(:,1))  
        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  
   
     ! Lecture des temperatures du sol profond:  
172    
173      DO nsrf = 1, nbsrf      call NF95_INQ_VARID(ncid, 'Tsoil', varid)
174         DO isoil=1, nsoilmx      call NF95_GET_VAR(ncid, varid, tsoil)
           IF (isoil.GT.99 .AND. nsrf.GT.99) THEN  
              PRINT *, "Trop de couches ou sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str7,'(i2.2,"srf",i2.2)') isoil, nsrf  
           ierr = NF90_INQ_VARID (nid, 'Tsoil'//str7, nvarid)  
           IF (ierr.NE.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 = NF_GET_VAR_REAL(nid, nvarid, tsoil(1,isoil,nsrf))  
              IF (ierr.NE.NF90_NOERR) THEN  
                 PRINT *, "Lecture echouee pour <Tsoil"//str7//">"  
                 stop 1  
              ENDIF  
           ENDIF  
        ENDDO  
     ENDDO  
175    
176      !IM "slab" ocean      !IM "slab" ocean
177        ! Lecture de tslab (pour slab ocean seulement):
178      ! Lecture de tslab (pour slab ocean seulement):            tslab = 0.
179        seaice = 0.
     IF (ocean .eq. 'slab  ') then  
        ierr = NF90_INQ_VARID (nid, "TSLAB", nvarid)  
        IF (ierr.NE.NF90_NOERR) THEN  
           PRINT *, "phyetat0: Le champ <TSLAB> est absent"  
           stop 1  
        ENDIF  
        call nf95_get_var(nid, nvarid, 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 (nid, "SEAICE", nvarid)  
        IF (ierr.NE.NF90_NOERR) THEN  
           PRINT *, "phyetat0: Le champ <SEAICE> est absent"  
           stop 1  
        ENDIF  
        call nf95_get_var(nid, nvarid, seaice)  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(seaice(i),xmin)  
           xmax = MAX(seaice(i),xmax)  
        ENDDO  
        PRINT *,'Masse de la glace de mer seaice:', xmin, xmax  
     ELSE  
        tslab = 0.  
        seaice = 0.  
     ENDIF  
180    
181      ! Lecture de l'humidite de l'air juste au dessus du sol:      ! Lecture de l'humidite de l'air juste au dessus du sol:
182    
183      ierr = NF90_INQ_VARID (nid, "QS", nvarid)      ierr = NF90_INQ_VARID(ncid, "QS", varid)
184      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
185         PRINT *, 'phyetat0: Le champ <QS> est absent'         PRINT *, 'phyetat0: Le champ <QS> est absent'
186         PRINT *, '          Mais je vais essayer de lire QS**'         PRINT *, ' Mais je vais essayer de lire QS**'
187         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
188            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
189               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
190               stop 1               stop 1
191            ENDIF            ENDIF
192            WRITE(str2,'(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
193            ierr = NF90_INQ_VARID (nid, "QS"//str2, nvarid)            call NF95_INQ_VARID(ncid, "QS"//str2, varid)
194            IF (ierr.NE.NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, qsurf(:, nsrf))
              PRINT *, "phyetat0: Le champ <QS"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, qsurf(1,nsrf))  
           IF (ierr.NE.NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <QS"//str2//">"  
              stop 1  
           ENDIF  
195            xmin = 1.0E+20            xmin = 1.0E+20
196            xmax = -1.0E+20            xmax = -1.0E+20
197            DO i = 1, klon            DO i = 1, klon
198               xmin = MIN(qsurf(i,nsrf),xmin)               xmin = MIN(qsurf(i, nsrf), xmin)
199               xmax = MAX(qsurf(i,nsrf),xmax)               xmax = MAX(qsurf(i, nsrf), xmax)
200            ENDDO            ENDDO
201            PRINT *,'Humidite pres du sol QS**:', nsrf, xmin, xmax            PRINT *, 'Humidite pres du sol QS**:', nsrf, xmin, xmax
202         ENDDO         ENDDO
203      ELSE      ELSE
204         PRINT *, 'phyetat0: Le champ <QS> est present'         PRINT *, 'phyetat0: Le champ <QS> est present'
205         PRINT *, '          J ignore donc les autres humidites QS**'         PRINT *, ' J ignore donc les autres humidites QS**'
206         call nf95_get_var(nid, nvarid, qsurf(:,1))         call nf95_get_var(ncid, varid, qsurf(:, 1))
207         xmin = 1.0E+20         xmin = 1.0E+20
208         xmax = -1.0E+20         xmax = -1.0E+20
209         DO i = 1, klon         DO i = 1, klon
210            xmin = MIN(qsurf(i,1),xmin)            xmin = MIN(qsurf(i, 1), xmin)
211            xmax = MAX(qsurf(i,1),xmax)            xmax = MAX(qsurf(i, 1), xmax)
212         ENDDO         ENDDO
213         PRINT *,'Humidite pres du sol <QS>', xmin, xmax         PRINT *, 'Humidite pres du sol <QS>', xmin, xmax
214         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
215            DO i = 1, klon            DO i = 1, klon
216               qsurf(i,nsrf) = qsurf(i,1)               qsurf(i, nsrf) = qsurf(i, 1)
217            ENDDO            ENDDO
218         ENDDO         ENDDO
219      ENDIF      ENDIF
220    
221      ! Eau dans le sol (pour le modele de sol "bucket")      ! Eau dans le sol (pour le modele de sol "bucket")
222    
223      ierr = NF90_INQ_VARID(nid, "QSOL", nvarid)      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
224      IF (ierr ==  NF90_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
225         call nf95_get_var(nid, nvarid, qsol)         call nf95_get_var(ncid, varid, qsol)
226      else      else
227         PRINT *, 'phyetat0: Le champ <QSOL> est absent'         PRINT *, 'phyetat0: Le champ <QSOL> est absent'
228         PRINT *, '          Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
229         qsol = 0.         qsol = 0.
230      ENDIF      ENDIF
     xmin = 1.0E+20  
     xmax = -1.0E+20  
     DO i = 1, klon  
        xmin = MIN(qsol(i),xmin)  
        xmax = MAX(qsol(i),xmax)  
     ENDDO  
     PRINT *,'Eau dans le sol (mm) <QSOL>', xmin, xmax  
231    
232      ! Lecture de neige au sol:      ! Lecture de neige au sol:
233    
234      ierr = NF90_INQ_VARID (nid, "SNOW", nvarid)      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)
235      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
236         PRINT *, 'phyetat0: Le champ <SNOW> est absent'         PRINT *, 'phyetat0: Le champ <SNOW> est absent'
237         PRINT *, '          Mais je vais essayer de lire SNOW**'         PRINT *, ' Mais je vais essayer de lire SNOW**'
238         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
239            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
240               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
241               stop 1               stop 1
242            ENDIF            ENDIF
243            WRITE(str2,'(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
244            ierr = NF90_INQ_VARID (nid, "SNOW"//str2, nvarid)            call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)
245            IF (ierr.NE.NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, snow(:, nsrf))
              PRINT *, "phyetat0: Le champ <SNOW"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, snow(1,nsrf))  
           IF (ierr.NE.NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <SNOW"//str2//">"  
              stop 1  
           ENDIF  
246            xmin = 1.0E+20            xmin = 1.0E+20
247            xmax = -1.0E+20            xmax = -1.0E+20
248            DO i = 1, klon            DO i = 1, klon
249               xmin = MIN(snow(i,nsrf),xmin)               xmin = MIN(snow(i, nsrf), xmin)
250               xmax = MAX(snow(i,nsrf),xmax)               xmax = MAX(snow(i, nsrf), xmax)
251            ENDDO            ENDDO
252            PRINT *,'Neige du sol SNOW**:', nsrf, xmin, xmax            PRINT *, 'Neige du sol SNOW**:', nsrf, xmin, xmax
253         ENDDO         ENDDO
254      ELSE      ELSE
255         PRINT *, 'phyetat0: Le champ <SNOW> est present'         PRINT *, 'phyetat0: Le champ <SNOW> est present'
256         PRINT *, '          J ignore donc les autres neiges SNOW**'         PRINT *, ' J ignore donc les autres neiges SNOW**'
257         call nf95_get_var(nid, nvarid, snow(:,1))         call nf95_get_var(ncid, varid, snow(:, 1))
258         xmin = 1.0E+20         xmin = 1.0E+20
259         xmax = -1.0E+20         xmax = -1.0E+20
260         DO i = 1, klon         DO i = 1, klon
261            xmin = MIN(snow(i,1),xmin)            xmin = MIN(snow(i, 1), xmin)
262            xmax = MAX(snow(i,1),xmax)            xmax = MAX(snow(i, 1), xmax)
263         ENDDO         ENDDO
264         PRINT *,'Neige du sol <SNOW>', xmin, xmax         PRINT *, 'Neige du sol <SNOW>', xmin, xmax
265         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
266            DO i = 1, klon            DO i = 1, klon
267               snow(i,nsrf) = snow(i,1)               snow(i, nsrf) = snow(i, 1)
268            ENDDO            ENDDO
269         ENDDO         ENDDO
270      ENDIF      ENDIF
271    
272      ! Lecture de albedo au sol:      ! Lecture de albedo au sol:
273    
274      ierr = NF90_INQ_VARID (nid, "ALBE", nvarid)      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)
275      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
276         PRINT *, 'phyetat0: Le champ <ALBE> est absent'         PRINT *, 'phyetat0: Le champ <ALBE> est absent'
277         PRINT *, '          Mais je vais essayer de lire ALBE**'         PRINT *, ' Mais je vais essayer de lire ALBE**'
278         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
279            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
280               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
281               stop 1               stop 1
282            ENDIF            ENDIF
283            WRITE(str2,'(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
284            ierr = NF90_INQ_VARID (nid, "ALBE"//str2, nvarid)            call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)
285            IF (ierr.NE.NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, albe(:, nsrf))
              PRINT *, "phyetat0: Le champ <ALBE"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, albe(1,nsrf))  
           IF (ierr.NE.NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <ALBE"//str2//">"  
              stop 1  
           ENDIF  
286            xmin = 1.0E+20            xmin = 1.0E+20
287            xmax = -1.0E+20            xmax = -1.0E+20
288            DO i = 1, klon            DO i = 1, klon
289               xmin = MIN(albe(i,nsrf),xmin)               xmin = MIN(albe(i, nsrf), xmin)
290               xmax = MAX(albe(i,nsrf),xmax)               xmax = MAX(albe(i, nsrf), xmax)
291            ENDDO            ENDDO
292            PRINT *,'Albedo du sol ALBE**:', nsrf, xmin, xmax            PRINT *, 'Albedo du sol ALBE**:', nsrf, xmin, xmax
293         ENDDO         ENDDO
294      ELSE      ELSE
295         PRINT *, 'phyetat0: Le champ <ALBE> est present'         PRINT *, 'phyetat0: Le champ <ALBE> est present'
296         PRINT *, '          J ignore donc les autres ALBE**'         PRINT *, ' J ignore donc les autres ALBE**'
297         call nf95_get_var(nid, nvarid, albe(:,1))         call nf95_get_var(ncid, varid, albe(:, 1))
298         xmin = 1.0E+20         xmin = 1.0E+20
299         xmax = -1.0E+20         xmax = -1.0E+20
300         DO i = 1, klon         DO i = 1, klon
301            xmin = MIN(albe(i,1),xmin)            xmin = MIN(albe(i, 1), xmin)
302            xmax = MAX(albe(i,1),xmax)            xmax = MAX(albe(i, 1), xmax)
303         ENDDO         ENDDO
304         PRINT *,'Neige du sol <ALBE>', xmin, xmax         PRINT *, 'Neige du sol <ALBE>', xmin, xmax
305         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
306            DO i = 1, klon            DO i = 1, klon
307               albe(i,nsrf) = albe(i,1)               albe(i, nsrf) = albe(i, 1)
308            ENDDO            ENDDO
309         ENDDO         ENDDO
310      ENDIF      ENDIF
311    
312        ! Lecture de evaporation:
313    
314      ! Lecture de albedo au sol LW:      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)
315        IF (ierr /= NF90_NOERR) THEN
     ierr = NF90_INQ_VARID (nid, "ALBLW", nvarid)  
     IF (ierr.NE.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(nid, nvarid, alblw(:,1))  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(alblw(i,1),xmin)  
           xmax = MAX(alblw(i,1),xmax)  
        ENDDO  
        PRINT *,'Neige du sol <ALBLW>', xmin, xmax  
        DO nsrf = 2, nbsrf  
           DO i = 1, klon  
              alblw(i,nsrf) = alblw(i,1)  
           ENDDO  
        ENDDO  
     ENDIF  
   
     ! Lecture de evaporation:    
   
     ierr = NF90_INQ_VARID (nid, "EVAP", nvarid)  
     IF (ierr.NE.NF90_NOERR) THEN  
316         PRINT *, 'phyetat0: Le champ <EVAP> est absent'         PRINT *, 'phyetat0: Le champ <EVAP> est absent'
317         PRINT *, '          Mais je vais essayer de lire EVAP**'         PRINT *, ' Mais je vais essayer de lire EVAP**'
318         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
319            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
320               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
321               stop 1               stop 1
322            ENDIF            ENDIF
323            WRITE(str2,'(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
324            ierr = NF90_INQ_VARID (nid, "EVAP"//str2, nvarid)            call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)
325            IF (ierr.NE.NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, evap(:, nsrf))
              PRINT *, "phyetat0: Le champ <EVAP"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, evap(1,nsrf))  
           IF (ierr.NE.NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <EVAP"//str2//">"  
              stop 1  
           ENDIF  
326            xmin = 1.0E+20            xmin = 1.0E+20
327            xmax = -1.0E+20            xmax = -1.0E+20
328            DO i = 1, klon            DO i = 1, klon
329               xmin = MIN(evap(i,nsrf),xmin)               xmin = MIN(evap(i, nsrf), xmin)
330               xmax = MAX(evap(i,nsrf),xmax)               xmax = MAX(evap(i, nsrf), xmax)
331            ENDDO            ENDDO
332            PRINT *,'evap du sol EVAP**:', nsrf, xmin, xmax            PRINT *, 'evap du sol EVAP**:', nsrf, xmin, xmax
333         ENDDO         ENDDO
334      ELSE      ELSE
335         PRINT *, 'phyetat0: Le champ <EVAP> est present'         PRINT *, 'phyetat0: Le champ <EVAP> est present'
336         PRINT *, '          J ignore donc les autres EVAP**'         PRINT *, ' J ignore donc les autres EVAP**'
337         call nf95_get_var(nid, nvarid, evap(:,1))         call nf95_get_var(ncid, varid, evap(:, 1))
338         xmin = 1.0E+20         xmin = 1.0E+20
339         xmax = -1.0E+20         xmax = -1.0E+20
340         DO i = 1, klon         DO i = 1, klon
341            xmin = MIN(evap(i,1),xmin)            xmin = MIN(evap(i, 1), xmin)
342            xmax = MAX(evap(i,1),xmax)            xmax = MAX(evap(i, 1), xmax)
343         ENDDO         ENDDO
344         PRINT *,'Evap du sol <EVAP>', xmin, xmax         PRINT *, 'Evap du sol <EVAP>', xmin, xmax
345         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
346            DO i = 1, klon            DO i = 1, klon
347               evap(i,nsrf) = evap(i,1)               evap(i, nsrf) = evap(i, 1)
348            ENDDO            ENDDO
349         ENDDO         ENDDO
350      ENDIF      ENDIF
351    
352      ! Lecture precipitation liquide:      ! Lecture precipitation liquide:
353    
354      ierr = NF90_INQ_VARID (nid, "rain_f", nvarid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
355      IF (ierr.NE.NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, rain_fall)
        PRINT *, 'phyetat0: Le champ <rain_f> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, rain_fall)  
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <rain_f>'  
        stop 1  
     ENDIF  
     xmin = 1.0E+20  
     xmax = -1.0E+20  
     DO i = 1, klon  
        xmin = MIN(rain_fall(i),xmin)  
        xmax = MAX(rain_fall(i),xmax)  
     ENDDO  
     PRINT *,'Precipitation liquide rain_f:', xmin, xmax  
356    
357      ! Lecture precipitation solide:      ! Lecture precipitation solide:
358    
359      ierr = NF90_INQ_VARID (nid, "snow_f", nvarid)      call NF95_INQ_VARID(ncid, "snow_f", varid)
360      IF (ierr.NE.NF90_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.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <snow_f>'  
        stop 1  
     ENDIF  
361      xmin = 1.0E+20      xmin = 1.0E+20
362      xmax = -1.0E+20      xmax = -1.0E+20
363      DO i = 1, klon      DO i = 1, klon
364         xmin = MIN(snow_fall(i),xmin)         xmin = MIN(snow_fall(i), xmin)
365         xmax = MAX(snow_fall(i),xmax)         xmax = MAX(snow_fall(i), xmax)
366      ENDDO      ENDDO
367      PRINT *,'Precipitation solide snow_f:', xmin, xmax      PRINT *, 'Precipitation solide snow_f:', xmin, xmax
368    
369      ! Lecture rayonnement solaire au sol:      ! Lecture rayonnement solaire au sol:
370    
371      ierr = NF90_INQ_VARID (nid, "solsw", nvarid)      ierr = NF90_INQ_VARID(ncid, "solsw", varid)
372      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
373         PRINT *, 'phyetat0: Le champ <solsw> est absent'         PRINT *, 'phyetat0: Le champ <solsw> est absent'
374         PRINT *, 'mis a zero'         PRINT *, 'mis a zero'
375         solsw = 0.         solsw = 0.
376      ELSE      ELSE
377         call nf95_get_var(nid, nvarid, solsw)         call nf95_get_var(ncid, varid, solsw)
378      ENDIF      ENDIF
379      xmin = 1.0E+20      xmin = 1.0E+20
380      xmax = -1.0E+20      xmax = -1.0E+20
381      DO i = 1, klon      DO i = 1, klon
382         xmin = MIN(solsw(i),xmin)         xmin = MIN(solsw(i), xmin)
383         xmax = MAX(solsw(i),xmax)         xmax = MAX(solsw(i), xmax)
384      ENDDO      ENDDO
385      PRINT *,'Rayonnement solaire au sol solsw:', xmin, xmax      PRINT *, 'Rayonnement solaire au sol solsw:', xmin, xmax
386    
387      ! Lecture rayonnement IF au sol:      ! Lecture rayonnement IF au sol:
388    
389      ierr = NF90_INQ_VARID (nid, "sollw", nvarid)      ierr = NF90_INQ_VARID(ncid, "sollw", varid)
390      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
391         PRINT *, 'phyetat0: Le champ <sollw> est absent'         PRINT *, 'phyetat0: Le champ <sollw> est absent'
392         PRINT *, 'mis a zero'         PRINT *, 'mis a zero'
393         sollw = 0.         sollw = 0.
394      ELSE      ELSE
395         call nf95_get_var(nid, nvarid, sollw)         call nf95_get_var(ncid, varid, sollw)
396      ENDIF      ENDIF
397      xmin = 1.0E+20      PRINT *, 'Rayonnement IF au sol sollw:', minval(sollw), maxval(sollw)
     xmax = -1.0E+20  
     DO i = 1, klon  
        xmin = MIN(sollw(i),xmin)  
        xmax = MAX(sollw(i),xmax)  
     ENDDO  
     PRINT *,'Rayonnement IF au sol sollw:', xmin, xmax  
   
398    
399      ! Lecture derive des flux:      ! Lecture derive des flux:
400    
401      ierr = NF90_INQ_VARID (nid, "fder", nvarid)      ierr = NF90_INQ_VARID(ncid, "fder", varid)
402      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
403         PRINT *, 'phyetat0: Le champ <fder> est absent'         PRINT *, 'phyetat0: Le champ <fder> est absent'
404         PRINT *, 'mis a zero'         PRINT *, 'mis a zero'
405         fder = 0.         fder = 0.
406      ELSE      ELSE
407         call nf95_get_var(nid, nvarid, fder)         call nf95_get_var(ncid, varid, fder)
408      ENDIF      ENDIF
409      xmin = 1.0E+20      xmin = 1.0E+20
410      xmax = -1.0E+20      xmax = -1.0E+20
411      DO i = 1, klon      DO i = 1, klon
412         xmin = MIN(fder(i),xmin)         xmin = MIN(fder(i), xmin)
413         xmax = MAX(fder(i),xmax)         xmax = MAX(fder(i), xmax)
414      ENDDO      ENDDO
415      PRINT *,'Derive des flux fder:', xmin, xmax      PRINT *, 'Derive des flux fder:', xmin, xmax
   
416    
417      ! Lecture du rayonnement net au sol:      ! Lecture du rayonnement net au sol:
418    
419      ierr = NF90_INQ_VARID (nid, "RADS", nvarid)      call NF95_INQ_VARID(ncid, "RADS", varid)
420      IF (ierr.NE.NF90_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.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <RADS>'  
        stop 1  
     ENDIF  
421      xmin = 1.0E+20      xmin = 1.0E+20
422      xmax = -1.0E+20      xmax = -1.0E+20
423      DO i = 1, klon      DO i = 1, klon
424         xmin = MIN(radsol(i),xmin)         xmin = MIN(radsol(i), xmin)
425         xmax = MAX(radsol(i),xmax)         xmax = MAX(radsol(i), xmax)
426      ENDDO      ENDDO
427      PRINT *,'Rayonnement net au sol radsol:', xmin, xmax      PRINT *, 'Rayonnement net au sol radsol:', xmin, xmax
428    
429      ! Lecture de la longueur de rugosite      ! Lecture de la longueur de rugosite
430    
431        ierr = NF90_INQ_VARID(ncid, "RUG", varid)
432      ierr = NF90_INQ_VARID (nid, "RUG", nvarid)      IF (ierr /= NF90_NOERR) THEN
     IF (ierr.NE.NF90_NOERR) THEN  
433         PRINT *, 'phyetat0: Le champ <RUG> est absent'         PRINT *, 'phyetat0: Le champ <RUG> est absent'
434         PRINT *, '          Mais je vais essayer de lire RUG**'         PRINT *, ' Mais je vais essayer de lire RUG**'
435         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
436            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
437               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
438               stop 1               stop 1
439            ENDIF            ENDIF
440            WRITE(str2,'(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
441            ierr = NF90_INQ_VARID (nid, "RUG"//str2, nvarid)            call NF95_INQ_VARID(ncid, "RUG"//str2, varid)
442            IF (ierr.NE.NF90_NOERR) THEN            call NF95_GET_VAR(ncid, varid, frugs(:, nsrf))
              PRINT *, "phyetat0: Le champ <RUG"//str2//"> est absent"  
              stop 1  
           ENDIF  
           ierr = NF_GET_VAR_REAL(nid, nvarid, frugs(1,nsrf))  
           IF (ierr.NE.NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <RUG"//str2//">"  
              stop 1  
           ENDIF  
443            xmin = 1.0E+20            xmin = 1.0E+20
444            xmax = -1.0E+20            xmax = -1.0E+20
445            DO i = 1, klon            DO i = 1, klon
446               xmin = MIN(frugs(i,nsrf),xmin)               xmin = MIN(frugs(i, nsrf), xmin)
447               xmax = MAX(frugs(i,nsrf),xmax)               xmax = MAX(frugs(i, nsrf), xmax)
448            ENDDO            ENDDO
449            PRINT *,'rugosite du sol RUG**:', nsrf, xmin, xmax            PRINT *, 'rugosite du sol RUG**:', nsrf, xmin, xmax
450         ENDDO         ENDDO
451      ELSE      ELSE
452         PRINT *, 'phyetat0: Le champ <RUG> est present'         PRINT *, 'phyetat0: Le champ <RUG> est present'
453         PRINT *, '          J ignore donc les autres RUG**'         PRINT *, ' J ignore donc les autres RUG**'
454         call nf95_get_var(nid, nvarid, frugs(:,1))         call nf95_get_var(ncid, varid, frugs(:, 1))
455         xmin = 1.0E+20         xmin = 1.0E+20
456         xmax = -1.0E+20         xmax = -1.0E+20
457         DO i = 1, klon         DO i = 1, klon
458            xmin = MIN(frugs(i,1),xmin)            xmin = MIN(frugs(i, 1), xmin)
459            xmax = MAX(frugs(i,1),xmax)            xmax = MAX(frugs(i, 1), xmax)
460         ENDDO         ENDDO
461         PRINT *,'rugosite <RUG>', xmin, xmax         PRINT *, 'rugosite <RUG>', xmin, xmax
462         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
463            DO i = 1, klon            DO i = 1, klon
464               frugs(i,nsrf) = frugs(i,1)               frugs(i, nsrf) = frugs(i, 1)
465            ENDDO            ENDDO
466         ENDDO         ENDDO
467      ENDIF      ENDIF
468    
   
469      ! Lecture de l'age de la neige:      ! Lecture de l'age de la neige:
470    
471      ierr = NF90_INQ_VARID (nid, "AGESNO", nvarid)      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)
472      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
473         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
474         PRINT *, '          Mais je vais essayer de lire AGESNO**'         PRINT *, ' Mais je vais essayer de lire AGESNO**'
475         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
476            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
477               PRINT *, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
478               stop 1               stop 1
479            ENDIF            ENDIF
480            WRITE(str2,'(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
481            ierr = NF90_INQ_VARID (nid, "AGESNO"//str2, nvarid)            ierr = NF90_INQ_VARID(ncid, "AGESNO"//str2, varid)
482            IF (ierr.NE.NF90_NOERR) THEN            IF (ierr /= NF90_NOERR) THEN
483               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
484               agesno = 50.0               agesno = 50.0
485            ENDIF            ENDIF
486            ierr = NF_GET_VAR_REAL(nid, nvarid, agesno(1,nsrf))            call NF95_GET_VAR(ncid, varid, agesno(:, nsrf))
           IF (ierr.NE.NF90_NOERR) THEN  
              PRINT *, "phyetat0: Lecture echouee pour <AGESNO"//str2//">"  
              stop 1  
           ENDIF  
487            xmin = 1.0E+20            xmin = 1.0E+20
488            xmax = -1.0E+20            xmax = -1.0E+20
489            DO i = 1, klon            DO i = 1, klon
490               xmin = MIN(agesno(i,nsrf),xmin)               xmin = MIN(agesno(i, nsrf), xmin)
491               xmax = MAX(agesno(i,nsrf),xmax)               xmax = MAX(agesno(i, nsrf), xmax)
492            ENDDO            ENDDO
493            PRINT *,'Age de la neige AGESNO**:', nsrf, xmin, xmax            PRINT *, 'Age de la neige AGESNO**:', nsrf, xmin, xmax
494         ENDDO         ENDDO
495      ELSE      ELSE
496         PRINT *, 'phyetat0: Le champ <AGESNO> est present'         PRINT *, 'phyetat0: Le champ <AGESNO> est present'
497         PRINT *, '          J ignore donc les autres AGESNO**'         PRINT *, ' J ignore donc les autres AGESNO**'
498         call nf95_get_var(nid, nvarid, agesno(:,1))         call nf95_get_var(ncid, varid, agesno(:, 1))
499         xmin = 1.0E+20         xmin = 1.0E+20
500         xmax = -1.0E+20         xmax = -1.0E+20
501         DO i = 1, klon         DO i = 1, klon
502            xmin = MIN(agesno(i,1),xmin)            xmin = MIN(agesno(i, 1), xmin)
503            xmax = MAX(agesno(i,1),xmax)            xmax = MAX(agesno(i, 1), xmax)
504         ENDDO         ENDDO
505         PRINT *,'Age de la neige <AGESNO>', xmin, xmax         PRINT *, 'Age de la neige <AGESNO>', xmin, xmax
506         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
507            DO i = 1, klon            DO i = 1, klon
508               agesno(i,nsrf) = agesno(i,1)               agesno(i, nsrf) = agesno(i, 1)
509            ENDDO            ENDDO
510         ENDDO         ENDDO
511      ENDIF      ENDIF
512    
513        call NF95_INQ_VARID(ncid, "ZMEA", varid)
514      ierr = NF90_INQ_VARID (nid, "ZMEA", nvarid)      call NF95_GET_VAR(ncid, varid, zmea)
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Le champ <ZMEA> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zmea)  
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZMEA>'  
        stop 1  
     ENDIF  
515      xmin = 1.0E+20      xmin = 1.0E+20
516      xmax = -1.0E+20      xmax = -1.0E+20
517      DO i = 1, klon      DO i = 1, klon
518         xmin = MIN(zmea(i),xmin)         xmin = MIN(zmea(i), xmin)
519         xmax = MAX(zmea(i),xmax)         xmax = MAX(zmea(i), xmax)
520      ENDDO      ENDDO
521      PRINT *,'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
   
522    
523      ierr = NF90_INQ_VARID (nid, "ZSTD", nvarid)      call NF95_INQ_VARID(ncid, "ZSTD", varid)
524      IF (ierr.NE.NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zstd)
        PRINT *, 'phyetat0: Le champ <ZSTD> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zstd)  
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZSTD>'  
        stop 1  
     ENDIF  
525      xmin = 1.0E+20      xmin = 1.0E+20
526      xmax = -1.0E+20      xmax = -1.0E+20
527      DO i = 1, klon      DO i = 1, klon
528         xmin = MIN(zstd(i),xmin)         xmin = MIN(zstd(i), xmin)
529         xmax = MAX(zstd(i),xmax)         xmax = MAX(zstd(i), xmax)
530      ENDDO      ENDDO
531      PRINT *,'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
   
532    
533      ierr = NF90_INQ_VARID (nid, "ZSIG", nvarid)      call NF95_INQ_VARID(ncid, "ZSIG", varid)
534      IF (ierr.NE.NF90_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zsig)
        PRINT *, 'phyetat0: Le champ <ZSIG> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zsig)  
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZSIG>'  
        stop 1  
     ENDIF  
535      xmin = 1.0E+20      xmin = 1.0E+20
536      xmax = -1.0E+20      xmax = -1.0E+20
537      DO i = 1, klon      DO i = 1, klon
538         xmin = MIN(zsig(i),xmin)         xmin = MIN(zsig(i), xmin)
539         xmax = MAX(zsig(i),xmax)         xmax = MAX(zsig(i), xmax)
540      ENDDO      ENDDO
541      PRINT *,'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
542    
543        call NF95_INQ_VARID(ncid, "ZGAM", varid)
544      ierr = NF90_INQ_VARID (nid, "ZGAM", nvarid)      call NF95_GET_VAR(ncid, varid, zgam)
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Le champ <ZGAM> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zgam)  
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZGAM>'  
        stop 1  
     ENDIF  
545      xmin = 1.0E+20      xmin = 1.0E+20
546      xmax = -1.0E+20      xmax = -1.0E+20
547      DO i = 1, klon      DO i = 1, klon
548         xmin = MIN(zgam(i),xmin)         xmin = MIN(zgam(i), xmin)
549         xmax = MAX(zgam(i),xmax)         xmax = MAX(zgam(i), xmax)
550      ENDDO      ENDDO
551      PRINT *,'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
552    
553        call NF95_INQ_VARID(ncid, "ZTHE", varid)
554      ierr = NF90_INQ_VARID (nid, "ZTHE", nvarid)      call NF95_GET_VAR(ncid, varid, zthe)
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Le champ <ZTHE> est absent'  
        stop 1  
     ENDIF  
     ierr = NF_GET_VAR_REAL(nid, nvarid, zthe)  
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZTHE>'  
        stop 1  
     ENDIF  
555      xmin = 1.0E+20      xmin = 1.0E+20
556      xmax = -1.0E+20      xmax = -1.0E+20
557      DO i = 1, klon      DO i = 1, klon
558         xmin = MIN(zthe(i),xmin)         xmin = MIN(zthe(i), xmin)
559         xmax = MAX(zthe(i),xmax)         xmax = MAX(zthe(i), xmax)
560      ENDDO      ENDDO
561      PRINT *,'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
   
562    
563      ierr = NF90_INQ_VARID (nid, "ZPIC", nvarid)      call NF95_INQ_VARID(ncid, "ZPIC", varid)
564      IF (ierr.NE.NF90_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.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZPIC>'  
        stop 1  
     ENDIF  
565      xmin = 1.0E+20      xmin = 1.0E+20
566      xmax = -1.0E+20      xmax = -1.0E+20
567      DO i = 1, klon      DO i = 1, klon
568         xmin = MIN(zpic(i),xmin)         xmin = MIN(zpic(i), xmin)
569         xmax = MAX(zpic(i),xmax)         xmax = MAX(zpic(i), xmax)
570      ENDDO      ENDDO
571      PRINT *,'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
572    
573      ierr = NF90_INQ_VARID (nid, "ZVAL", nvarid)      call NF95_INQ_VARID(ncid, "ZVAL", varid)
574      IF (ierr.NE.NF90_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.NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Lecture echouee pour <ZVAL>'  
        stop 1  
     ENDIF  
575      xmin = 1.0E+20      xmin = 1.0E+20
576      xmax = -1.0E+20      xmax = -1.0E+20
577      DO i = 1, klon      DO i = 1, klon
578         xmin = MIN(zval(i),xmin)         xmin = MIN(zval(i), xmin)
579         xmax = MAX(zval(i),xmax)         xmax = MAX(zval(i), xmax)
580      ENDDO      ENDDO
581      PRINT *,'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
582    
583      ancien_ok = .TRUE.      ancien_ok = .TRUE.
584    
585      ierr = NF90_INQ_VARID (nid, "TANCIEN", nvarid)      ierr = NF90_INQ_VARID(ncid, "TANCIEN", varid)
586      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
587         PRINT *, "phyetat0: Le champ <TANCIEN> est absent"         PRINT *, "phyetat0: Le champ <TANCIEN> est absent"
588         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
589         ancien_ok = .FALSE.         ancien_ok = .FALSE.
590      ELSE      ELSE
591         call nf95_get_var(nid, nvarid, t_ancien)         call nf95_get_var(ncid, varid, t_ancien)
592      ENDIF      ENDIF
593    
594      ierr = NF90_INQ_VARID (nid, "QANCIEN", nvarid)      ierr = NF90_INQ_VARID(ncid, "QANCIEN", varid)
595      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
596         PRINT *, "phyetat0: Le champ <QANCIEN> est absent"         PRINT *, "phyetat0: Le champ <QANCIEN> est absent"
597         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
598         ancien_ok = .FALSE.         ancien_ok = .FALSE.
599      ELSE      ELSE
600         call nf95_get_var(nid, nvarid, q_ancien)         call nf95_get_var(ncid, varid, q_ancien)
601      ENDIF      ENDIF
602    
603      ierr = NF90_INQ_VARID (nid, "CLWCON", nvarid)      ierr = NF90_INQ_VARID(ncid, "CLWCON", varid)
604      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
605         PRINT *, "phyetat0: Le champ CLWCON est absent"         PRINT *, "phyetat0: Le champ CLWCON est absent"
606         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
607         clwcon = 0.         clwcon = 0.
608      ELSE      ELSE
609         call nf95_get_var(nid, nvarid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
610           clwcon(:, 2:) = 0.
611      ENDIF      ENDIF
612      xmin = 1.0E+20      xmin = 1.0E+20
613      xmax = -1.0E+20      xmax = -1.0E+20
614      xmin = MINval(clwcon)      xmin = MINval(clwcon)
615      xmax = MAXval(clwcon)      xmax = MAXval(clwcon)
616      PRINT *,'Eau liquide convective (ecart-type) clwcon:', xmin, xmax      PRINT *, 'Eau liquide convective (ecart-type) clwcon:', xmin, xmax
617    
618      ierr = NF90_INQ_VARID (nid, "RNEBCON", nvarid)      ierr = NF90_INQ_VARID(ncid, "RNEBCON", varid)
619      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
620         PRINT *, "phyetat0: Le champ RNEBCON est absent"         PRINT *, "phyetat0: Le champ RNEBCON est absent"
621         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
622         rnebcon = 0.         rnebcon = 0.
623      ELSE      ELSE
624         call nf95_get_var(nid, nvarid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
625           rnebcon(:, 2:) = 0.
626      ENDIF      ENDIF
627      xmin = 1.0E+20      xmin = 1.0E+20
628      xmax = -1.0E+20      xmax = -1.0E+20
629      xmin = MINval(rnebcon)      xmin = MINval(rnebcon)
630      xmax = MAXval(rnebcon)      xmax = MAXval(rnebcon)
631      PRINT *,'Nebulosite convective (ecart-type) rnebcon:', xmin, xmax      PRINT *, 'Nebulosite convective (ecart-type) rnebcon:', xmin, xmax
   
   
     ierr = NF90_INQ_VARID (nid, "QANCIEN", nvarid)  
     IF (ierr.NE.NF90_NOERR) THEN  
        PRINT *, "phyetat0: Le champ <QANCIEN> est absent"  
        PRINT *, "Depart legerement fausse. Mais je continue"  
        ancien_ok = .FALSE.  
     ELSE  
        call nf95_get_var(nid, nvarid, q_ancien)  
     ENDIF  
632    
633      ! Lecture ratqs      ! Lecture ratqs
634    
635      ierr = NF90_INQ_VARID (nid, "RATQS", nvarid)      ierr = NF90_INQ_VARID(ncid, "RATQS", varid)
636      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
637         PRINT *, "phyetat0: Le champ <RATQS> est absent"         PRINT *, "phyetat0: Le champ <RATQS> est absent"
638         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
639         ratqs = 0.         ratqs = 0.
640      ELSE      ELSE
641         call nf95_get_var(nid, nvarid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
642           ratqs(:, 2:) = 0.
643      ENDIF      ENDIF
644      xmin = 1.0E+20      xmin = 1.0E+20
645      xmax = -1.0E+20      xmax = -1.0E+20
646      xmin = MINval(ratqs)      xmin = MINval(ratqs)
647      xmax = MAXval(ratqs)      xmax = MAXval(ratqs)
648      PRINT *,'(ecart-type) ratqs:', xmin, xmax      PRINT *, '(ecart-type) ratqs:', xmin, xmax
649    
650      ! Lecture run_off_lic_0      ! Lecture run_off_lic_0
651    
652      ierr = NF90_INQ_VARID (nid, "RUNOFFLIC0", nvarid)      ierr = NF90_INQ_VARID(ncid, "RUNOFFLIC0", varid)
653      IF (ierr.NE.NF90_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
654         PRINT *, "phyetat0: Le champ <RUNOFFLIC0> est absent"         PRINT *, "phyetat0: Le champ <RUNOFFLIC0> est absent"
655         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
656         run_off_lic_0 = 0.         run_off_lic_0 = 0.
657      ELSE      ELSE
658         call nf95_get_var(nid, nvarid, run_off_lic_0)         call nf95_get_var(ncid, varid, run_off_lic_0)
659      ENDIF      ENDIF
660      xmin = 1.0E+20      xmin = 1.0E+20
661      xmax = -1.0E+20      xmax = -1.0E+20
662      xmin = MINval(run_off_lic_0)      xmin = MINval(run_off_lic_0)
663      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
664      PRINT *,'(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
665    
666        call nf95_inq_varid(ncid, "sig1", varid)
667        call nf95_get_var(ncid, varid, sig1)
668    
669      ! Fermer le fichier:      call nf95_inq_varid(ncid, "w01", varid)
670        call nf95_get_var(ncid, varid, w01)
671    
672      ierr = NF_CLOSE(nid)      call NF95_CLOSE(ncid)
673    
674    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0
675    

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

  ViewVC Help
Powered by ViewVC 1.1.21