/[lmdze]/trunk/Sources/dyn3d/etat0.f
ViewVC logotype

Diff of /trunk/Sources/dyn3d/etat0.f

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

revision 97 by guez, Fri Apr 25 14:58:31 2014 UTC revision 107 by guez, Thu Sep 11 15:09:15 2014 UTC
# Line 13  module etat0_mod Line 13  module etat0_mod
13    
14  contains  contains
15    
16    SUBROUTINE etat0    SUBROUTINE etat0(phis)
17    
18      ! From "etat0_netcdf.F", version 1.3, 2005/05/25 13:10:09      ! From "etat0_netcdf.F", version 1.3, 2005/05/25 13:10:09
19    
# Line 52  contains Line 52  contains
52      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
53      use start_inter_3d_m, only: start_inter_3d      use start_inter_3d_m, only: start_inter_3d
54      use temps, only: itau_phy, annee_ref, day_ref      use temps, only: itau_phy, annee_ref, day_ref
55        use test_disvert_m, only: test_disvert
56    
57      ! Variables local to the procedure:      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
58        ! surface geopotential, in m2 s-2
59    
60        ! Local:
61    
62      REAL latfi(klon), lonfi(klon)      REAL latfi(klon), lonfi(klon)
63      ! (latitude and longitude of a point of the scalar grid identified      ! (latitude and longitude of a point of the scalar grid identified
# Line 68  contains Line 72  contains
72      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
73    
74      real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor      real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor
75      REAL tsol(klon), qsol(klon), sn(klon)      REAL sn(klon)
76      REAL tsolsrf(klon, nbsrf), qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
77      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf), evap(klon, nbsrf)
78      REAL alblw(klon, nbsrf)      REAL alblw(klon, nbsrf)
79      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
80      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL radsol(klon), rain_fall(klon), snow_fall(klon)
81      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon), fder(klon)
82      !IM "slab" ocean      !IM "slab" ocean
     REAL tslab(klon)  
83      real seaice(klon) ! kg m-2      real seaice(klon) ! kg m-2
84      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
85      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
86      real, dimension(iim + 1, jjm + 1):: zmea_2d, zstd_2d, zsig_2d, zgam_2d      real, dimension(iim + 1, jjm + 1):: zmea_2d, zstd_2d, zsig_2d, zgam_2d
87      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
88      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps
# Line 131  contains Line 133  contains
133    
134      pa = 5e4      pa = 5e4
135      CALL disvert      CALL disvert
136        call test_disvert
137      CALL inigeom      CALL inigeom
138      CALL inifilr      CALL inifilr
139    
# Line 208  contains Line 211  contains
211         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
212      end if      end if
213    
     tsol = pack(tsol_2d, dyn_phy)  
     qsol = pack(qsol_2d, dyn_phy)  
214      sn = 0. ! snow      sn = 0. ! snow
215      radsol = 0.      radsol = 0.
     tslab = 0. ! IM "slab" ocean  
216      seaice = 0.      seaice = 0.
217      rugmer = 0.001      rugmer = 0.001
218      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
# Line 317  contains Line 317  contains
317      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)
318    
319      ! Initialisations :      ! Initialisations :
     tsolsrf(:, is_ter) = tsol  
     tsolsrf(:, is_lic) = tsol  
     tsolsrf(:, is_oce) = tsol  
     tsolsrf(:, is_sic) = tsol  
320      snsrf(:, is_ter) = sn      snsrf(:, is_ter) = sn
321      snsrf(:, is_lic) = sn      snsrf(:, is_lic) = sn
322      snsrf(:, is_oce) = sn      snsrf(:, is_oce) = sn
# Line 331  contains Line 327  contains
327      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
328      alblw = albe      alblw = albe
329      evap = 0.      evap = 0.
330      qsolsrf(:, is_ter) = 150.      qsolsrf = 150.
331      qsolsrf(:, is_lic) = 150.      tsoil = spread(spread(pack(tsol_2d, dyn_phy), 2, nsoilmx), 3, nbsrf)
     qsolsrf(:, is_oce) = 150.  
     qsolsrf(:, is_sic) = 150.  
     tsoil = spread(spread(tsol, 2, nsoilmx), 3, nbsrf)  
332      rain_fall = 0.      rain_fall = 0.
333      snow_fall = 0.      snow_fall = 0.
334      solsw = 165.      solsw = 165.
# Line 343  contains Line 336  contains
336      t_ancien = 273.15      t_ancien = 273.15
337      q_ancien = 0.      q_ancien = 0.
338      agesno = 0.      agesno = 0.
     !IM "slab" ocean  
     tslab = tsolsrf(:, is_oce)  
339      seaice = 0.      seaice = 0.
340    
341      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
# Line 359  contains Line 350  contains
350      sig1 = 0.      sig1 = 0.
351      w01 = 0.      w01 = 0.
352    
353      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &      call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, &
354           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &
355           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &           albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &
356           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &           frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
357           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
358      CALL histclo      CALL histclo
359    
360    END SUBROUTINE etat0    END SUBROUTINE etat0

Legend:
Removed from v.97  
changed lines
  Added in v.107

  ViewVC Help
Powered by ViewVC 1.1.21