/[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 22 by guez, Fri Jul 31 15:18:47 2009 UTC trunk/phylmd/phyetat0.f90 revision 76 by guez, Fri Nov 15 18:45:49 2013 UTC
# Line 10  module phyetat0_m Line 10  module phyetat0_m
10    
11  contains  contains
12    
13    SUBROUTINE phyetat0(fichnom, pctsrf, tsol,tsoil, ocean, tslab,seaice, &    SUBROUTINE phyetat0(fichnom, pctsrf, tsol, tsoil, ocean, tslab, seaice, &
14         qsurf,qsol,snow, &         qsurf, qsol, snow, albe, alblw, evap, rain_fall, snow_fall, solsw, &
15         albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, &         sollw, fder, radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, &
16         fder,radsol,frugs,agesno, &         zpic, zval, t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, &
17         zmea,zstd,zsig,zgam,zthe,zpic,zval, &         run_off_lic_0, 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_get_att, nf90_global, nf90_inq_varid, NF90_NOERR, &
28             NF90_NOWRITE
29        use netcdf95, only: handle_err, nf95_get_var, nf95_close, NF95_OPEN, &
30             nf95_inq_varid
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  
32    
33      include "netcdf.inc"      CHARACTER(len=*), intent(in):: fichnom
34        REAL pctsrf(klon, nbsrf)
35      CHARACTER(len=*) fichnom      REAL tsol(klon, nbsrf)
36      REAL tsol(klon,nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
37      REAL tsoil(klon,nsoilmx,nbsrf)      CHARACTER(len=*), intent(in):: ocean
     !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 qsol(klon)
41      REAL snow(klon,nbsrf)      REAL snow(klon, nbsrf)
42      REAL albe(klon,nbsrf)      REAL albe(klon, nbsrf)
43      REAL alblw(klon,nbsrf)      REAL alblw(klon, nbsrf)
44      REAL evap(klon,nbsrf)      REAL evap(klon, nbsrf)
45      REAL radsol(klon)      REAL, intent(out):: rain_fall(klon)
     REAL rain_fall(klon)  
46      REAL snow_fall(klon)      REAL snow_fall(klon)
     REAL sollw(klon)  
47      real solsw(klon)      real solsw(klon)
48        REAL, intent(out):: sollw(klon)
49      real fder(klon)      real fder(klon)
50      REAL frugs(klon,nbsrf)      REAL radsol(klon)
51      REAL agesno(klon,nbsrf)      REAL frugs(klon, nbsrf)
52        REAL agesno(klon, nbsrf)
53      REAL zmea(klon)      REAL zmea(klon)
54      REAL, intent(out):: zstd(klon)      REAL, intent(out):: zstd(klon)
55      REAL, intent(out):: zsig(klon)      REAL, intent(out):: zsig(klon)
# Line 57  contains Line 57  contains
57      REAL zthe(klon)      REAL zthe(klon)
58      REAL zpic(klon)      REAL zpic(klon)
59      REAL zval(klon)      REAL zval(klon)
60      REAL pctsrf(klon, nbsrf)      REAL t_ancien(klon, klev), q_ancien(klon, klev)
61      REAL fractint(klon)      LOGICAL, intent(out):: ancien_ok
62        real rnebcon(klon, klev), ratqs(klon, klev), clwcon(klon, klev)
63      REAL run_off_lic_0(klon)      REAL run_off_lic_0(klon)
64        real, intent(out):: sig1(klon, klev) ! section adiabatic updraft
65    
66      REAL t_ancien(klon,klev), q_ancien(klon,klev)      real, intent(out):: w01(klon, klev)
67      real rnebcon(klon,klev),clwcon(klon,klev),ratqs(klon,klev)      ! vertical velocity within adiabatic updraft
     LOGICAL ancien_ok  
   
     CHARACTER(len=*), intent(in):: ocean  
68    
69        ! Local:
70        REAL fractint(klon)
71      REAL xmin, xmax      REAL xmin, xmax
72        INTEGER ncid, varid
     INTEGER nid, nvarid  
73      INTEGER ierr, i, nsrf, isoil      INTEGER ierr, i, nsrf, isoil
74      CHARACTER*7 str7      CHARACTER(len=7) str7
75      CHARACTER*2 str2      CHARACTER(len=2) str2
76    
77      !---------------------------------------------------------------      !---------------------------------------------------------------
78    
79      print *, "Call sequence information: phyetat0"      print *, "Call sequence information: phyetat0"
80    
81      ! Ouvrir le fichier contenant l'etat initial:      ! Fichier contenant l'état initial :
   
82      print *, 'fichnom = ', fichnom      print *, 'fichnom = ', fichnom
83      ierr = NF_OPEN (fichnom, NF_NOWRITE,nid)      call NF95_OPEN(fichnom, NF90_NOWRITE, ncid)
     IF (ierr.NE.NF_NOERR) THEN  
        write(6,*)' Pb d''ouverture du fichier '//fichnom  
        write(6,*)' ierr = ', ierr  
        STOP 1  
     ENDIF  
84    
85      ierr = nf90_get_att(nid, nf90_global, "itau_phy", itau_phy)      ierr = nf90_get_att(ncid, nf90_global, "itau_phy", itau_phy)
86      call handle_err("phyetat0 itau_phy", ierr, nid, nf90_global)      call handle_err("phyetat0 itau_phy", ierr, ncid, nf90_global)
87    
88      ! Lecture des latitudes (coordonnees):      ! Lecture des latitudes (coordonnees):
89    
90      ierr = NF_INQ_VARID (nid, "latitude", nvarid)      call NF95_INQ_VARID(ncid, "latitude", varid)
91      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  
92    
93      ! Lecture des longitudes (coordonnees):      ! Lecture des longitudes (coordonnees):
94    
95      ierr = NF_INQ_VARID (nid, "longitude", nvarid)      call NF95_INQ_VARID(ncid, "longitude", varid)
96      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  
   
97    
98      ! Lecture du masque terre mer      ! Lecture du masque terre mer
99    
100      ierr = NF_INQ_VARID (nid, "masque", nvarid)      ierr = NF90_INQ_VARID(ncid, "masque", varid)
101      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
102         ierr = NF_GET_VAR_REAL(nid, nvarid, zmasq)         call nf95_get_var(ncid, varid, zmasq)
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, 'phyetat0: Lecture echouee pour <masque>'  
           stop 1  
        ENDIF  
103      else      else
104         PRINT*, 'phyetat0: Le champ <masque> est absent'         PRINT *, 'phyetat0: Le champ <masque> est absent'
105         PRINT*, 'fichier startphy non compatible avec phyetat0'         PRINT *, 'fichier startphy non compatible avec phyetat0'
        !      stop 1  
106      ENDIF      ENDIF
107      ! Lecture des fractions pour chaque sous-surface      ! Lecture des fractions pour chaque sous-surface
108    
# Line 140  contains Line 112  contains
112    
113      ! fraction de terre      ! fraction de terre
114    
115      ierr = NF_INQ_VARID (nid, "FTER", nvarid)      ierr = NF90_INQ_VARID(ncid, "FTER", varid)
116      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
117         ierr = NF_GET_VAR_REAL(nid, nvarid, pctsrf(1 : klon,is_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  
118      else      else
119         PRINT*, 'phyetat0: Le champ <FTER> est absent'         PRINT *, 'phyetat0: Le champ <FTER> est absent'
        !$$$         stop 1  
120      ENDIF      ENDIF
121    
122      ! fraction de glace de terre      ! fraction de glace de terre
123    
124      ierr = NF_INQ_VARID (nid, "FLIC", nvarid)      ierr = NF90_INQ_VARID(ncid, "FLIC", varid)
125      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
126         ierr = NF_GET_VAR_REAL(nid, nvarid, pctsrf(1 : klon,is_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  
127      else      else
128         PRINT*, 'phyetat0: Le champ <FLIC> est absent'         PRINT *, 'phyetat0: Le champ <FLIC> est absent'
        !$$$         stop 1  
129      ENDIF      ENDIF
130    
131      ! fraction d'ocean      ! fraction d'ocean
132    
133      ierr = NF_INQ_VARID (nid, "FOCE", nvarid)      ierr = NF90_INQ_VARID(ncid, "FOCE", varid)
134      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
135         ierr = NF_GET_VAR_REAL(nid, nvarid, pctsrf(1 : klon,is_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  
136      else      else
137         PRINT*, 'phyetat0: Le champ <FOCE> est absent'         PRINT *, 'phyetat0: Le champ <FOCE> est absent'
        !$$$         stop 1  
138      ENDIF      ENDIF
139    
140      ! fraction glace de mer      ! fraction glace de mer
141    
142      ierr = NF_INQ_VARID (nid, "FSIC", nvarid)      ierr = NF90_INQ_VARID(ncid, "FSIC", varid)
143      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
144         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  
145      else      else
146         PRINT*, 'phyetat0: Le champ <FSIC> est absent'         PRINT *, 'phyetat0: Le champ <FSIC> est absent'
        !$$$         stop 1  
147      ENDIF      ENDIF
148    
149      !  Verification de l'adequation entre le masque et les sous-surfaces      ! Verification de l'adequation entre le masque et les sous-surfaces
150    
151      fractint( 1 : klon) = pctsrf(1 : klon, is_ter)  &      fractint = pctsrf(:, is_ter) + pctsrf(:, is_lic)
          + pctsrf(1 : klon, is_lic)  
152      DO i = 1 , klon      DO i = 1 , klon
153         IF ( abs(fractint(i) - zmasq(i) ) .GT. EPSFRA ) THEN         IF ( abs(fractint(i) - zmasq(i) ) > EPSFRA ) THEN
154            WRITE(*,*) 'phyetat0: attention fraction terre pas ',  &            WRITE(*, *) 'phyetat0: attention fraction terre pas ', &
155                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &                 'coherente ', i, zmasq(i), pctsrf(i, is_ter) &
156                 ,pctsrf(i, is_lic)                 , pctsrf(i, is_lic)
157         ENDIF         ENDIF
158      END DO      END DO
159      fractint (1 : klon) =  pctsrf(1 : klon, is_oce)  &      fractint = pctsrf(:, is_oce) + pctsrf(:, is_sic)
          + pctsrf(1 : klon, is_sic)  
160      DO i = 1 , klon      DO i = 1 , klon
161         IF ( abs( fractint(i) - (1. - zmasq(i))) .GT. EPSFRA ) THEN         IF ( abs( fractint(i) - (1. - zmasq(i))) > EPSFRA ) THEN
162            WRITE(*,*) 'phyetat0 attention fraction ocean pas ',  &            WRITE(*, *) 'phyetat0 attention fraction ocean pas ', &
163                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &                 'coherente ', i, zmasq(i) , pctsrf(i, is_oce) &
164                 ,pctsrf(i, is_sic)                 , pctsrf(i, is_sic)
165         ENDIF         ENDIF
166      END DO      END DO
167    
168      ! Lecture des temperatures du sol:      ! Lecture des temperatures du sol:
169    
170      ierr = NF_INQ_VARID (nid, "TS", nvarid)      ierr = NF90_INQ_VARID(ncid, "TS", varid)
171      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
172         PRINT*, 'phyetat0: Le champ <TS> est absent'         PRINT *, 'phyetat0 : Le champ <TS> est absent'
173         PRINT*, '          Mais je vais essayer de lire TS**'         PRINT *, ' Mais je vais essayer de lire TS**'
174         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
175            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
176               PRINT*, "Trop de sous-mailles"               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//">"  
177               stop 1               stop 1
178            ENDIF            ENDIF
179              WRITE(str2, '(i2.2)') nsrf
180              call NF95_INQ_VARID(ncid, "TS"//str2, varid)
181              call NF95_GET_VAR(ncid, varid, tsol(:, nsrf))
182            xmin = 1.0E+20            xmin = 1.0E+20
183            xmax = -1.0E+20            xmax = -1.0E+20
184            DO i = 1, klon            DO i = 1, klon
185               xmin = MIN(tsol(i,nsrf),xmin)               xmin = MIN(tsol(i, nsrf), xmin)
186               xmax = MAX(tsol(i,nsrf),xmax)               xmax = MAX(tsol(i, nsrf), xmax)
187            ENDDO            ENDDO
188            PRINT*,'Temperature du sol TS**:', nsrf, xmin, xmax            PRINT *, 'Temperature du sol TS**:', nsrf, xmin, xmax
189         ENDDO         ENDDO
190      ELSE      ELSE
191         PRINT*, 'phyetat0: Le champ <TS> est present'         PRINT *, 'phyetat0: Le champ <TS> est present'
192         PRINT*, '          J ignore donc les autres temperatures TS**'         PRINT *, ' J ignore donc les autres temperatures TS**'
193         ierr = NF_GET_VAR_REAL(nid, nvarid, tsol(1,1))         call nf95_get_var(ncid, varid, tsol(:, 1))
        IF (ierr.NE.NF_NOERR) THEN  
           PRINT*, "phyetat0: Lecture echouee pour <TS>"  
           stop 1  
        ENDIF  
194         xmin = 1.0E+20         xmin = 1.0E+20
195         xmax = -1.0E+20         xmax = -1.0E+20
196         DO i = 1, klon         DO i = 1, klon
197            xmin = MIN(tsol(i,1),xmin)            xmin = MIN(tsol(i, 1), xmin)
198            xmax = MAX(tsol(i,1),xmax)            xmax = MAX(tsol(i, 1), xmax)
199         ENDDO         ENDDO
200         PRINT*,'Temperature du sol <TS>', xmin, xmax         PRINT *, 'Temperature du sol <TS>', xmin, xmax
201         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
202            DO i = 1, klon            DO i = 1, klon
203               tsol(i,nsrf) = tsol(i,1)               tsol(i, nsrf) = tsol(i, 1)
204            ENDDO            ENDDO
205         ENDDO         ENDDO
206      ENDIF      ENDIF
# Line 271  contains Line 209  contains
209    
210      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
211         DO isoil=1, nsoilmx         DO isoil=1, nsoilmx
212            IF (isoil.GT.99 .AND. nsrf.GT.99) THEN            IF (isoil > 99 .AND. nsrf > 99) THEN
213               PRINT*, "Trop de couches ou sous-mailles"               PRINT *, "Trop de couches ou sous-mailles"
214               stop 1               stop 1
215            ENDIF            ENDIF
216            WRITE(str7,'(i2.2,"srf",i2.2)') isoil, nsrf            WRITE(str7, '(i2.2, "srf", i2.2)') isoil, nsrf
217            ierr = NF_INQ_VARID (nid, 'Tsoil'//str7, nvarid)            ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)
218            IF (ierr.NE.NF_NOERR) THEN            IF (ierr /= NF90_NOERR) THEN
219               PRINT*, "phyetat0: Le champ <Tsoil"//str7//"> est absent"               PRINT *, "phyetat0: Le champ <Tsoil"//str7//"> est absent"
220               PRINT*, "          Il prend donc la valeur de surface"               PRINT *, " Il prend donc la valeur de surface"
221               DO i=1, klon               DO i=1, klon
222                  tsoil(i,isoil,nsrf)=tsol(i,nsrf)                  tsoil(i, isoil, nsrf)=tsol(i, nsrf)
223               ENDDO               ENDDO
224            ELSE            ELSE
225               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  
226            ENDIF            ENDIF
227         ENDDO         ENDDO
228      ENDDO      ENDDO
229    
230      !IM "slab" ocean      !IM "slab" ocean
231    
232      ! Lecture de tslab (pour slab ocean seulement):            ! Lecture de tslab (pour slab ocean seulement):
233    
234      IF (ocean .eq. 'slab  ') then      IF (ocean .eq. 'slab ') then
235         ierr = NF_INQ_VARID (nid, "TSLAB", nvarid)         call NF95_INQ_VARID(ncid, "TSLAB", varid)
236         IF (ierr.NE.NF_NOERR) THEN         call nf95_get_var(ncid, varid, tslab)
           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  
237         xmin = 1.0E+20         xmin = 1.0E+20
238         xmax = -1.0E+20         xmax = -1.0E+20
239         DO i = 1, klon         DO i = 1, klon
240            xmin = MIN(tslab(i),xmin)            xmin = MIN(tslab(i), xmin)
241            xmax = MAX(tslab(i),xmax)            xmax = MAX(tslab(i), xmax)
242         ENDDO         ENDDO
243         PRINT*,'Ecart de la SST tslab:', xmin, xmax         PRINT *, 'Ecart de la SST tslab:', xmin, xmax
244    
245         ! Lecture de seaice (pour slab ocean seulement):         ! Lecture de seaice (pour slab ocean seulement):
246    
247         ierr = NF_INQ_VARID (nid, "SEAICE", nvarid)         call NF95_INQ_VARID(ncid, "SEAICE", varid)
248         IF (ierr.NE.NF_NOERR) THEN         call nf95_get_var(ncid, varid, seaice)
           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  
249         xmin = 1.0E+20         xmin = 1.0E+20
250         xmax = -1.0E+20         xmax = -1.0E+20
251         DO i = 1, klon         DO i = 1, klon
252            xmin = MIN(seaice(i),xmin)            xmin = MIN(seaice(i), xmin)
253            xmax = MAX(seaice(i),xmax)            xmax = MAX(seaice(i), xmax)
254         ENDDO         ENDDO
255         PRINT*,'Masse de la glace de mer seaice:', xmin, xmax         PRINT *, 'Masse de la glace de mer seaice:', xmin, xmax
256      ELSE      ELSE
257         tslab = 0.         tslab = 0.
258         seaice = 0.         seaice = 0.
# Line 342  contains Line 260  contains
260    
261      ! Lecture de l'humidite de l'air juste au dessus du sol:      ! Lecture de l'humidite de l'air juste au dessus du sol:
262    
263      ierr = NF_INQ_VARID (nid, "QS", nvarid)      ierr = NF90_INQ_VARID(ncid, "QS", varid)
264      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
265         PRINT*, 'phyetat0: Le champ <QS> est absent'         PRINT *, 'phyetat0: Le champ <QS> est absent'
266         PRINT*, '          Mais je vais essayer de lire QS**'         PRINT *, ' Mais je vais essayer de lire QS**'
267         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
268            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
269               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//">"  
270               stop 1               stop 1
271            ENDIF            ENDIF
272              WRITE(str2, '(i2.2)') nsrf
273              call NF95_INQ_VARID(ncid, "QS"//str2, varid)
274              call NF95_GET_VAR(ncid, varid, qsurf(:, nsrf))
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(qsurf(i,nsrf),xmin)               xmin = MIN(qsurf(i, nsrf), xmin)
279               xmax = MAX(qsurf(i,nsrf),xmax)               xmax = MAX(qsurf(i, nsrf), xmax)
280            ENDDO            ENDDO
281            PRINT*,'Humidite pres du sol QS**:', nsrf, xmin, xmax            PRINT *, 'Humidite pres du sol QS**:', nsrf, xmin, xmax
282         ENDDO         ENDDO
283      ELSE      ELSE
284         PRINT*, 'phyetat0: Le champ <QS> est present'         PRINT *, 'phyetat0: Le champ <QS> est present'
285         PRINT*, '          J ignore donc les autres humidites QS**'         PRINT *, ' J ignore donc les autres humidites QS**'
286         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  
287         xmin = 1.0E+20         xmin = 1.0E+20
288         xmax = -1.0E+20         xmax = -1.0E+20
289         DO i = 1, klon         DO i = 1, klon
290            xmin = MIN(qsurf(i,1),xmin)            xmin = MIN(qsurf(i, 1), xmin)
291            xmax = MAX(qsurf(i,1),xmax)            xmax = MAX(qsurf(i, 1), xmax)
292         ENDDO         ENDDO
293         PRINT*,'Humidite pres du sol <QS>', xmin, xmax         PRINT *, 'Humidite pres du sol <QS>', xmin, xmax
294         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
295            DO i = 1, klon            DO i = 1, klon
296               qsurf(i,nsrf) = qsurf(i,1)               qsurf(i, nsrf) = qsurf(i, 1)
297            ENDDO            ENDDO
298         ENDDO         ENDDO
299      ENDIF      ENDIF
300    
301      ! Eau dans le sol (pour le modele de sol "bucket")      ! Eau dans le sol (pour le modele de sol "bucket")
302    
303      ierr = NF_INQ_VARID (nid, "QSOL", nvarid)      ierr = NF90_INQ_VARID(ncid, "QSOL", varid)
304      IF (ierr .EQ.  NF_NOERR) THEN      IF (ierr == NF90_NOERR) THEN
305         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  
306      else      else
307         PRINT*, 'phyetat0: Le champ <QSOL> est absent'         PRINT *, 'phyetat0: Le champ <QSOL> est absent'
308         PRINT*, '          Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
309         qsol(:)=0.         qsol = 0.
        !$$$         stop 1  
310      ENDIF      ENDIF
311      xmin = 1.0E+20      xmin = 1.0E+20
312      xmax = -1.0E+20      xmax = -1.0E+20
313      DO i = 1, klon      DO i = 1, klon
314         xmin = MIN(qsol(i),xmin)         xmin = MIN(qsol(i), xmin)
315         xmax = MAX(qsol(i),xmax)         xmax = MAX(qsol(i), xmax)
316      ENDDO      ENDDO
317      PRINT*,'Eau dans le sol (mm) <QSOL>', xmin, xmax      PRINT *, 'Eau dans le sol (mm) <QSOL>', xmin, xmax
318    
319      ! Lecture de neige au sol:      ! Lecture de neige au sol:
320    
321      ierr = NF_INQ_VARID (nid, "SNOW", nvarid)      ierr = NF90_INQ_VARID(ncid, "SNOW", varid)
322      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
323         PRINT*, 'phyetat0: Le champ <SNOW> est absent'         PRINT *, 'phyetat0: Le champ <SNOW> est absent'
324         PRINT*, '          Mais je vais essayer de lire SNOW**'         PRINT *, ' Mais je vais essayer de lire SNOW**'
325         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
326            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
327               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//">"  
328               stop 1               stop 1
329            ENDIF            ENDIF
330              WRITE(str2, '(i2.2)') nsrf
331              call NF95_INQ_VARID(ncid, "SNOW"//str2, varid)
332              call NF95_GET_VAR(ncid, varid, snow(:, nsrf))
333            xmin = 1.0E+20            xmin = 1.0E+20
334            xmax = -1.0E+20            xmax = -1.0E+20
335            DO i = 1, klon            DO i = 1, klon
336               xmin = MIN(snow(i,nsrf),xmin)               xmin = MIN(snow(i, nsrf), xmin)
337               xmax = MAX(snow(i,nsrf),xmax)               xmax = MAX(snow(i, nsrf), xmax)
338            ENDDO            ENDDO
339            PRINT*,'Neige du sol SNOW**:', nsrf, xmin, xmax            PRINT *, 'Neige du sol SNOW**:', nsrf, xmin, xmax
340         ENDDO         ENDDO
341      ELSE      ELSE
342         PRINT*, 'phyetat0: Le champ <SNOW> est present'         PRINT *, 'phyetat0: Le champ <SNOW> est present'
343         PRINT*, '          J ignore donc les autres neiges SNOW**'         PRINT *, ' J ignore donc les autres neiges SNOW**'
344         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  
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(snow(i,1),xmin)            xmin = MIN(snow(i, 1), xmin)
349            xmax = MAX(snow(i,1),xmax)            xmax = MAX(snow(i, 1), xmax)
350         ENDDO         ENDDO
351         PRINT*,'Neige du sol <SNOW>', xmin, xmax         PRINT *, 'Neige du sol <SNOW>', xmin, xmax
352         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
353            DO i = 1, klon            DO i = 1, klon
354               snow(i,nsrf) = snow(i,1)               snow(i, nsrf) = snow(i, 1)
355            ENDDO            ENDDO
356         ENDDO         ENDDO
357      ENDIF      ENDIF
358    
359      ! Lecture de albedo au sol:      ! Lecture de albedo au sol:
360    
361      ierr = NF_INQ_VARID (nid, "ALBE", nvarid)      ierr = NF90_INQ_VARID(ncid, "ALBE", varid)
362      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
363         PRINT*, 'phyetat0: Le champ <ALBE> est absent'         PRINT *, 'phyetat0: Le champ <ALBE> est absent'
364         PRINT*, '          Mais je vais essayer de lire ALBE**'         PRINT *, ' Mais je vais essayer de lire ALBE**'
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, "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//">"  
368               stop 1               stop 1
369            ENDIF            ENDIF
370              WRITE(str2, '(i2.2)') nsrf
371              call NF95_INQ_VARID(ncid, "ALBE"//str2, varid)
372              call NF95_GET_VAR(ncid, varid, albe(:, 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(albe(i,nsrf),xmin)               xmin = MIN(albe(i, nsrf), xmin)
377               xmax = MAX(albe(i,nsrf),xmax)               xmax = MAX(albe(i, nsrf), xmax)
378            ENDDO            ENDDO
379            PRINT*,'Albedo du sol ALBE**:', nsrf, xmin, xmax            PRINT *, 'Albedo du sol ALBE**:', nsrf, xmin, xmax
380         ENDDO         ENDDO
381      ELSE      ELSE
382         PRINT*, 'phyetat0: Le champ <ALBE> est present'         PRINT *, 'phyetat0: Le champ <ALBE> est present'
383         PRINT*, '          J ignore donc les autres ALBE**'         PRINT *, ' J ignore donc les autres ALBE**'
384         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  
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(albe(i,1),xmin)            xmin = MIN(albe(i, 1), xmin)
389            xmax = MAX(albe(i,1),xmax)            xmax = MAX(albe(i, 1), xmax)
390         ENDDO         ENDDO
391         PRINT*,'Neige du sol <ALBE>', xmin, xmax         PRINT *, 'Neige du sol <ALBE>', xmin, xmax
392         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
393            DO i = 1, klon            DO i = 1, klon
394               albe(i,nsrf) = albe(i,1)               albe(i, nsrf) = albe(i, 1)
395            ENDDO            ENDDO
396         ENDDO         ENDDO
397      ENDIF      ENDIF
398    
   
399      ! Lecture de albedo au sol LW:      ! Lecture de albedo au sol LW:
400    
401      ierr = NF_INQ_VARID (nid, "ALBLW", nvarid)      ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)
402      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
403         PRINT*, 'phyetat0: Le champ <ALBLW> est absent'         PRINT *, 'phyetat0: Le champ <ALBLW> est absent'
404         !        PRINT*, '          Mais je vais essayer de lire ALBLW**'         ! PRINT *, ' Mais je vais essayer de lire ALBLW**'
405         PRINT*, '          Mais je vais prendre ALBE**'         PRINT *, ' Mais je vais prendre ALBE**'
406         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
407            DO i = 1, klon            DO i = 1, klon
408               alblw(i,nsrf) = albe(i,nsrf)               alblw(i, nsrf) = albe(i, nsrf)
409            ENDDO            ENDDO
410         ENDDO         ENDDO
411      ELSE      ELSE
412         PRINT*, 'phyetat0: Le champ <ALBLW> est present'         PRINT *, 'phyetat0: Le champ <ALBLW> est present'
413         PRINT*, '          J ignore donc les autres ALBLW**'         PRINT *, ' J ignore donc les autres ALBLW**'
414         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  
415         xmin = 1.0E+20         xmin = 1.0E+20
416         xmax = -1.0E+20         xmax = -1.0E+20
417         DO i = 1, klon         DO i = 1, klon
418            xmin = MIN(alblw(i,1),xmin)            xmin = MIN(alblw(i, 1), xmin)
419            xmax = MAX(alblw(i,1),xmax)            xmax = MAX(alblw(i, 1), xmax)
420         ENDDO         ENDDO
421         PRINT*,'Neige du sol <ALBLW>', xmin, xmax         PRINT *, 'Neige du sol <ALBLW>', xmin, xmax
422         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
423            DO i = 1, klon            DO i = 1, klon
424               alblw(i,nsrf) = alblw(i,1)               alblw(i, nsrf) = alblw(i, 1)
425            ENDDO            ENDDO
426         ENDDO         ENDDO
427      ENDIF      ENDIF
428    
429      ! Lecture de evaporation:        ! Lecture de evaporation:
430    
431      ierr = NF_INQ_VARID (nid, "EVAP", nvarid)      ierr = NF90_INQ_VARID(ncid, "EVAP", varid)
432      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
433         PRINT*, 'phyetat0: Le champ <EVAP> est absent'         PRINT *, 'phyetat0: Le champ <EVAP> est absent'
434         PRINT*, '          Mais je vais essayer de lire EVAP**'         PRINT *, ' Mais je vais essayer de lire EVAP**'
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"
              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//">"  
438               stop 1               stop 1
439            ENDIF            ENDIF
440              WRITE(str2, '(i2.2)') nsrf
441              call NF95_INQ_VARID(ncid, "EVAP"//str2, varid)
442              call NF95_GET_VAR(ncid, varid, evap(:, nsrf))
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(evap(i,nsrf),xmin)               xmin = MIN(evap(i, nsrf), xmin)
447               xmax = MAX(evap(i,nsrf),xmax)               xmax = MAX(evap(i, nsrf), xmax)
448            ENDDO            ENDDO
449            PRINT*,'evap du sol EVAP**:', nsrf, xmin, xmax            PRINT *, 'evap du sol EVAP**:', nsrf, xmin, xmax
450         ENDDO         ENDDO
451      ELSE      ELSE
452         PRINT*, 'phyetat0: Le champ <EVAP> est present'         PRINT *, 'phyetat0: Le champ <EVAP> est present'
453         PRINT*, '          J ignore donc les autres EVAP**'         PRINT *, ' J ignore donc les autres EVAP**'
454         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  
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(evap(i,1),xmin)            xmin = MIN(evap(i, 1), xmin)
459            xmax = MAX(evap(i,1),xmax)            xmax = MAX(evap(i, 1), xmax)
460         ENDDO         ENDDO
461         PRINT*,'Evap du sol <EVAP>', xmin, xmax         PRINT *, 'Evap du sol <EVAP>', xmin, xmax
462         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
463            DO i = 1, klon            DO i = 1, klon
464               evap(i,nsrf) = evap(i,1)               evap(i, nsrf) = evap(i, 1)
465            ENDDO            ENDDO
466         ENDDO         ENDDO
467      ENDIF      ENDIF
468    
469      ! Lecture precipitation liquide:      ! Lecture precipitation liquide:
470    
471      ierr = NF_INQ_VARID (nid, "rain_f", nvarid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
472      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  
473      xmin = 1.0E+20      xmin = 1.0E+20
474      xmax = -1.0E+20      xmax = -1.0E+20
475      DO i = 1, klon      DO i = 1, klon
476         xmin = MIN(rain_fall(i),xmin)         xmin = MIN(rain_fall(i), xmin)
477         xmax = MAX(rain_fall(i),xmax)         xmax = MAX(rain_fall(i), xmax)
478      ENDDO      ENDDO
479      PRINT*,'Precipitation liquide rain_f:', xmin, xmax      PRINT *, 'Precipitation liquide rain_f:', xmin, xmax
480    
481      ! Lecture precipitation solide:      ! Lecture precipitation solide:
482    
483      ierr = NF_INQ_VARID (nid, "snow_f", nvarid)      call NF95_INQ_VARID(ncid, "snow_f", varid)
484      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  
485      xmin = 1.0E+20      xmin = 1.0E+20
486      xmax = -1.0E+20      xmax = -1.0E+20
487      DO i = 1, klon      DO i = 1, klon
488         xmin = MIN(snow_fall(i),xmin)         xmin = MIN(snow_fall(i), xmin)
489         xmax = MAX(snow_fall(i),xmax)         xmax = MAX(snow_fall(i), xmax)
490      ENDDO      ENDDO
491      PRINT*,'Precipitation solide snow_f:', xmin, xmax      PRINT *, 'Precipitation solide snow_f:', xmin, xmax
492    
493      ! Lecture rayonnement solaire au sol:      ! Lecture rayonnement solaire au sol:
494    
495      ierr = NF_INQ_VARID (nid, "solsw", nvarid)      ierr = NF90_INQ_VARID(ncid, "solsw", varid)
496      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
497         PRINT*, 'phyetat0: Le champ <solsw> est absent'         PRINT *, 'phyetat0: Le champ <solsw> est absent'
498         PRINT*, 'mis a zero'         PRINT *, 'mis a zero'
499         solsw = 0.         solsw = 0.
500      ELSE      ELSE
501         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  
502      ENDIF      ENDIF
503      xmin = 1.0E+20      xmin = 1.0E+20
504      xmax = -1.0E+20      xmax = -1.0E+20
505      DO i = 1, klon      DO i = 1, klon
506         xmin = MIN(solsw(i),xmin)         xmin = MIN(solsw(i), xmin)
507         xmax = MAX(solsw(i),xmax)         xmax = MAX(solsw(i), xmax)
508      ENDDO      ENDDO
509      PRINT*,'Rayonnement solaire au sol solsw:', xmin, xmax      PRINT *, 'Rayonnement solaire au sol solsw:', xmin, xmax
510    
511      ! Lecture rayonnement IF au sol:      ! Lecture rayonnement IF au sol:
512    
513      ierr = NF_INQ_VARID (nid, "sollw", nvarid)      ierr = NF90_INQ_VARID(ncid, "sollw", varid)
514      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
515         PRINT*, 'phyetat0: Le champ <sollw> est absent'         PRINT *, 'phyetat0: Le champ <sollw> est absent'
516         PRINT*, 'mis a zero'         PRINT *, 'mis a zero'
517         sollw = 0.         sollw = 0.
518      ELSE      ELSE
519         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  
520      ENDIF      ENDIF
521      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  
   
522    
523      ! Lecture derive des flux:      ! Lecture derive des flux:
524    
525      ierr = NF_INQ_VARID (nid, "fder", nvarid)      ierr = NF90_INQ_VARID(ncid, "fder", varid)
526      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
527         PRINT*, 'phyetat0: Le champ <fder> est absent'         PRINT *, 'phyetat0: Le champ <fder> est absent'
528         PRINT*, 'mis a zero'         PRINT *, 'mis a zero'
529         fder = 0.         fder = 0.
530      ELSE      ELSE
531         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  
532      ENDIF      ENDIF
533      xmin = 1.0E+20      xmin = 1.0E+20
534      xmax = -1.0E+20      xmax = -1.0E+20
535      DO i = 1, klon      DO i = 1, klon
536         xmin = MIN(fder(i),xmin)         xmin = MIN(fder(i), xmin)
537         xmax = MAX(fder(i),xmax)         xmax = MAX(fder(i), xmax)
538      ENDDO      ENDDO
539      PRINT*,'Derive des flux fder:', xmin, xmax      PRINT *, 'Derive des flux fder:', xmin, xmax
   
540    
541      ! Lecture du rayonnement net au sol:      ! Lecture du rayonnement net au sol:
542    
543      ierr = NF_INQ_VARID (nid, "RADS", nvarid)      call NF95_INQ_VARID(ncid, "RADS", varid)
544      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  
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(radsol(i),xmin)         xmin = MIN(radsol(i), xmin)
549         xmax = MAX(radsol(i),xmax)         xmax = MAX(radsol(i), xmax)
550      ENDDO      ENDDO
551      PRINT*,'Rayonnement net au sol radsol:', xmin, xmax      PRINT *, 'Rayonnement net au sol radsol:', xmin, xmax
552    
553      ! Lecture de la longueur de rugosite      ! Lecture de la longueur de rugosite
554    
555        ierr = NF90_INQ_VARID(ncid, "RUG", varid)
556      ierr = NF_INQ_VARID (nid, "RUG", nvarid)      IF (ierr /= NF90_NOERR) THEN
557      IF (ierr.NE.NF_NOERR) THEN         PRINT *, 'phyetat0: Le champ <RUG> est absent'
558         PRINT*, 'phyetat0: Le champ <RUG> est absent'         PRINT *, ' Mais je vais essayer de lire RUG**'
        PRINT*, '          Mais je vais essayer de lire RUG**'  
559         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
560            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
561               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//">"  
562               stop 1               stop 1
563            ENDIF            ENDIF
564              WRITE(str2, '(i2.2)') nsrf
565              call NF95_INQ_VARID(ncid, "RUG"//str2, varid)
566              call NF95_GET_VAR(ncid, varid, frugs(:, nsrf))
567            xmin = 1.0E+20            xmin = 1.0E+20
568            xmax = -1.0E+20            xmax = -1.0E+20
569            DO i = 1, klon            DO i = 1, klon
570               xmin = MIN(frugs(i,nsrf),xmin)               xmin = MIN(frugs(i, nsrf), xmin)
571               xmax = MAX(frugs(i,nsrf),xmax)               xmax = MAX(frugs(i, nsrf), xmax)
572            ENDDO            ENDDO
573            PRINT*,'rugosite du sol RUG**:', nsrf, xmin, xmax            PRINT *, 'rugosite du sol RUG**:', nsrf, xmin, xmax
574         ENDDO         ENDDO
575      ELSE      ELSE
576         PRINT*, 'phyetat0: Le champ <RUG> est present'         PRINT *, 'phyetat0: Le champ <RUG> est present'
577         PRINT*, '          J ignore donc les autres RUG**'         PRINT *, ' J ignore donc les autres RUG**'
578         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  
579         xmin = 1.0E+20         xmin = 1.0E+20
580         xmax = -1.0E+20         xmax = -1.0E+20
581         DO i = 1, klon         DO i = 1, klon
582            xmin = MIN(frugs(i,1),xmin)            xmin = MIN(frugs(i, 1), xmin)
583            xmax = MAX(frugs(i,1),xmax)            xmax = MAX(frugs(i, 1), xmax)
584         ENDDO         ENDDO
585         PRINT*,'rugosite <RUG>', xmin, xmax         PRINT *, 'rugosite <RUG>', xmin, xmax
586         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
587            DO i = 1, klon            DO i = 1, klon
588               frugs(i,nsrf) = frugs(i,1)               frugs(i, nsrf) = frugs(i, 1)
589            ENDDO            ENDDO
590         ENDDO         ENDDO
591      ENDIF      ENDIF
592    
   
593      ! Lecture de l'age de la neige:      ! Lecture de l'age de la neige:
594    
595      ierr = NF_INQ_VARID (nid, "AGESNO", nvarid)      ierr = NF90_INQ_VARID(ncid, "AGESNO", varid)
596      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
597         PRINT*, 'phyetat0: Le champ <AGESNO> est absent'         PRINT *, 'phyetat0: Le champ <AGESNO> est absent'
598         PRINT*, '          Mais je vais essayer de lire AGESNO**'         PRINT *, ' Mais je vais essayer de lire AGESNO**'
599         DO nsrf = 1, nbsrf         DO nsrf = 1, nbsrf
600            IF (nsrf.GT.99) THEN            IF (nsrf > 99) THEN
601               PRINT*, "Trop de sous-mailles"               PRINT *, "Trop de sous-mailles"
602               stop 1               stop 1
603            ENDIF            ENDIF
604            WRITE(str2,'(i2.2)') nsrf            WRITE(str2, '(i2.2)') nsrf
605            ierr = NF_INQ_VARID (nid, "AGESNO"//str2, nvarid)            ierr = NF90_INQ_VARID(ncid, "AGESNO"//str2, varid)
606            IF (ierr.NE.NF_NOERR) THEN            IF (ierr /= NF90_NOERR) THEN
607               PRINT*, "phyetat0: Le champ <AGESNO"//str2//"> est absent"               PRINT *, "phyetat0: Le champ <AGESNO"//str2//"> est absent"
608               agesno = 50.0               agesno = 50.0
609            ENDIF            ENDIF
610            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  
611            xmin = 1.0E+20            xmin = 1.0E+20
612            xmax = -1.0E+20            xmax = -1.0E+20
613            DO i = 1, klon            DO i = 1, klon
614               xmin = MIN(agesno(i,nsrf),xmin)               xmin = MIN(agesno(i, nsrf), xmin)
615               xmax = MAX(agesno(i,nsrf),xmax)               xmax = MAX(agesno(i, nsrf), xmax)
616            ENDDO            ENDDO
617            PRINT*,'Age de la neige AGESNO**:', nsrf, xmin, xmax            PRINT *, 'Age de la neige AGESNO**:', nsrf, xmin, xmax
618         ENDDO         ENDDO
619      ELSE      ELSE
620         PRINT*, 'phyetat0: Le champ <AGESNO> est present'         PRINT *, 'phyetat0: Le champ <AGESNO> est present'
621         PRINT*, '          J ignore donc les autres AGESNO**'         PRINT *, ' J ignore donc les autres AGESNO**'
622         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  
623         xmin = 1.0E+20         xmin = 1.0E+20
624         xmax = -1.0E+20         xmax = -1.0E+20
625         DO i = 1, klon         DO i = 1, klon
626            xmin = MIN(agesno(i,1),xmin)            xmin = MIN(agesno(i, 1), xmin)
627            xmax = MAX(agesno(i,1),xmax)            xmax = MAX(agesno(i, 1), xmax)
628         ENDDO         ENDDO
629         PRINT*,'Age de la neige <AGESNO>', xmin, xmax         PRINT *, 'Age de la neige <AGESNO>', xmin, xmax
630         DO nsrf = 2, nbsrf         DO nsrf = 2, nbsrf
631            DO i = 1, klon            DO i = 1, klon
632               agesno(i,nsrf) = agesno(i,1)               agesno(i, nsrf) = agesno(i, 1)
633            ENDDO            ENDDO
634         ENDDO         ENDDO
635      ENDIF      ENDIF
636    
637        call NF95_INQ_VARID(ncid, "ZMEA", varid)
638      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  
639      xmin = 1.0E+20      xmin = 1.0E+20
640      xmax = -1.0E+20      xmax = -1.0E+20
641      DO i = 1, klon      DO i = 1, klon
642         xmin = MIN(zmea(i),xmin)         xmin = MIN(zmea(i), xmin)
643         xmax = MAX(zmea(i),xmax)         xmax = MAX(zmea(i), xmax)
644      ENDDO      ENDDO
645      PRINT*,'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zmea:', xmin, xmax
646    
647        call NF95_INQ_VARID(ncid, "ZSTD", varid)
648      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  
649      xmin = 1.0E+20      xmin = 1.0E+20
650      xmax = -1.0E+20      xmax = -1.0E+20
651      DO i = 1, klon      DO i = 1, klon
652         xmin = MIN(zstd(i),xmin)         xmin = MIN(zstd(i), xmin)
653         xmax = MAX(zstd(i),xmax)         xmax = MAX(zstd(i), xmax)
654      ENDDO      ENDDO
655      PRINT*,'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zstd:', xmin, xmax
656    
657        call NF95_INQ_VARID(ncid, "ZSIG", varid)
658      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  
659      xmin = 1.0E+20      xmin = 1.0E+20
660      xmax = -1.0E+20      xmax = -1.0E+20
661      DO i = 1, klon      DO i = 1, klon
662         xmin = MIN(zsig(i),xmin)         xmin = MIN(zsig(i), xmin)
663         xmax = MAX(zsig(i),xmax)         xmax = MAX(zsig(i), xmax)
664      ENDDO      ENDDO
665      PRINT*,'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zsig:', xmin, xmax
   
666    
667      ierr = NF_INQ_VARID (nid, "ZGAM", nvarid)      call NF95_INQ_VARID(ncid, "ZGAM", varid)
668      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zgam)
        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  
669      xmin = 1.0E+20      xmin = 1.0E+20
670      xmax = -1.0E+20      xmax = -1.0E+20
671      DO i = 1, klon      DO i = 1, klon
672         xmin = MIN(zgam(i),xmin)         xmin = MIN(zgam(i), xmin)
673         xmax = MAX(zgam(i),xmax)         xmax = MAX(zgam(i), xmax)
674      ENDDO      ENDDO
675      PRINT*,'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zgam:', xmin, xmax
   
676    
677      ierr = NF_INQ_VARID (nid, "ZTHE", nvarid)      call NF95_INQ_VARID(ncid, "ZTHE", varid)
678      IF (ierr.NE.NF_NOERR) THEN      call NF95_GET_VAR(ncid, varid, zthe)
        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  
679      xmin = 1.0E+20      xmin = 1.0E+20
680      xmax = -1.0E+20      xmax = -1.0E+20
681      DO i = 1, klon      DO i = 1, klon
682         xmin = MIN(zthe(i),xmin)         xmin = MIN(zthe(i), xmin)
683         xmax = MAX(zthe(i),xmax)         xmax = MAX(zthe(i), xmax)
684      ENDDO      ENDDO
685      PRINT*,'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zthe:', xmin, xmax
686    
687        call NF95_INQ_VARID(ncid, "ZPIC", varid)
688      ierr = NF_INQ_VARID (nid, "ZPIC", nvarid)      call NF95_GET_VAR(ncid, varid, zpic)
     IF (ierr.NE.NF_NOERR) THEN  
        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  
689      xmin = 1.0E+20      xmin = 1.0E+20
690      xmax = -1.0E+20      xmax = -1.0E+20
691      DO i = 1, klon      DO i = 1, klon
692         xmin = MIN(zpic(i),xmin)         xmin = MIN(zpic(i), xmin)
693         xmax = MAX(zpic(i),xmax)         xmax = MAX(zpic(i), xmax)
694      ENDDO      ENDDO
695      PRINT*,'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zpic:', xmin, xmax
696    
697      ierr = NF_INQ_VARID (nid, "ZVAL", nvarid)      call NF95_INQ_VARID(ncid, "ZVAL", varid)
698      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  
699      xmin = 1.0E+20      xmin = 1.0E+20
700      xmax = -1.0E+20      xmax = -1.0E+20
701      DO i = 1, klon      DO i = 1, klon
702         xmin = MIN(zval(i),xmin)         xmin = MIN(zval(i), xmin)
703         xmax = MAX(zval(i),xmax)         xmax = MAX(zval(i), xmax)
704      ENDDO      ENDDO
705      PRINT*,'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax      PRINT *, 'OROGRAPHIE SOUS-MAILLE zval:', xmin, xmax
706    
707      ancien_ok = .TRUE.      ancien_ok = .TRUE.
708    
709      ierr = NF_INQ_VARID (nid, "TANCIEN", nvarid)      ierr = NF90_INQ_VARID(ncid, "TANCIEN", varid)
710      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
711         PRINT*, "phyetat0: Le champ <TANCIEN> est absent"         PRINT *, "phyetat0: Le champ <TANCIEN> est absent"
712         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
713         ancien_ok = .FALSE.         ancien_ok = .FALSE.
714      ELSE      ELSE
715         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  
716      ENDIF      ENDIF
717    
718      ierr = NF_INQ_VARID (nid, "QANCIEN", nvarid)      ierr = NF90_INQ_VARID(ncid, "QANCIEN", varid)
719      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
720         PRINT*, "phyetat0: Le champ <QANCIEN> est absent"         PRINT *, "phyetat0: Le champ <QANCIEN> est absent"
721         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
722         ancien_ok = .FALSE.         ancien_ok = .FALSE.
723      ELSE      ELSE
724         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  
725      ENDIF      ENDIF
726    
727      ierr = NF_INQ_VARID (nid, "CLWCON", nvarid)      ierr = NF90_INQ_VARID(ncid, "CLWCON", varid)
728      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
729         PRINT*, "phyetat0: Le champ CLWCON est absent"         PRINT *, "phyetat0: Le champ CLWCON est absent"
730         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
731         clwcon = 0.         clwcon = 0.
732      ELSE      ELSE
733         ierr = NF_GET_VAR_REAL(nid, nvarid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
734         IF (ierr.NE.NF_NOERR) THEN         clwcon(:, 2:) = 0.
           PRINT*, "phyetat0: Lecture echouee pour <CLWCON>"  
           stop 1  
        ENDIF  
735      ENDIF      ENDIF
736      xmin = 1.0E+20      xmin = 1.0E+20
737      xmax = -1.0E+20      xmax = -1.0E+20
738      xmin = MINval(clwcon)      xmin = MINval(clwcon)
739      xmax = MAXval(clwcon)      xmax = MAXval(clwcon)
740      PRINT*,'Eau liquide convective (ecart-type) clwcon:', xmin, xmax      PRINT *, 'Eau liquide convective (ecart-type) clwcon:', xmin, xmax
741    
742      ierr = NF_INQ_VARID (nid, "RNEBCON", nvarid)      ierr = NF90_INQ_VARID(ncid, "RNEBCON", varid)
743      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
744         PRINT*, "phyetat0: Le champ RNEBCON est absent"         PRINT *, "phyetat0: Le champ RNEBCON est absent"
745         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
746         rnebcon = 0.         rnebcon = 0.
747      ELSE      ELSE
748         ierr = NF_GET_VAR_REAL(nid, nvarid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
749         IF (ierr.NE.NF_NOERR) THEN         rnebcon(:, 2:) = 0.
           PRINT*, "phyetat0: Lecture echouee pour <RNEBCON>"  
           stop 1  
        ENDIF  
750      ENDIF      ENDIF
751      xmin = 1.0E+20      xmin = 1.0E+20
752      xmax = -1.0E+20      xmax = -1.0E+20
753      xmin = MINval(rnebcon)      xmin = MINval(rnebcon)
754      xmax = MAXval(rnebcon)      xmax = MAXval(rnebcon)
755      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  
756    
757      ! Lecture ratqs      ! Lecture ratqs
758    
759      ierr = NF_INQ_VARID (nid, "RATQS", nvarid)      ierr = NF90_INQ_VARID(ncid, "RATQS", varid)
760      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
761         PRINT*, "phyetat0: Le champ <RATQS> est absent"         PRINT *, "phyetat0: Le champ <RATQS> est absent"
762         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
763         ratqs = 0.         ratqs = 0.
764      ELSE      ELSE
765         ierr = NF_GET_VAR_REAL(nid, nvarid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
766         IF (ierr.NE.NF_NOERR) THEN         ratqs(:, 2:) = 0.
           PRINT*, "phyetat0: Lecture echouee pour <RATQS>"  
           stop 1  
        ENDIF  
767      ENDIF      ENDIF
768      xmin = 1.0E+20      xmin = 1.0E+20
769      xmax = -1.0E+20      xmax = -1.0E+20
770      xmin = MINval(ratqs)      xmin = MINval(ratqs)
771      xmax = MAXval(ratqs)      xmax = MAXval(ratqs)
772      PRINT*,'(ecart-type) ratqs:', xmin, xmax      PRINT *, '(ecart-type) ratqs:', xmin, xmax
773    
774      ! Lecture run_off_lic_0      ! Lecture run_off_lic_0
775    
776      ierr = NF_INQ_VARID (nid, "RUNOFFLIC0", nvarid)      ierr = NF90_INQ_VARID(ncid, "RUNOFFLIC0", varid)
777      IF (ierr.NE.NF_NOERR) THEN      IF (ierr /= NF90_NOERR) THEN
778         PRINT*, "phyetat0: Le champ <RUNOFFLIC0> est absent"         PRINT *, "phyetat0: Le champ <RUNOFFLIC0> est absent"
779         PRINT*, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
780         run_off_lic_0 = 0.         run_off_lic_0 = 0.
781      ELSE      ELSE
782         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  
783      ENDIF      ENDIF
784      xmin = 1.0E+20      xmin = 1.0E+20
785      xmax = -1.0E+20      xmax = -1.0E+20
786      xmin = MINval(run_off_lic_0)      xmin = MINval(run_off_lic_0)
787      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
788      PRINT*,'(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
789    
790        call nf95_inq_varid(ncid, "sig1", varid)
791        call nf95_get_var(ncid, varid, sig1)
792    
793      ! Fermer le fichier:      call nf95_inq_varid(ncid, "w01", varid)
794        call nf95_get_var(ncid, varid, w01)
795    
796      ierr = NF_CLOSE(nid)      call NF95_CLOSE(ncid)
797    
798    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0
799    

Legend:
Removed from v.22  
changed lines
  Added in v.76

  ViewVC Help
Powered by ViewVC 1.1.21