/[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 15 by guez, Fri Aug 1 15:24:12 2008 UTC trunk/phylmd/phyetat0.f revision 101 by guez, Mon Jul 7 17:45:21 2014 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)    REAL, save:: rlat(klon), rlon(klon) ! latitude and longitude, in degrees
   ! latitude et longitude pour chaque point, in degrees  
8    
9    private klon    private klon
10    
11  contains  contains
12    
13    SUBROUTINE phyetat0(fichnom, pctsrf, tsol,tsoil, ocean, tslab,seaice, &    SUBROUTINE phyetat0(pctsrf, tsol, tsoil, tslab, seaice, qsurf, qsol, &
14         qsurf,qsol,snow, &         snow, albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, &
15         albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, &         radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
16         fder,radsol,frugs,agesno, &         t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, &
17         zmea,zstd,zsig,zgam,zthe,zpic,zval, &         sig1, w01)
18         t_ancien,q_ancien,ancien_ok, rnebcon, ratqs,clwcon, &  
19         run_off_lic_0)      ! From phylmd/phyetat0.F, version 1.4 2005/06/03 10:03:07
20        ! Author: Z.X. Li (LMD/CNRS)
21      ! From phylmd/phyetat0.F,v 1.4 2005/06/03 10:03:07      ! Date: 1993/08/18
22      ! 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  
23    
24      USE indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf      use dimphy, only: zmasq, klev
25      USE dimsoil, ONLY : nsoilmx      USE dimsoil, ONLY : nsoilmx
26        USE indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
27        use netcdf, only: nf90_global, nf90_inq_varid, NF90_NOERR, &
28             NF90_NOWRITE
29        use netcdf95, only: nf95_close, nf95_get_att, nf95_get_var, &
30             nf95_inq_varid, nf95_inquire_variable, NF95_OPEN
31      USE temps, ONLY : itau_phy      USE temps, ONLY : itau_phy
     use netcdf, only: nf90_get_att, nf90_global  
     use netcdf95, only: handle_err  
     use dimphy, only: zmasq, klev  
   
     include "netcdf.inc"  
32    
33      CHARACTER(len=*) fichnom      REAL pctsrf(klon, nbsrf)
34      REAL tsol(klon,nbsrf)      REAL tsol(klon, nbsrf)
35      REAL tsoil(klon,nsoilmx,nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
     !IM "slab" ocean  
36      REAL tslab(klon), seaice(klon)      REAL tslab(klon), seaice(klon)
37      REAL qsurf(klon,nbsrf)      REAL qsurf(klon, nbsrf)
38      REAL qsol(klon)      REAL, intent(out):: qsol(:) ! (klon)
39      REAL snow(klon,nbsrf)      REAL snow(klon, nbsrf)
40      REAL albe(klon,nbsrf)      REAL albe(klon, nbsrf)
41      REAL alblw(klon,nbsrf)      REAL alblw(klon, nbsrf)
42      REAL evap(klon,nbsrf)      REAL evap(klon, nbsrf)
43      REAL radsol(klon)      REAL, intent(out):: rain_fall(klon)
     REAL rain_fall(klon)  
44      REAL snow_fall(klon)      REAL snow_fall(klon)
     REAL sollw(klon)  
45      real solsw(klon)      real solsw(klon)
46        REAL, intent(out):: sollw(klon)
47      real fder(klon)      real fder(klon)
48      REAL frugs(klon,nbsrf)      REAL radsol(klon)
49      REAL agesno(klon,nbsrf)      REAL frugs(klon, nbsrf)
50        REAL agesno(klon, nbsrf)
51      REAL zmea(klon)      REAL zmea(klon)
52      REAL, intent(out):: zstd(klon)      REAL, intent(out):: zstd(klon)
53      REAL, intent(out):: zsig(klon)      REAL, intent(out):: zsig(klon)
# Line 58  contains Line 55  contains
55      REAL zthe(klon)      REAL zthe(klon)
56      REAL zpic(klon)      REAL zpic(klon)
57      REAL zval(klon)      REAL zval(klon)
58      REAL pctsrf(klon, nbsrf)      REAL t_ancien(klon, klev), q_ancien(klon, klev)
59      REAL fractint(klon)      LOGICAL, intent(out):: ancien_ok
60        real rnebcon(klon, klev), ratqs(klon, klev), clwcon(klon, klev)
61      REAL run_off_lic_0(klon)      REAL run_off_lic_0(klon)
62        real, intent(out):: sig1(klon, klev) ! section adiabatic updraft
63    
64      REAL t_ancien(klon,klev), q_ancien(klon,klev)      real, intent(out):: w01(klon, klev)
65      real rnebcon(klon,klev),clwcon(klon,klev),ratqs(klon,klev)      ! vertical velocity within adiabatic updraft
     LOGICAL ancien_ok  
   
     CHARACTER(len=*), intent(in):: ocean  
66    
67        ! Local:
68        REAL fractint(klon)
69      REAL xmin, xmax      REAL xmin, xmax
70        INTEGER ncid, varid, ndims
     INTEGER nid, nvarid  
71      INTEGER ierr, i, nsrf, isoil      INTEGER ierr, i, nsrf, isoil
72      CHARACTER*7 str7      CHARACTER(len=7) str7
73      CHARACTER*2 str2      CHARACTER(len=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.NF_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 = NF_INQ_VARID (nid, "latitude", nvarid)      call NF95_INQ_VARID(ncid, "latitude", varid)
87      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  
88    
89      ! Lecture des longitudes (coordonnees):      ! Lecture des longitudes (coordonnees):
90    
91      ierr = NF_INQ_VARID (nid, "longitude", nvarid)      call NF95_INQ_VARID(ncid, "longitude", varid)
92      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  
   
93    
94      ! Lecture du masque terre mer      ! Lecture du masque terre mer
95    
96      ierr = NF_INQ_VARID (nid, "masque", nvarid)      call NF95_INQ_VARID(ncid, "masque", varid)
97      IF (ierr .EQ.  NF_NOERR) THEN      call nf95_get_var(ncid, varid, zmasq)
98         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  
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 141  contains Line 104  contains
104    
105      ! fraction de terre      ! fraction de terre
106    
107      ierr = NF_INQ_VARID (nid, "FTER", nvarid)      ierr = NF90_INQ_VARID(ncid, "FTER", varid)
108      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
109         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  
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 = NF_INQ_VARID (nid, "FLIC", nvarid)      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)
117      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
118         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  
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 = NF_INQ_VARID (nid, "FOCE", nvarid)      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)
126      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
127         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  
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 = NF_INQ_VARID (nid, "FSIC", nvarid)      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)
135      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
136         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  
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 = NF_INQ_VARID (nid, "TS", nvarid)     ! Lecture des temperatures du sol profond:
     IF (ierr.NE.NF_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 = 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  
   
     ! Lecture des temperatures du sol profond:  
172    
173      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
174         DO isoil=1, nsoilmx         DO isoil=1, nsoilmx
175            IF (isoil.GT.99 .AND. nsrf.GT.99) THEN            IF (isoil > 99 .AND. nsrf > 99) THEN
176               PRINT*, "Trop de couches ou sous-mailles"               PRINT *, "Trop de couches ou sous-mailles"
177               stop 1               stop 1
178            ENDIF            ENDIF
179            WRITE(str7,'(i2.2,"srf",i2.2)') isoil, nsrf            WRITE(str7, '(i2.2, "srf", i2.2)') isoil, nsrf
180            ierr = NF_INQ_VARID (nid, 'Tsoil'//str7, nvarid)            ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)
181            IF (ierr.NE.NF_NOERR) THEN            IF (ierr /= NF90_NOERR) THEN
182               PRINT*, "phyetat0: Le champ <Tsoil"//str7//"> est absent"               PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
183               PRINT*, "          Il prend donc la valeur de surface"               PRINT *, " Il prend donc la valeur de surface"
184               DO i=1, klon               DO i=1, klon
185                  tsoil(i,isoil,nsrf)=tsol(i,nsrf)                  tsoil(i, isoil, nsrf)=tsol(i, nsrf)
186               ENDDO               ENDDO
187            ELSE            ELSE
188               ierr = NF_GET_VAR_REAL(nid, nvarid, tsoil(1,isoil,nsrf))               call NF95_GET_VAR(ncid, varid, tsoil(:, isoil, nsrf))
              IF (ierr.NE.NF_NOERR) THEN  
                 PRINT*, "Lecture echouee pour <Tsoil"//str7//">"  
                 stop 1  
              ENDIF  
189            ENDIF            ENDIF
190         ENDDO         ENDDO
191      ENDDO      ENDDO
192    
193      !IM "slab" ocean      !IM "slab" ocean
194        ! Lecture de tslab (pour slab ocean seulement):
195      ! Lecture de tslab (pour slab ocean seulement):            tslab = 0.
196        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  
197    
198      ! Lecture de l'humidite de l'air juste au dessus du sol:      ! Lecture de l'humidite de l'air juste au dessus du sol:
199    
200      ierr = NF_INQ_VARID (nid, "QS", nvarid)      ierr = NF90_INQ_VARID(ncid, "QS", varid)
201      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
202         PRINT*, 'phyetat0: Le champ <QS> est absent'         PRINT *, 'phyetat0: Le champ <QS> est absent'
203         PRINT*, '          Mais je vais essayer de lire QS**'         PRINT *, ' Mais je vais essayer de lire QS**'
204         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
205            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
206               PRINT*, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
              stop 1  
           ENDIF  
           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//">"  
207               stop 1               stop 1
208            ENDIF            ENDIF
209              WRITE(str2, '(i2.2)') nsrf
210              call NF95_INQ_VARID(ncid, "QS"//str2, varid)
211              call NF95_GET_VAR(ncid, varid, qsurf(:, nsrf))
212            xmin = 1.0E+20            xmin = 1.0E+20
213            xmax = -1.0E+20            xmax = -1.0E+20
214            DO i = 1, klon            DO i = 1, klon
215               xmin = MIN(qsurf(i,nsrf),xmin)               xmin = MIN(qsurf(i, nsrf), xmin)
216               xmax = MAX(qsurf(i,nsrf),xmax)               xmax = MAX(qsurf(i, nsrf), xmax)
217            ENDDO            ENDDO
218            PRINT*,'Humidite pres du sol QS**:', nsrf, xmin, xmax            PRINT *, 'Humidite pres du sol QS**:', nsrf, xmin, xmax
219         ENDDO         ENDDO
220      ELSE      ELSE
221         PRINT*, 'phyetat0: Le champ <QS> est present'         PRINT *, 'phyetat0: Le champ <QS> est present'
222         PRINT*, '          J ignore donc les autres humidites QS**'         PRINT *, ' J ignore donc les autres humidites QS**'
223         ierr = NF_GET_VAR_REAL(nid, nvarid, qsurf(1,1))         call nf95_get_var(ncid, varid, qsurf(:, 1))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <QS>"  
           stop 1  
        ENDIF  
224         xmin = 1.0E+20         xmin = 1.0E+20
225         xmax = -1.0E+20         xmax = -1.0E+20
226         DO i = 1, klon         DO i = 1, klon
227            xmin = MIN(qsurf(i,1),xmin)            xmin = MIN(qsurf(i, 1), xmin)
228            xmax = MAX(qsurf(i,1),xmax)            xmax = MAX(qsurf(i, 1), xmax)
229         ENDDO         ENDDO
230         PRINT*,'Humidite pres du sol <QS>', xmin, xmax         PRINT *, 'Humidite pres du sol <QS>', xmin, xmax
231         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
232            DO i = 1, klon            DO i = 1, klon
233               qsurf(i,nsrf) = qsurf(i,1)               qsurf(i, nsrf) = qsurf(i, 1)
234            ENDDO            ENDDO
235         ENDDO         ENDDO
236      ENDIF      ENDIF
237    
238      ! Eau dans le sol (pour le modele de sol "bucket")      ! Eau dans le sol (pour le modele de sol "bucket")
239    
240      ierr = NF_INQ_VARID (nid, "QSOL", nvarid)      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
241      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
242         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  
243      else      else
244         PRINT*, 'phyetat0: Le champ <QSOL> est absent'         PRINT *, 'phyetat0: Le champ <QSOL> est absent'
245         PRINT*, '          Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
246         qsol(:)=0.         qsol = 0.
        !$$$         stop 1  
247      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  
248    
249      ! Lecture de neige au sol:      ! Lecture de neige au sol:
250    
251      ierr = NF_INQ_VARID (nid, "SNOW", nvarid)      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)
252      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
253         PRINT*, 'phyetat0: Le champ <SNOW> est absent'         PRINT *, 'phyetat0: Le champ <SNOW> est absent'
254         PRINT*, '          Mais je vais essayer de lire SNOW**'         PRINT *, ' Mais je vais essayer de lire SNOW**'
255         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
256            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
257               PRINT*, "Trop de sous-mailles"               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//">"  
258               stop 1               stop 1
259            ENDIF            ENDIF
260              WRITE(str2, '(i2.2)') nsrf
261              call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)
262              call NF95_GET_VAR(ncid, varid, snow(:, nsrf))
263            xmin = 1.0E+20            xmin = 1.0E+20
264            xmax = -1.0E+20            xmax = -1.0E+20
265            DO i = 1, klon            DO i = 1, klon
266               xmin = MIN(snow(i,nsrf),xmin)               xmin = MIN(snow(i, nsrf), xmin)
267               xmax = MAX(snow(i,nsrf),xmax)               xmax = MAX(snow(i, nsrf), xmax)
268            ENDDO            ENDDO
269            PRINT*,'Neige du sol SNOW**:', nsrf, xmin, xmax            PRINT *, 'Neige du sol SNOW**:', nsrf, xmin, xmax
270         ENDDO         ENDDO
271      ELSE      ELSE
272         PRINT*, 'phyetat0: Le champ <SNOW> est present'         PRINT *, 'phyetat0: Le champ <SNOW> est present'
273         PRINT*, '          J ignore donc les autres neiges SNOW**'         PRINT *, ' J ignore donc les autres neiges SNOW**'
274         ierr = NF_GET_VAR_REAL(nid, nvarid, snow(1,1))         call nf95_get_var(ncid, varid, snow(:, 1))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <SNOW>"  
           stop 1  
        ENDIF  
275         xmin = 1.0E+20         xmin = 1.0E+20
276         xmax = -1.0E+20         xmax = -1.0E+20
277         DO i = 1, klon         DO i = 1, klon
278            xmin = MIN(snow(i,1),xmin)            xmin = MIN(snow(i, 1), xmin)
279            xmax = MAX(snow(i,1),xmax)            xmax = MAX(snow(i, 1), xmax)
280         ENDDO         ENDDO
281         PRINT*,'Neige du sol <SNOW>', xmin, xmax         PRINT *, 'Neige du sol <SNOW>', xmin, xmax
282         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
283            DO i = 1, klon            DO i = 1, klon
284               snow(i,nsrf) = snow(i,1)               snow(i, nsrf) = snow(i, 1)
285            ENDDO            ENDDO
286         ENDDO         ENDDO
287      ENDIF      ENDIF
288    
289      ! Lecture de albedo au sol:      ! Lecture de albedo au sol:
290    
291      ierr = NF_INQ_VARID (nid, "ALBE", nvarid)      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)
292      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
293         PRINT*, 'phyetat0: Le champ <ALBE> est absent'         PRINT *, 'phyetat0: Le champ <ALBE> est absent'
294         PRINT*, '          Mais je vais essayer de lire ALBE**'         PRINT *, ' Mais je vais essayer de lire ALBE**'
295         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
296            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
297               PRINT*, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
              stop 1  
           ENDIF  
           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//">"  
298               stop 1               stop 1
299            ENDIF            ENDIF
300              WRITE(str2, '(i2.2)') nsrf
301              call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)
302              call NF95_GET_VAR(ncid, varid, albe(:, nsrf))
303            xmin = 1.0E+20            xmin = 1.0E+20
304            xmax = -1.0E+20            xmax = -1.0E+20
305            DO i = 1, klon            DO i = 1, klon
306               xmin = MIN(albe(i,nsrf),xmin)               xmin = MIN(albe(i, nsrf), xmin)
307               xmax = MAX(albe(i,nsrf),xmax)               xmax = MAX(albe(i, nsrf), xmax)
308            ENDDO            ENDDO
309            PRINT*,'Albedo du sol ALBE**:', nsrf, xmin, xmax            PRINT *, 'Albedo du sol ALBE**:', nsrf, xmin, xmax
310         ENDDO         ENDDO
311      ELSE      ELSE
312         PRINT*, 'phyetat0: Le champ <ALBE> est present'         PRINT *, 'phyetat0: Le champ <ALBE> est present'
313         PRINT*, '          J ignore donc les autres ALBE**'         PRINT *, ' J ignore donc les autres ALBE**'
314         ierr = NF_GET_VAR_REAL(nid, nvarid, albe(1,1))         call nf95_get_var(ncid, varid, albe(:, 1))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <ALBE>"  
           stop 1  
        ENDIF  
315         xmin = 1.0E+20         xmin = 1.0E+20
316         xmax = -1.0E+20         xmax = -1.0E+20
317         DO i = 1, klon         DO i = 1, klon
318            xmin = MIN(albe(i,1),xmin)            xmin = MIN(albe(i, 1), xmin)
319            xmax = MAX(albe(i,1),xmax)            xmax = MAX(albe(i, 1), xmax)
320         ENDDO         ENDDO
321         PRINT*,'Neige du sol <ALBE>', xmin, xmax         PRINT *, 'Neige du sol <ALBE>', xmin, xmax
322         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
323            DO i = 1, klon            DO i = 1, klon
324               albe(i,nsrf) = albe(i,1)               albe(i, nsrf) = albe(i, 1)
325            ENDDO            ENDDO
326         ENDDO         ENDDO
327      ENDIF      ENDIF
328    
   
329      ! Lecture de albedo au sol LW:      ! Lecture de albedo au sol LW:
330    
331      ierr = NF_INQ_VARID (nid, "ALBLW", nvarid)      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)
332      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
333         PRINT*, 'phyetat0: Le champ <ALBLW> est absent'         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'
334         !        PRINT*, '          Mais je vais essayer de lire ALBLW**'         ! PRINT *, ' Mais je vais essayer de lire ALBLW**'
335         PRINT*, '          Mais je vais prendre ALBE**'         PRINT *, ' Mais je vais prendre ALBE**'
336         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
337            DO i = 1, klon            DO i = 1, klon
338               alblw(i,nsrf) = albe(i,nsrf)               alblw(i, nsrf) = albe(i, nsrf)
339            ENDDO            ENDDO
340         ENDDO         ENDDO
341      ELSE      ELSE
342         PRINT*, 'phyetat0: Le champ <ALBLW> est present'         PRINT *, 'phyetat0: Le champ <ALBLW> est present'
343         PRINT*, '          J ignore donc les autres ALBLW**'         PRINT *, ' J ignore donc les autres ALBLW**'
344         ierr = NF_GET_VAR_REAL(nid, nvarid, alblw(1,1))         call nf95_get_var(ncid, varid, alblw(:, 1))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <ALBLW>"  
           stop 1  
        ENDIF  
345         xmin = 1.0E+20         xmin = 1.0E+20
346         xmax = -1.0E+20         xmax = -1.0E+20
347         DO i = 1, klon         DO i = 1, klon
348            xmin = MIN(alblw(i,1),xmin)            xmin = MIN(alblw(i, 1), xmin)
349            xmax = MAX(alblw(i,1),xmax)            xmax = MAX(alblw(i, 1), xmax)
350         ENDDO         ENDDO
351         PRINT*,'Neige du sol <ALBLW>', xmin, xmax         PRINT *, 'Neige du sol <ALBLW>', xmin, xmax
352         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
353            DO i = 1, klon            DO i = 1, klon
354               alblw(i,nsrf) = alblw(i,1)               alblw(i, nsrf) = alblw(i, 1)
355            ENDDO            ENDDO
356         ENDDO         ENDDO
357      ENDIF      ENDIF
358    
359      ! Lecture de evaporation:        ! Lecture de evaporation:
360    
361      ierr = NF_INQ_VARID (nid, "EVAP", nvarid)      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)
362      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
363         PRINT*, 'phyetat0: Le champ <EVAP> est absent'         PRINT *, 'phyetat0: Le champ <EVAP> est absent'
364         PRINT*, '          Mais je vais essayer de lire EVAP**'         PRINT *, ' Mais je vais essayer de lire EVAP**'
365         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
366            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
367               PRINT*, "Trop de sous-mailles"               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//">"  
368               stop 1               stop 1
369            ENDIF            ENDIF
370              WRITE(str2, '(i2.2)') nsrf
371              call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)
372              call NF95_GET_VAR(ncid, varid, evap(:, nsrf))
373            xmin = 1.0E+20            xmin = 1.0E+20
374            xmax = -1.0E+20            xmax = -1.0E+20
375            DO i = 1, klon            DO i = 1, klon
376               xmin = MIN(evap(i,nsrf),xmin)               xmin = MIN(evap(i, nsrf), xmin)
377               xmax = MAX(evap(i,nsrf),xmax)               xmax = MAX(evap(i, nsrf), xmax)
378            ENDDO            ENDDO
379            PRINT*,'evap du sol EVAP**:', nsrf, xmin, xmax            PRINT *, 'evap du sol EVAP**:', nsrf, xmin, xmax
380         ENDDO         ENDDO
381      ELSE      ELSE
382         PRINT*, 'phyetat0: Le champ <EVAP> est present'         PRINT *, 'phyetat0: Le champ <EVAP> est present'
383         PRINT*, '          J ignore donc les autres EVAP**'         PRINT *, ' J ignore donc les autres EVAP**'
384         ierr = NF_GET_VAR_REAL(nid, nvarid, evap(1,1))         call nf95_get_var(ncid, varid, evap(:, 1))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <EVAP>"  
           stop 1  
        ENDIF  
385         xmin = 1.0E+20         xmin = 1.0E+20
386         xmax = -1.0E+20         xmax = -1.0E+20
387         DO i = 1, klon         DO i = 1, klon
388            xmin = MIN(evap(i,1),xmin)            xmin = MIN(evap(i, 1), xmin)
389            xmax = MAX(evap(i,1),xmax)            xmax = MAX(evap(i, 1), xmax)
390         ENDDO         ENDDO
391         PRINT*,'Evap du sol <EVAP>', xmin, xmax         PRINT *, 'Evap du sol <EVAP>', xmin, xmax
392         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
393            DO i = 1, klon            DO i = 1, klon
394               evap(i,nsrf) = evap(i,1)               evap(i, nsrf) = evap(i, 1)
395            ENDDO            ENDDO
396         ENDDO         ENDDO
397      ENDIF      ENDIF
398    
399      ! Lecture precipitation liquide:      ! Lecture precipitation liquide:
400    
401      ierr = NF_INQ_VARID (nid, "rain_f", nvarid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
402      IF (ierr.NE.NF_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.NF_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  
403    
404      ! Lecture precipitation solide:      ! Lecture precipitation solide:
405    
406      ierr = NF_INQ_VARID (nid, "snow_f", nvarid)      call NF95_INQ_VARID(ncid, "snow_f", varid)
407      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  
408      xmin = 1.0E+20      xmin = 1.0E+20
409      xmax = -1.0E+20      xmax = -1.0E+20
410      DO i = 1, klon      DO i = 1, klon
411         xmin = MIN(snow_fall(i),xmin)         xmin = MIN(snow_fall(i), xmin)
412         xmax = MAX(snow_fall(i),xmax)         xmax = MAX(snow_fall(i), xmax)
413      ENDDO      ENDDO
414      PRINT*,'Precipitation solide snow_f:', xmin, xmax      PRINT *, 'Precipitation solide snow_f:', xmin, xmax
415    
416      ! Lecture rayonnement solaire au sol:      ! Lecture rayonnement solaire au sol:
417    
418      ierr = NF_INQ_VARID (nid, "solsw", nvarid)      ierr = NF90_INQ_VARID(ncid, "solsw", varid)
419      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
420         PRINT*, 'phyetat0: Le champ <solsw> est absent'         PRINT *, 'phyetat0: Le champ <solsw> est absent'
421         PRINT*, 'mis a zero'         PRINT *, 'mis a zero'
422         solsw = 0.         solsw = 0.
423      ELSE      ELSE
424         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  
425      ENDIF      ENDIF
426      xmin = 1.0E+20      xmin = 1.0E+20
427      xmax = -1.0E+20      xmax = -1.0E+20
428      DO i = 1, klon      DO i = 1, klon
429         xmin = MIN(solsw(i),xmin)         xmin = MIN(solsw(i), xmin)
430         xmax = MAX(solsw(i),xmax)         xmax = MAX(solsw(i), xmax)
431      ENDDO      ENDDO
432      PRINT*,'Rayonnement solaire au sol solsw:', xmin, xmax      PRINT *, 'Rayonnement solaire au sol solsw:', xmin, xmax
433    
434      ! Lecture rayonnement IF au sol:      ! Lecture rayonnement IF au sol:
435    
436      ierr = NF_INQ_VARID (nid, "sollw", nvarid)      ierr = NF90_INQ_VARID(ncid, "sollw", varid)
437      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
438         PRINT*, 'phyetat0: Le champ <sollw> est absent'         PRINT *, 'phyetat0: Le champ <sollw> est absent'
439         PRINT*, 'mis a zero'         PRINT *, 'mis a zero'
440         sollw = 0.         sollw = 0.
441      ELSE      ELSE
442         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  
443      ENDIF      ENDIF
444      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  
   
445    
446      ! Lecture derive des flux:      ! Lecture derive des flux:
447    
448      ierr = NF_INQ_VARID (nid, "fder", nvarid)      ierr = NF90_INQ_VARID(ncid, "fder", varid)
449      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
450         PRINT*, 'phyetat0: Le champ <fder> est absent'         PRINT *, 'phyetat0: Le champ <fder> est absent'
451         PRINT*, 'mis a zero'         PRINT *, 'mis a zero'
452         fder = 0.         fder = 0.
453      ELSE      ELSE
454         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  
455      ENDIF      ENDIF
456      xmin = 1.0E+20      xmin = 1.0E+20
457      xmax = -1.0E+20      xmax = -1.0E+20
458      DO i = 1, klon      DO i = 1, klon
459         xmin = MIN(fder(i),xmin)         xmin = MIN(fder(i), xmin)
460         xmax = MAX(fder(i),xmax)         xmax = MAX(fder(i), xmax)
461      ENDDO      ENDDO
462      PRINT*,'Derive des flux fder:', xmin, xmax      PRINT *, 'Derive des flux fder:', xmin, xmax
   
463    
464      ! Lecture du rayonnement net au sol:      ! Lecture du rayonnement net au sol:
465    
466      ierr = NF_INQ_VARID (nid, "RADS", nvarid)      call NF95_INQ_VARID(ncid, "RADS", varid)
467      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  
468      xmin = 1.0E+20      xmin = 1.0E+20
469      xmax = -1.0E+20      xmax = -1.0E+20
470      DO i = 1, klon      DO i = 1, klon
471         xmin = MIN(radsol(i),xmin)         xmin = MIN(radsol(i), xmin)
472         xmax = MAX(radsol(i),xmax)         xmax = MAX(radsol(i), xmax)
473      ENDDO      ENDDO
474      PRINT*,'Rayonnement net au sol radsol:', xmin, xmax      PRINT *, 'Rayonnement net au sol radsol:', xmin, xmax
475    
476      ! Lecture de la longueur de rugosite      ! Lecture de la longueur de rugosite
477    
478        ierr = NF90_INQ_VARID(ncid, "RUG", varid)
479      ierr = NF_INQ_VARID (nid, "RUG", nvarid)      IF (ierr /= NF90_NOERR) THEN
480      IF (ierr.NE.NF_NOERR) THEN         PRINT *, 'phyetat0: Le champ <RUG> est absent'
481         PRINT*, 'phyetat0: Le champ <RUG> est absent'         PRINT *, ' Mais je vais essayer de lire RUG**'
        PRINT*, '          Mais je vais essayer de lire RUG**'  
482         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
483            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
484               PRINT*, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
              stop 1  
           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//">"  
485               stop 1               stop 1
486            ENDIF            ENDIF
487              WRITE(str2, '(i2.2)') nsrf
488              call NF95_INQ_VARID(ncid, "RUG"//str2, varid)
489              call NF95_GET_VAR(ncid, varid, frugs(:, nsrf))
490            xmin = 1.0E+20            xmin = 1.0E+20
491            xmax = -1.0E+20            xmax = -1.0E+20
492            DO i = 1, klon            DO i = 1, klon
493               xmin = MIN(frugs(i,nsrf),xmin)               xmin = MIN(frugs(i, nsrf), xmin)
494               xmax = MAX(frugs(i,nsrf),xmax)               xmax = MAX(frugs(i, nsrf), xmax)
495            ENDDO            ENDDO
496            PRINT*,'rugosite du sol RUG**:', nsrf, xmin, xmax            PRINT *, 'rugosite du sol RUG**:', nsrf, xmin, xmax
497         ENDDO         ENDDO
498      ELSE      ELSE
499         PRINT*, 'phyetat0: Le champ <RUG> est present'         PRINT *, 'phyetat0: Le champ <RUG> est present'
500         PRINT*, '          J ignore donc les autres RUG**'         PRINT *, ' J ignore donc les autres RUG**'
501         ierr = NF_GET_VAR_REAL(nid, nvarid, frugs(1,1))         call nf95_get_var(ncid, varid, frugs(:, 1))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <RUG>"  
           stop 1  
        ENDIF  
502         xmin = 1.0E+20         xmin = 1.0E+20
503         xmax = -1.0E+20         xmax = -1.0E+20
504         DO i = 1, klon         DO i = 1, klon
505            xmin = MIN(frugs(i,1),xmin)            xmin = MIN(frugs(i, 1), xmin)
506            xmax = MAX(frugs(i,1),xmax)            xmax = MAX(frugs(i, 1), xmax)
507         ENDDO         ENDDO
508         PRINT*,'rugosite <RUG>', xmin, xmax         PRINT *, 'rugosite <RUG>', xmin, xmax
509         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
510            DO i = 1, klon            DO i = 1, klon
511               frugs(i,nsrf) = frugs(i,1)               frugs(i, nsrf) = frugs(i, 1)
512            ENDDO            ENDDO
513         ENDDO         ENDDO
514      ENDIF      ENDIF
515    
   
516      ! Lecture de l'age de la neige:      ! Lecture de l'age de la neige:
517    
518      ierr = NF_INQ_VARID (nid, "AGESNO", nvarid)      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)
519      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
520         PRINT*, 'phyetat0: Le champ <AGESNO> est absent'         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
521         PRINT*, '          Mais je vais essayer de lire AGESNO**'         PRINT *, ' Mais je vais essayer de lire AGESNO**'
522         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
523            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
524               PRINT*, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
525               stop 1               stop 1
526            ENDIF            ENDIF
527            WRITE(str2,'(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
528            ierr = NF_INQ_VARID (nid, "AGESNO"//str2, nvarid)            ierr = NF90_INQ_VARID(ncid, "AGESNO"//str2, varid)
529            IF (ierr.NE.NF_NOERR) THEN            IF (ierr /= NF90_NOERR) THEN
530               PRINT*, "phyetat0: Le champ <AGESNO"//str2//"> est absent"               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
531               agesno = 50.0               agesno = 50.0
532            ENDIF            ENDIF
533            ierr = NF_GET_VAR_REAL(nid, nvarid, agesno(1,nsrf))            call NF95_GET_VAR(ncid, varid, agesno(:, nsrf))
           IF (ierr.NE.NF_NOERR) THEN  
              PRINT*, "phyetat0: Lecture echouee pour <AGESNO"//str2//">"  
              stop 1  
           ENDIF  
534            xmin = 1.0E+20            xmin = 1.0E+20
535            xmax = -1.0E+20            xmax = -1.0E+20
536            DO i = 1, klon            DO i = 1, klon
537               xmin = MIN(agesno(i,nsrf),xmin)               xmin = MIN(agesno(i, nsrf), xmin)
538               xmax = MAX(agesno(i,nsrf),xmax)               xmax = MAX(agesno(i, nsrf), xmax)
539            ENDDO            ENDDO
540            PRINT*,'Age de la neige AGESNO**:', nsrf, xmin, xmax            PRINT *, 'Age de la neige AGESNO**:', nsrf, xmin, xmax
541         ENDDO         ENDDO
542      ELSE      ELSE
543         PRINT*, 'phyetat0: Le champ <AGESNO> est present'         PRINT *, 'phyetat0: Le champ <AGESNO> est present'
544         PRINT*, '          J ignore donc les autres AGESNO**'         PRINT *, ' J ignore donc les autres AGESNO**'
545         ierr = NF_GET_VAR_REAL(nid, nvarid, agesno(1,1))         call nf95_get_var(ncid, varid, agesno(:, 1))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <AGESNO>"  
           stop 1  
        ENDIF  
546         xmin = 1.0E+20         xmin = 1.0E+20
547         xmax = -1.0E+20         xmax = -1.0E+20
548         DO i = 1, klon         DO i = 1, klon
549            xmin = MIN(agesno(i,1),xmin)            xmin = MIN(agesno(i, 1), xmin)
550            xmax = MAX(agesno(i,1),xmax)            xmax = MAX(agesno(i, 1), xmax)
551         ENDDO         ENDDO
552         PRINT*,'Age de la neige <AGESNO>', xmin, xmax         PRINT *, 'Age de la neige <AGESNO>', xmin, xmax
553         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
554            DO i = 1, klon            DO i = 1, klon
555               agesno(i,nsrf) = agesno(i,1)               agesno(i, nsrf) = agesno(i, 1)
556            ENDDO            ENDDO
557         ENDDO         ENDDO
558      ENDIF      ENDIF
559    
560        call NF95_INQ_VARID(ncid, "ZMEA", varid)
561      ierr = NF_INQ_VARID (nid, "ZMEA", nvarid)      call NF95_GET_VAR(ncid, varid, zmea)
     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  
562      xmin = 1.0E+20      xmin = 1.0E+20
563      xmax = -1.0E+20      xmax = -1.0E+20
564      DO i = 1, klon      DO i = 1, klon
565         xmin = MIN(zmea(i),xmin)         xmin = MIN(zmea(i), xmin)
566         xmax = MAX(zmea(i),xmax)         xmax = MAX(zmea(i), xmax)
567      ENDDO      ENDDO
568      PRINT*,'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
569    
570        call NF95_INQ_VARID(ncid, "ZSTD", varid)
571      ierr = NF_INQ_VARID (nid, "ZSTD", nvarid)      call NF95_GET_VAR(ncid, varid, zstd)
     IF (ierr.NE.NF_NOERR) THEN  
        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  
572      xmin = 1.0E+20      xmin = 1.0E+20
573      xmax = -1.0E+20      xmax = -1.0E+20
574      DO i = 1, klon      DO i = 1, klon
575         xmin = MIN(zstd(i),xmin)         xmin = MIN(zstd(i), xmin)
576         xmax = MAX(zstd(i),xmax)         xmax = MAX(zstd(i), xmax)
577      ENDDO      ENDDO
578      PRINT*,'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
579    
580        call NF95_INQ_VARID(ncid, "ZSIG", varid)
581      ierr = NF_INQ_VARID (nid, "ZSIG", nvarid)      call NF95_GET_VAR(ncid, varid, zsig)
     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  
582      xmin = 1.0E+20      xmin = 1.0E+20
583      xmax = -1.0E+20      xmax = -1.0E+20
584      DO i = 1, klon      DO i = 1, klon
585         xmin = MIN(zsig(i),xmin)         xmin = MIN(zsig(i), xmin)
586         xmax = MAX(zsig(i),xmax)         xmax = MAX(zsig(i), xmax)
587      ENDDO      ENDDO
588      PRINT*,'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
589    
590        call NF95_INQ_VARID(ncid, "ZGAM", varid)
591      ierr = NF_INQ_VARID (nid, "ZGAM", nvarid)      call NF95_GET_VAR(ncid, varid, zgam)
     IF (ierr.NE.NF_NOERR) THEN  
        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  
592      xmin = 1.0E+20      xmin = 1.0E+20
593      xmax = -1.0E+20      xmax = -1.0E+20
594      DO i = 1, klon      DO i = 1, klon
595         xmin = MIN(zgam(i),xmin)         xmin = MIN(zgam(i), xmin)
596         xmax = MAX(zgam(i),xmax)         xmax = MAX(zgam(i), xmax)
597      ENDDO      ENDDO
598      PRINT*,'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
599    
600        call NF95_INQ_VARID(ncid, "ZTHE", varid)
601      ierr = NF_INQ_VARID (nid, "ZTHE", nvarid)      call NF95_GET_VAR(ncid, varid, zthe)
     IF (ierr.NE.NF_NOERR) THEN  
        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  
602      xmin = 1.0E+20      xmin = 1.0E+20
603      xmax = -1.0E+20      xmax = -1.0E+20
604      DO i = 1, klon      DO i = 1, klon
605         xmin = MIN(zthe(i),xmin)         xmin = MIN(zthe(i), xmin)
606         xmax = MAX(zthe(i),xmax)         xmax = MAX(zthe(i), xmax)
607      ENDDO      ENDDO
608      PRINT*,'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
   
609    
610      ierr = NF_INQ_VARID (nid, "ZPIC", nvarid)      call NF95_INQ_VARID(ncid, "ZPIC", varid)
611      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  
612      xmin = 1.0E+20      xmin = 1.0E+20
613      xmax = -1.0E+20      xmax = -1.0E+20
614      DO i = 1, klon      DO i = 1, klon
615         xmin = MIN(zpic(i),xmin)         xmin = MIN(zpic(i), xmin)
616         xmax = MAX(zpic(i),xmax)         xmax = MAX(zpic(i), xmax)
617      ENDDO      ENDDO
618      PRINT*,'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
619    
620      ierr = NF_INQ_VARID (nid, "ZVAL", nvarid)      call NF95_INQ_VARID(ncid, "ZVAL", varid)
621      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  
622      xmin = 1.0E+20      xmin = 1.0E+20
623      xmax = -1.0E+20      xmax = -1.0E+20
624      DO i = 1, klon      DO i = 1, klon
625         xmin = MIN(zval(i),xmin)         xmin = MIN(zval(i), xmin)
626         xmax = MAX(zval(i),xmax)         xmax = MAX(zval(i), xmax)
627      ENDDO      ENDDO
628      PRINT*,'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
629    
630      ancien_ok = .TRUE.      ancien_ok = .TRUE.
631    
632      ierr = NF_INQ_VARID (nid, "TANCIEN", nvarid)      ierr = NF90_INQ_VARID(ncid, "TANCIEN", varid)
633      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
634         PRINT*, "phyetat0: Le champ <TANCIEN> est absent"         PRINT *, "phyetat0: Le champ <TANCIEN> est absent"
635         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
636         ancien_ok = .FALSE.         ancien_ok = .FALSE.
637      ELSE      ELSE
638         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  
639      ENDIF      ENDIF
640    
641      ierr = NF_INQ_VARID (nid, "QANCIEN", nvarid)      ierr = NF90_INQ_VARID(ncid, "QANCIEN", varid)
642      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
643         PRINT*, "phyetat0: Le champ <QANCIEN> est absent"         PRINT *, "phyetat0: Le champ <QANCIEN> est absent"
644         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
645         ancien_ok = .FALSE.         ancien_ok = .FALSE.
646      ELSE      ELSE
647         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  
648      ENDIF      ENDIF
649    
650      ierr = NF_INQ_VARID (nid, "CLWCON", nvarid)      ierr = NF90_INQ_VARID(ncid, "CLWCON", varid)
651      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
652         PRINT*, "phyetat0: Le champ CLWCON est absent"         PRINT *, "phyetat0: Le champ CLWCON est absent"
653         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
654         clwcon = 0.         clwcon = 0.
655      ELSE      ELSE
656         ierr = NF_GET_VAR_REAL(nid, nvarid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
657         IF (ierr.NE.NF_NOERR) THEN         clwcon(:, 2:) = 0.
           PRINT*, "phyetat0: Lecture echouee pour <CLWCON>"  
           stop 1  
        ENDIF  
658      ENDIF      ENDIF
659      xmin = 1.0E+20      xmin = 1.0E+20
660      xmax = -1.0E+20      xmax = -1.0E+20
661      xmin = MINval(clwcon)      xmin = MINval(clwcon)
662      xmax = MAXval(clwcon)      xmax = MAXval(clwcon)
663      PRINT*,'Eau liquide convective (ecart-type) clwcon:', xmin, xmax      PRINT *, 'Eau liquide convective (ecart-type) clwcon:', xmin, xmax
664    
665      ierr = NF_INQ_VARID (nid, "RNEBCON", nvarid)      ierr = NF90_INQ_VARID(ncid, "RNEBCON", varid)
666      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
667         PRINT*, "phyetat0: Le champ RNEBCON est absent"         PRINT *, "phyetat0: Le champ RNEBCON est absent"
668         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
669         rnebcon = 0.         rnebcon = 0.
670      ELSE      ELSE
671         ierr = NF_GET_VAR_REAL(nid, nvarid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
672         IF (ierr.NE.NF_NOERR) THEN         rnebcon(:, 2:) = 0.
           PRINT*, "phyetat0: Lecture echouee pour <RNEBCON>"  
           stop 1  
        ENDIF  
673      ENDIF      ENDIF
674      xmin = 1.0E+20      xmin = 1.0E+20
675      xmax = -1.0E+20      xmax = -1.0E+20
676      xmin = MINval(rnebcon)      xmin = MINval(rnebcon)
677      xmax = MAXval(rnebcon)      xmax = MAXval(rnebcon)
678      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  
679    
680      ! Lecture ratqs      ! Lecture ratqs
681    
682      ierr = NF_INQ_VARID (nid, "RATQS", nvarid)      ierr = NF90_INQ_VARID(ncid, "RATQS", varid)
683      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
684         PRINT*, "phyetat0: Le champ <RATQS> est absent"         PRINT *, "phyetat0: Le champ <RATQS> est absent"
685         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
686         ratqs = 0.         ratqs = 0.
687      ELSE      ELSE
688         ierr = NF_GET_VAR_REAL(nid, nvarid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
689         IF (ierr.NE.NF_NOERR) THEN         ratqs(:, 2:) = 0.
           PRINT*, "phyetat0: Lecture echouee pour <RATQS>"  
           stop 1  
        ENDIF  
690      ENDIF      ENDIF
691      xmin = 1.0E+20      xmin = 1.0E+20
692      xmax = -1.0E+20      xmax = -1.0E+20
693      xmin = MINval(ratqs)      xmin = MINval(ratqs)
694      xmax = MAXval(ratqs)      xmax = MAXval(ratqs)
695      PRINT*,'(ecart-type) ratqs:', xmin, xmax      PRINT *, '(ecart-type) ratqs:', xmin, xmax
696    
697      ! Lecture run_off_lic_0      ! Lecture run_off_lic_0
698    
699      ierr = NF_INQ_VARID (nid, "RUNOFFLIC0", nvarid)      ierr = NF90_INQ_VARID(ncid, "RUNOFFLIC0", varid)
700      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
701         PRINT*, "phyetat0: Le champ <RUNOFFLIC0> est absent"         PRINT *, "phyetat0: Le champ <RUNOFFLIC0> est absent"
702         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
703         run_off_lic_0 = 0.         run_off_lic_0 = 0.
704      ELSE      ELSE
705         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  
706      ENDIF      ENDIF
707      xmin = 1.0E+20      xmin = 1.0E+20
708      xmax = -1.0E+20      xmax = -1.0E+20
709      xmin = MINval(run_off_lic_0)      xmin = MINval(run_off_lic_0)
710      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
711      PRINT*,'(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
712    
713        call nf95_inq_varid(ncid, "sig1", varid)
714        call nf95_get_var(ncid, varid, sig1)
715    
716      ! Fermer le fichier:      call nf95_inq_varid(ncid, "w01", varid)
717        call nf95_get_var(ncid, varid, w01)
718    
719      ierr = NF_CLOSE(nid)      call NF95_CLOSE(ncid)
720    
721    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0
722    

Legend:
Removed from v.15  
changed lines
  Added in v.101

  ViewVC Help
Powered by ViewVC 1.1.21