/[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

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

Legend:
Removed from v.12  
changed lines
  Added in v.62

  ViewVC Help
Powered by ViewVC 1.1.21