/[lmdze]/trunk/phylmd/phyetat0.f90
ViewVC logotype

Diff of /trunk/phylmd/phyetat0.f90

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

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

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

  ViewVC Help
Powered by ViewVC 1.1.21