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

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

  ViewVC Help
Powered by ViewVC 1.1.21