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

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

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

revision 134 by guez, Wed Apr 29 15:47:56 2015 UTC revision 155 by guez, Wed Jul 8 17:03:45 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(pctsrf, tsol, tsoil, tslab, seaice, qsurf, qsol, &    SUBROUTINE phyetat0(pctsrf, tsol, tsoil, tslab, seaice, qsurf, qsol, &
16         snow, albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, &         snow, albe, evap, rain_fall, snow_fall, solsw, sollw, fder, &
17         radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &         radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
18         t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, &         t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, &
19         sig1, w01)         sig1, w01)
# Line 38  contains Line 40  contains
40      REAL, intent(out):: 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)
     REAL alblw(klon, nbsrf)  
43      REAL evap(klon, nbsrf)      REAL evap(klon, nbsrf)
44      REAL, intent(out):: rain_fall(klon)      REAL, intent(out):: rain_fall(klon)
45      REAL snow_fall(klon)      REAL snow_fall(klon)
# Line 68  contains Line 69  contains
69      REAL fractint(klon)      REAL fractint(klon)
70      REAL xmin, xmax      REAL xmin, xmax
71      INTEGER ncid, varid, ndims      INTEGER ncid, varid, ndims
72      INTEGER ierr, i, nsrf, isoil      INTEGER ierr, i, nsrf
     CHARACTER(len=7) str7  
73      CHARACTER(len=2) str2      CHARACTER(len=2) str2
74    
75      !---------------------------------------------------------------      !---------------------------------------------------------------
# Line 170  contains Line 170  contains
170    
171     ! Lecture des temperatures du sol profond:     ! Lecture des temperatures du sol profond:
172    
173      DO nsrf = 1, nbsrf      call NF95_INQ_VARID(ncid, 'Tsoil', varid)
174         DO isoil=1, nsoilmx      call NF95_GET_VAR(ncid, varid, tsoil)
           IF (isoil > 99 .AND. nsrf > 99) THEN  
              PRINT *, "Trop de couches ou sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str7, '(i2.2, "srf", i2.2)') isoil, nsrf  
           ierr = NF90_INQ_VARID(ncid, 'Tsoil'//str7, varid)  
           IF (ierr /= NF90_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  
              call NF95_GET_VAR(ncid, varid, tsoil(:, isoil, nsrf))  
           ENDIF  
        ENDDO  
     ENDDO  
175    
176      !IM "slab" ocean      !IM "slab" ocean
177      ! Lecture de tslab (pour slab ocean seulement):      ! Lecture de tslab (pour slab ocean seulement):
# Line 325  contains Line 308  contains
308            ENDDO            ENDDO
309         ENDDO         ENDDO
310      ENDIF      ENDIF
   
     ! Lecture de albedo au sol LW:  
   
     ierr = NF90_INQ_VARID(ncid, "ALBLW", varid)  
     IF (ierr /= NF90_NOERR) THEN  
        PRINT *, 'phyetat0: Le champ <ALBLW> est absent'  
        ! PRINT *, ' Mais je vais essayer de lire ALBLW**'  
        PRINT *, ' Mais je vais prendre ALBE**'  
        DO nsrf = 1, nbsrf  
           DO i = 1, klon  
              alblw(i, nsrf) = albe(i, nsrf)  
           ENDDO  
        ENDDO  
     ELSE  
        PRINT *, 'phyetat0: Le champ <ALBLW> est present'  
        PRINT *, ' J ignore donc les autres ALBLW**'  
        call nf95_get_var(ncid, varid, alblw(:, 1))  
        xmin = 1.0E+20  
        xmax = -1.0E+20  
        DO i = 1, klon  
           xmin = MIN(alblw(i, 1), xmin)  
           xmax = MAX(alblw(i, 1), xmax)  
        ENDDO  
        PRINT *, 'Neige du sol <ALBLW>', xmin, xmax  
        DO nsrf = 2, nbsrf  
           DO i = 1, klon  
              alblw(i, nsrf) = alblw(i, 1)  
           ENDDO  
        ENDDO  
     ENDIF  
311    
312      ! Lecture de evaporation:      ! Lecture de evaporation:
313    

Legend:
Removed from v.134  
changed lines
  Added in v.155

  ViewVC Help
Powered by ViewVC 1.1.21