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

Diff of /trunk/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 113 by guez, Thu Sep 18 19:56:46 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 46  contains Line 46  contains
46      use q_sat_m, only: q_sat      use q_sat_m, only: q_sat
47      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
48      use regr_pr_o3_m, only: regr_pr_o3      use regr_pr_o3_m, only: regr_pr_o3
     use serre, only: alphax  
49      use startdyn, only: start_init_dyn      use startdyn, only: start_init_dyn
50      USE start_init_orog_m, only: start_init_orog, mask      USE start_init_orog_m, only: start_init_orog, mask
51      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
52      use start_inter_3d_m, only: start_inter_3d      use start_inter_3d_m, only: start_inter_3d
53      use temps, only: itau_phy, annee_ref, day_ref      use temps, only: itau_phy, annee_ref, day_ref
54        use test_disvert_m, only: test_disvert
55    
56      ! Variables local to the procedure:      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
57        ! surface geopotential, in m2 s-2
58    
59        ! Local:
60    
61      REAL latfi(klon), lonfi(klon)      REAL latfi(klon), lonfi(klon)
62      ! (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 71  contains
71      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
72    
73      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
74      REAL tsol(klon), qsol(klon), sn(klon)      REAL sn(klon)
75      REAL tsolsrf(klon, nbsrf), qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
76      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf), evap(klon, nbsrf)
77      REAL alblw(klon, nbsrf)      REAL alblw(klon, nbsrf)
78      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
79      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL radsol(klon), rain_fall(klon), snow_fall(klon)
80      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon), fder(klon)
81      !IM "slab" ocean      !IM "slab" ocean
     REAL tslab(klon)  
82      real seaice(klon) ! kg m-2      real seaice(klon) ! kg m-2
83      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
84      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
85      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
86      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
87      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 132  contains
132    
133      pa = 5e4      pa = 5e4
134      CALL disvert      CALL disvert
135        call test_disvert
136      CALL inigeom      CALL inigeom
137      CALL inifilr      CALL inifilr
138    
# Line 208  contains Line 210  contains
210         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
211      end if      end if
212    
     tsol = pack(tsol_2d, dyn_phy)  
     qsol = pack(qsol_2d, dyn_phy)  
213      sn = 0. ! snow      sn = 0. ! snow
214      radsol = 0.      radsol = 0.
     tslab = 0. ! IM "slab" ocean  
215      seaice = 0.      seaice = 0.
216      rugmer = 0.001      rugmer = 0.001
217      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
# Line 296  contains Line 295  contains
295      ! Calcul interm\'ediaire :      ! Calcul interm\'ediaire :
296      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
297    
     print *, 'ALPHAX = ', alphax  
   
298      forall (l = 1:llm)      forall (l = 1:llm)
299         masse(:, 1, l) = SUM(aire_2d(:iim, 1) * masse(:iim, 1, l)) / apoln         masse(:, 1, l) = SUM(aire_2d(:iim, 1) * masse(:iim, 1, l)) / apoln
300         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
# Line 317  contains Line 314  contains
314      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)
315    
316      ! Initialisations :      ! Initialisations :
     tsolsrf(:, is_ter) = tsol  
     tsolsrf(:, is_lic) = tsol  
     tsolsrf(:, is_oce) = tsol  
     tsolsrf(:, is_sic) = tsol  
317      snsrf(:, is_ter) = sn      snsrf(:, is_ter) = sn
318      snsrf(:, is_lic) = sn      snsrf(:, is_lic) = sn
319      snsrf(:, is_oce) = sn      snsrf(:, is_oce) = sn
# Line 331  contains Line 324  contains
324      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
325      alblw = albe      alblw = albe
326      evap = 0.      evap = 0.
327      qsolsrf(:, is_ter) = 150.      qsolsrf = 150.
328      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)  
329      rain_fall = 0.      rain_fall = 0.
330      snow_fall = 0.      snow_fall = 0.
331      solsw = 165.      solsw = 165.
# Line 343  contains Line 333  contains
333      t_ancien = 273.15      t_ancien = 273.15
334      q_ancien = 0.      q_ancien = 0.
335      agesno = 0.      agesno = 0.
     !IM "slab" ocean  
     tslab = tsolsrf(:, is_oce)  
336      seaice = 0.      seaice = 0.
337    
338      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
# Line 359  contains Line 347  contains
347      sig1 = 0.      sig1 = 0.
348      w01 = 0.      w01 = 0.
349    
350      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &      call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, &
351           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &
352           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &           albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &
353           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &           frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
354           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
355      CALL histclo      CALL histclo
356    
357    END SUBROUTINE etat0    END SUBROUTINE etat0

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

  ViewVC Help
Powered by ViewVC 1.1.21