/[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 62 by guez, Thu Jul 26 14:37:37 2012 UTC trunk/phylmd/phyetat0.f revision 101 by guez, Mon Jul 7 17:45:21 2014 UTC
# Line 10  module phyetat0_m Line 10  module phyetat0_m
10    
11  contains  contains
12    
13    SUBROUTINE phyetat0(fichnom, pctsrf, tsol, tsoil, ocean, tslab, seaice, &    SUBROUTINE phyetat0(pctsrf, tsol, tsoil, tslab, seaice, qsurf, qsol, &
14         qsurf, qsol, snow, albe, alblw, evap, rain_fall, snow_fall, solsw, &         snow, albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, &
15         sollw, fder, radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, &         radsol, frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &
16         zpic, zval, t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, &         t_ancien, q_ancien, ancien_ok, rnebcon, ratqs, clwcon, run_off_lic_0, &
17         run_off_lic_0)         sig1, w01)
18    
19      ! From phylmd/phyetat0.F, version 1.4 2005/06/03 10:03:07      ! From phylmd/phyetat0.F, version 1.4 2005/06/03 10:03:07
20      ! Author: Z.X. Li (LMD/CNRS)      ! Author: Z.X. Li (LMD/CNRS)
21      ! Date: 1993/08/18      ! Date: 1993/08/18
22      ! Objet : Lecture de l'état initial pour la physique      ! Objet : lecture de l'état initial pour la physique
23    
24      USE indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf      use dimphy, only: zmasq, klev
25      USE dimsoil, ONLY : nsoilmx      USE dimsoil, ONLY : nsoilmx
26      USE temps, ONLY : itau_phy      USE indicesol, ONLY : epsfra, is_lic, is_oce, is_sic, is_ter, nbsrf
27      use netcdf, only: nf90_get_att, nf90_global, nf90_inq_varid, NF90_NOERR, &      use netcdf, only: nf90_global, nf90_inq_varid, NF90_NOERR, &
28           NF90_NOWRITE           NF90_NOWRITE
29      use netcdf95, only: handle_err, nf95_get_var, nf95_close, NF95_OPEN, &      use netcdf95, only: nf95_close, nf95_get_att, nf95_get_var, &
30           nf95_inq_varid           nf95_inq_varid, nf95_inquire_variable, NF95_OPEN
31      use dimphy, only: zmasq, klev      USE temps, ONLY : itau_phy
32    
33      CHARACTER(len=*), intent(in):: fichnom      REAL pctsrf(klon, nbsrf)
34      REAL tsol(klon, nbsrf)      REAL tsol(klon, nbsrf)
35      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
36      REAL tslab(klon), seaice(klon)      REAL tslab(klon), seaice(klon)
37      REAL qsurf(klon, nbsrf)      REAL qsurf(klon, nbsrf)
38      REAL qsol(klon)      REAL, intent(out):: qsol(:) ! (klon)
39      REAL snow(klon, nbsrf)      REAL snow(klon, nbsrf)
40      REAL albe(klon, nbsrf)      REAL albe(klon, nbsrf)
41      REAL alblw(klon, nbsrf)      REAL alblw(klon, nbsrf)
42      REAL evap(klon, nbsrf)      REAL evap(klon, nbsrf)
     REAL radsol(klon)  
43      REAL, intent(out):: rain_fall(klon)      REAL, intent(out):: rain_fall(klon)
44      REAL snow_fall(klon)      REAL snow_fall(klon)
     REAL sollw(klon)  
45      real solsw(klon)      real solsw(klon)
46        REAL, intent(out):: sollw(klon)
47      real fder(klon)      real fder(klon)
48        REAL radsol(klon)
49      REAL frugs(klon, nbsrf)      REAL frugs(klon, nbsrf)
50      REAL agesno(klon, nbsrf)      REAL agesno(klon, nbsrf)
51      REAL zmea(klon)      REAL zmea(klon)
# Line 55  contains Line 55  contains
55      REAL zthe(klon)      REAL zthe(klon)
56      REAL zpic(klon)      REAL zpic(klon)
57      REAL zval(klon)      REAL zval(klon)
     REAL pctsrf(klon, nbsrf)  
     REAL fractint(klon)  
     REAL run_off_lic_0(klon)  
   
58      REAL t_ancien(klon, klev), q_ancien(klon, klev)      REAL t_ancien(klon, klev), q_ancien(klon, klev)
     real rnebcon(klon, klev), clwcon(klon, klev), ratqs(klon, klev)  
59      LOGICAL, intent(out):: ancien_ok      LOGICAL, intent(out):: ancien_ok
60        real rnebcon(klon, klev), ratqs(klon, klev), clwcon(klon, klev)
61        REAL run_off_lic_0(klon)
62        real, intent(out):: sig1(klon, klev) ! section adiabatic updraft
63    
64      CHARACTER(len=*), intent(in):: ocean      real, intent(out):: w01(klon, klev)
65        ! vertical velocity within adiabatic updraft
66    
67        ! Local:
68        REAL fractint(klon)
69      REAL xmin, xmax      REAL xmin, xmax
70        INTEGER ncid, varid, ndims
     INTEGER ncid, varid  
71      INTEGER ierr, i, nsrf, isoil      INTEGER ierr, i, nsrf, isoil
72      CHARACTER*7 str7      CHARACTER(len=7) str7
73      CHARACTER*2 str2      CHARACTER(len=2) str2
74    
75      !---------------------------------------------------------------      !---------------------------------------------------------------
76    
77      print *, "Call sequence information: phyetat0"      print *, "Call sequence information: phyetat0"
78    
79      ! Ouvrir le fichier contenant l'etat initial:      ! Fichier contenant l'état initial :
80      print *, 'fichnom = ', fichnom      call NF95_OPEN("startphy.nc", NF90_NOWRITE, ncid)
     call NF95_OPEN(fichnom, NF90_NOWRITE, ncid)  
81    
82      ierr = nf90_get_att(ncid, nf90_global, "itau_phy", itau_phy)      call nf95_get_att(ncid, nf90_global, "itau_phy", itau_phy)
     call handle_err("phyetat0 itau_phy", ierr, ncid, nf90_global)  
83    
84      ! Lecture des latitudes (coordonnees):      ! Lecture des latitudes (coordonnees):
85    
# Line 95  contains Line 93  contains
93    
94      ! Lecture du masque terre mer      ! Lecture du masque terre mer
95    
96      ierr = NF90_INQ_VARID(ncid, "masque", varid)      call NF95_INQ_VARID(ncid, "masque", varid)
97      IF (ierr == NF90_NOERR) THEN      call nf95_get_var(ncid, varid, zmasq)
98         call nf95_get_var(ncid, varid, zmasq)  
     else  
        PRINT *, 'phyetat0: Le champ <masque> est absent'  
        PRINT *, 'fichier startphy non compatible avec phyetat0'  
     ENDIF  
99      ! Lecture des fractions pour chaque sous-surface      ! Lecture des fractions pour chaque sous-surface
100    
101      ! initialisation des sous-surfaces      ! initialisation des sous-surfaces
# Line 164  contains Line 158  contains
158      END DO      END DO
159    
160      ! Lecture des temperatures du sol:      ! Lecture des temperatures du sol:
161        call NF95_INQ_VARID(ncid, "TS", varid)
162      ierr = NF90_INQ_VARID(ncid, "TS", varid)      call nf95_inquire_variable(ncid, varid, ndims = ndims)
163      IF (ierr /= NF90_NOERR) THEN      if (ndims == 2) then
164         PRINT *, 'phyetat0 : Le champ <TS> est absent'         call NF95_GET_VAR(ncid, varid, tsol)
165         PRINT *, ' Mais je vais essayer de lire TS**'      else
166         DO nsrf = 1, nbsrf         print *, "Found only one surface type for soil temperature."
           IF (nsrf > 99) THEN  
              PRINT *, "Trop de sous-mailles"  
              stop 1  
           ENDIF  
           WRITE(str2, '(i2.2)') nsrf  
           call NF95_INQ_VARID(ncid, "TS"//str2, varid)  
           call NF95_GET_VAR(ncid, varid, tsol(:, nsrf))  
           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**'  
167         call nf95_get_var(ncid, varid, tsol(:, 1))         call nf95_get_var(ncid, varid, tsol(:, 1))
168         xmin = 1.0E+20         tsol(:, 2:nbsrf) = spread(tsol(:, 1), dim = 2, ncopies = nbsrf - 1)
169         xmax = -1.0E+20      end if      
        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  
170    
171      ! Lecture des temperatures du sol profond:     ! Lecture des temperatures du sol profond:
172    
173      DO nsrf = 1, nbsrf      DO nsrf = 1, nbsrf
174         DO isoil=1, nsoilmx         DO isoil=1, nsoilmx
# Line 226  contains Line 191  contains
191      ENDDO      ENDDO
192    
193      !IM "slab" ocean      !IM "slab" ocean
   
194      ! Lecture de tslab (pour slab ocean seulement):      ! Lecture de tslab (pour slab ocean seulement):
195        tslab = 0.
196      IF (ocean .eq. 'slab ') then      seaice = 0.
        call NF95_INQ_VARID(ncid, "TSLAB", varid)  
        call nf95_get_var(ncid, varid, 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):  
   
        call NF95_INQ_VARID(ncid, "SEAICE", varid)  
        call nf95_get_var(ncid, varid, 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  
197    
198      ! Lecture de l'humidite de l'air juste au dessus du sol:      ! Lecture de l'humidite de l'air juste au dessus du sol:
199    
# Line 306  contains Line 245  contains
245         PRINT *, ' Valeur par defaut nulle'         PRINT *, ' Valeur par defaut nulle'
246         qsol = 0.         qsol = 0.
247      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  
248    
249      ! Lecture de neige au sol:      ! Lecture de neige au sol:
250    
# Line 468  contains Line 400  contains
400    
401      call NF95_INQ_VARID(ncid, "rain_f", varid)      call NF95_INQ_VARID(ncid, "rain_f", varid)
402      call NF95_GET_VAR(ncid, varid, rain_fall)      call NF95_GET_VAR(ncid, varid, rain_fall)
     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  
403    
404      ! Lecture precipitation solide:      ! Lecture precipitation solide:
405    
# Line 516  contains Line 441  contains
441      ELSE      ELSE
442         call nf95_get_var(ncid, varid, sollw)         call nf95_get_var(ncid, varid, sollw)
443      ENDIF      ENDIF
444      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  
445    
446      ! Lecture derive des flux:      ! Lecture derive des flux:
447    
# Line 734  contains Line 653  contains
653         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
654         clwcon = 0.         clwcon = 0.
655      ELSE      ELSE
656         call nf95_get_var(ncid, varid, clwcon)         call nf95_get_var(ncid, varid, clwcon(:, 1))
657           clwcon(:, 2:) = 0.
658      ENDIF      ENDIF
659      xmin = 1.0E+20      xmin = 1.0E+20
660      xmax = -1.0E+20      xmax = -1.0E+20
# Line 748  contains Line 668  contains
668         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
669         rnebcon = 0.         rnebcon = 0.
670      ELSE      ELSE
671         call nf95_get_var(ncid, varid, rnebcon)         call nf95_get_var(ncid, varid, rnebcon(:, 1))
672           rnebcon(:, 2:) = 0.
673      ENDIF      ENDIF
674      xmin = 1.0E+20      xmin = 1.0E+20
675      xmax = -1.0E+20      xmax = -1.0E+20
# Line 764  contains Line 685  contains
685         PRINT *, "Depart legerement fausse. Mais je continue"         PRINT *, "Depart legerement fausse. Mais je continue"
686         ratqs = 0.         ratqs = 0.
687      ELSE      ELSE
688         call nf95_get_var(ncid, varid, ratqs)         call nf95_get_var(ncid, varid, ratqs(:, 1))
689           ratqs(:, 2:) = 0.
690      ENDIF      ENDIF
691      xmin = 1.0E+20      xmin = 1.0E+20
692      xmax = -1.0E+20      xmax = -1.0E+20
# Line 788  contains Line 710  contains
710      xmax = MAXval(run_off_lic_0)      xmax = MAXval(run_off_lic_0)
711      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax      PRINT *, '(ecart-type) run_off_lic_0:', xmin, xmax
712    
713        call nf95_inq_varid(ncid, "sig1", varid)
714        call nf95_get_var(ncid, varid, sig1)
715    
716        call nf95_inq_varid(ncid, "w01", varid)
717        call nf95_get_var(ncid, varid, w01)
718    
719      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
720    
721    END SUBROUTINE phyetat0    END SUBROUTINE phyetat0

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

  ViewVC Help
Powered by ViewVC 1.1.21