/[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 91 by guez, Wed Mar 26 17:18:58 2014 UTC revision 129 by guez, Fri Feb 13 18:22:38 2015 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 21  contains Line 21  contains
21      use comconst, only: cpp, kappa, iniconst      use comconst, only: cpp, kappa, iniconst
22      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &
23           cu_2d, cv_2d, inigeom           cu_2d, cv_2d, inigeom
     use conf_gcm_m, only: dayref, anneeref  
24      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
25      use dimphy, only: zmasq      use dimphy, only: zmasq
26      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
27      use disvert_m, only: ap, bp, preff, pa, disvert      use disvert_m, only: ap, bp, preff, pa, disvert
28        use dynetat0_m, only: day_ref, annee_ref
29      use dynredem0_m, only: dynredem0      use dynredem0_m, only: dynredem0
30      use dynredem1_m, only: dynredem1      use dynredem1_m, only: dynredem1
31      use exner_hyb_m, only: exner_hyb      use exner_hyb_m, only: exner_hyb
# Line 43  contains Line 43  contains
43      use nr_util, only: pi, assert      use nr_util, only: pi, assert
44      use paramet_m, only: ip1jm, ip1jmp1      use paramet_m, only: ip1jm, ip1jmp1
45      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
     use pressure_var, only: pls, p3d  
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
54        use test_disvert_m, only: test_disvert
55        use unit_nml_m, only: unit_nml
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 69  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 113  contains Line 114  contains
114      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
115      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
116    
117        real pls(iim + 1, jjm + 1, llm)
118        ! (pressure at mid-layer of LMDZ grid, in Pa)
119        ! "pls(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
120        ! for layer "l")
121    
122        REAL p3d(iim + 1, jjm + 1, llm+1) ! pressure at layer interfaces, in Pa
123        ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
124        ! for interface "l")
125    
126        namelist /etat0_nml/ day_ref, annee_ref
127    
128      !---------------------------------      !---------------------------------
129    
130      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
131    
132        print *, "Enter namelist 'etat0_nml'."
133        read(unit=*, nml=etat0_nml)
134        write(unit_nml, nml=etat0_nml)
135    
136      CALL iniconst      CALL iniconst
137    
138      ! Construct a grid:      ! Construct a grid:
139    
140      pa = 5e4      pa = 5e4
141      CALL disvert      CALL disvert
142        call test_disvert
143      CALL inigeom      CALL inigeom
144      CALL inifilr      CALL inifilr
145    
# Line 195  contains Line 212  contains
212      if (nqmx >= 5) then      if (nqmx >= 5) then
213         ! Ozone:         ! Ozone:
214         call regr_lat_time_coefoz         call regr_lat_time_coefoz
215         call regr_pr_o3(q(:, :, :, 5))         call regr_pr_o3(p3d, q(:, :, :, 5))
216         ! Convert from mole fraction to mass fraction:         ! Convert from mole fraction to mass fraction:
217         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
218      end if      end if
219    
     tsol = pack(tsol_2d, dyn_phy)  
     qsol = pack(qsol_2d, dyn_phy)  
220      sn = 0. ! snow      sn = 0. ! snow
221      radsol = 0.      radsol = 0.
     tslab = 0. ! IM "slab" ocean  
222      seaice = 0.      seaice = 0.
223      rugmer = 0.001      rugmer = 0.001
224      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
# Line 288  contains Line 302  contains
302      ! Calcul interm\'ediaire :      ! Calcul interm\'ediaire :
303      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
304    
     print *, 'ALPHAX = ', alphax  
   
305      forall (l = 1:llm)      forall (l = 1:llm)
306         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
307         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
# Line 299  contains Line 311  contains
311      ! Initialisation pour traceurs:      ! Initialisation pour traceurs:
312      call iniadvtrac      call iniadvtrac
313      itau_phy = 0      itau_phy = 0
     day_ref = dayref  
     annee_ref = anneeref  
314    
315      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
316      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &
317           pbarv)           pbarv)
318      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem0("start.nc", day_ref, phis)
319      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)
320    
321      ! Initialisations :      ! Initialisations :
     tsolsrf(:, is_ter) = tsol  
     tsolsrf(:, is_lic) = tsol  
     tsolsrf(:, is_oce) = tsol  
     tsolsrf(:, is_sic) = tsol  
322      snsrf(:, is_ter) = sn      snsrf(:, is_ter) = sn
323      snsrf(:, is_lic) = sn      snsrf(:, is_lic) = sn
324      snsrf(:, is_oce) = sn      snsrf(:, is_oce) = sn
# Line 323  contains Line 329  contains
329      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
330      alblw = albe      alblw = albe
331      evap = 0.      evap = 0.
332      qsolsrf(:, is_ter) = 150.      qsolsrf = 150.
333      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)  
334      rain_fall = 0.      rain_fall = 0.
335      snow_fall = 0.      snow_fall = 0.
336      solsw = 165.      solsw = 165.
# Line 335  contains Line 338  contains
338      t_ancien = 273.15      t_ancien = 273.15
339      q_ancien = 0.      q_ancien = 0.
340      agesno = 0.      agesno = 0.
     !IM "slab" ocean  
     tslab = tsolsrf(:, is_oce)  
341      seaice = 0.      seaice = 0.
342    
343      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
# Line 351  contains Line 352  contains
352      sig1 = 0.      sig1 = 0.
353      w01 = 0.      w01 = 0.
354    
355      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &      call phyredem("startphy.nc", latfi, lonfi, pctsrf, tsoil(:, 1, :), tsoil, &
356           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &
357           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &           albe, alblw, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, &
358           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &           frugs, agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
359           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
360      CALL histclo      CALL histclo
361    
362    END SUBROUTINE etat0    END SUBROUTINE etat0

Legend:
Removed from v.91  
changed lines
  Added in v.129

  ViewVC Help
Powered by ViewVC 1.1.21