/[lmdze]/trunk/Sources/phylmd/phyetat0.f
ViewVC logotype

Diff of /trunk/Sources/phylmd/phyetat0.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

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

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

  ViewVC Help
Powered by ViewVC 1.1.21