/[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

trunk/dyn3d/etat0.f revision 91 by guez, Wed Mar 26 17:18:58 2014 UTC trunk/Sources/dyn3d/etat0.f revision 155 by guez, Wed Jul 8 17:03:45 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    
20      use caldyn0_m, only: caldyn0      use caldyn0_m, only: caldyn0
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: aire_2d, apoln, apols, cu_2d, cv_2d, inigeom
          cu_2d, cv_2d, inigeom  
     use conf_gcm_m, only: dayref, anneeref  
23      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
24      use dimphy, only: zmasq      use dimphy, only: zmasq
25      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
26      use disvert_m, only: ap, bp, preff, pa, disvert      use disvert_m, only: ap, bp, preff, pa, disvert
27        use dynetat0_m, only: day_ref, annee_ref, xprimp025, xprimm025, rlatu1, &
28             rlatu2, rlatu, rlatv, yprimu1, yprimu2, rlonu, rlonv, xprimu, xprimv
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
32        use fxhyp_m, only: fxhyp
33        use fyhyp_m, only: fyhyp
34      use geopot_m, only: geopot      use geopot_m, only: geopot
35      use grid_atob, only: grille_m      use grid_atob, only: grille_m
36      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
     use histclo_m, only: histclo  
37      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra
38      use iniadvtrac_m, only: iniadvtrac      use iniadvtrac_m, only: iniadvtrac
39      use inifilr_m, only: inifilr      use inifilr_m, only: inifilr
# Line 42  contains Line 43  contains
43           nf95_inq_varid, nf95_open           nf95_inq_varid, nf95_open
44      use nr_util, only: pi, assert      use nr_util, only: pi, assert
45      use paramet_m, only: ip1jm, ip1jmp1      use paramet_m, only: ip1jm, ip1jmp1
46        use phyetat0_m, only: rlat, rlon
47      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
     use pressure_var, only: pls, p3d  
48      use q_sat_m, only: q_sat      use q_sat_m, only: q_sat
49      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
50      use regr_pr_o3_m, only: regr_pr_o3      use regr_pr_o3_m, only: regr_pr_o3
     use serre, only: alphax  
51      use startdyn, only: start_init_dyn      use startdyn, only: start_init_dyn
52      USE start_init_orog_m, only: start_init_orog, mask      USE start_init_orog_m, only: start_init_orog, mask
53      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
54      use start_inter_3d_m, only: start_inter_3d      use start_inter_3d_m, only: start_inter_3d
55      use temps, only: itau_phy, annee_ref, day_ref      use temps, only: itau_phy
56        use test_disvert_m, only: test_disvert
57        use unit_nml_m, only: unit_nml
58    
59      ! Variables local to the procedure:      REAL, intent(out):: phis(:, :) ! (iim + 1, jjm + 1)
60        ! surface geopotential, in m2 s-2
61    
62      REAL latfi(klon), lonfi(klon)      ! Local:
     ! (latitude and longitude of a point of the scalar grid identified  
     ! by a simple index, in degrees)  
63    
64      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, teta
65      REAL vcov(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
# Line 69  contains Line 70  contains
70      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
71    
72      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
73      REAL tsol(klon), qsol(klon), sn(klon)      REAL sn(klon)
74      REAL tsolsrf(klon, nbsrf), qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)      REAL qsolsrf(klon, nbsrf), snsrf(klon, nbsrf)
75      REAL albe(klon, nbsrf), evap(klon, nbsrf)      REAL albe(klon, nbsrf), evap(klon, nbsrf)
76      REAL alblw(klon, nbsrf)      REAL alblw(klon, nbsrf)
77      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
78      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL radsol(klon), rain_fall(klon), snow_fall(klon)
79      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon), fder(klon)
80      !IM "slab" ocean      !IM "slab" ocean
     REAL tslab(klon)  
81      real seaice(klon) ! kg m-2      real seaice(klon) ! kg m-2
82      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
83      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
84      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
85      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
86      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 112  contains
112      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
113      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
114    
115        real pls(iim + 1, jjm + 1, llm)
116        ! (pressure at mid-layer of LMDZ grid, in Pa)
117        ! "pls(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
118        ! for layer "l")
119    
120        REAL p3d(iim + 1, jjm + 1, llm+1) ! pressure at layer interfaces, in Pa
121        ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
122        ! for interface "l")
123    
124        namelist /etat0_nml/ day_ref, annee_ref
125    
126      !---------------------------------      !---------------------------------
127    
128      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
129    
130        print *, "Enter namelist 'etat0_nml'."
131        read(unit=*, nml=etat0_nml)
132        write(unit_nml, nml=etat0_nml)
133    
134      CALL iniconst      CALL iniconst
135    
136      ! Construct a grid:      ! Construct a grid:
137    
138      pa = 5e4      pa = 5e4
139      CALL disvert      CALL disvert
140        call test_disvert
141    
142        CALL fyhyp(rlatu, rlatv, rlatu2, yprimu2, rlatu1, yprimu1)
143        CALL fxhyp(xprimm025, rlonv, xprimv, rlonu, xprimu, xprimp025)
144    
145        rlatu(1) = pi / 2.
146        rlatu(jjm + 1) = -rlatu(1)
147    
148      CALL inigeom      CALL inigeom
149      CALL inifilr      CALL inifilr
150    
151      latfi(1) = 90.      rlat(1) = 90.
152      latfi(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.) * 180. / pi      rlat(2:klon-1) = pack(spread(rlatu(2:jjm), 1, iim), .true.) * 180. / pi
153      ! (with conversion to degrees)      ! (with conversion to degrees)
154      latfi(klon) = - 90.      rlat(klon) = - 90.
155    
156      lonfi(1) = 0.      rlon(1) = 0.
157      lonfi(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.) * 180. / pi      rlon(2:klon-1) = pack(spread(rlonv(:iim), 2, jjm - 1), .true.) * 180. / pi
158      ! (with conversion to degrees)      ! (with conversion to degrees)
159      lonfi(klon) = 0.      rlon(klon) = 0.
160    
161      call start_init_orog(phis, zmea_2d, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &      call start_init_orog(phis, zmea_2d, zstd_2d, zsig_2d, zgam_2d, zthe_2d, &
162           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
# Line 195  contains Line 217  contains
217      if (nqmx >= 5) then      if (nqmx >= 5) then
218         ! Ozone:         ! Ozone:
219         call regr_lat_time_coefoz         call regr_lat_time_coefoz
220         call regr_pr_o3(q(:, :, :, 5))         call regr_pr_o3(p3d, q(:, :, :, 5))
221         ! Convert from mole fraction to mass fraction:         ! Convert from mole fraction to mass fraction:
222         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
223      end if      end if
224    
     tsol = pack(tsol_2d, dyn_phy)  
     qsol = pack(qsol_2d, dyn_phy)  
225      sn = 0. ! snow      sn = 0. ! snow
226      radsol = 0.      radsol = 0.
     tslab = 0. ! IM "slab" ocean  
227      seaice = 0.      seaice = 0.
228      rugmer = 0.001      rugmer = 0.001
229      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
# Line 288  contains Line 307  contains
307      ! Calcul interm\'ediaire :      ! Calcul interm\'ediaire :
308      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
309    
     print *, 'ALPHAX = ', alphax  
   
310      forall (l = 1:llm)      forall (l = 1:llm)
311         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
312         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
# Line 299  contains Line 316  contains
316      ! Initialisation pour traceurs:      ! Initialisation pour traceurs:
317      call iniadvtrac      call iniadvtrac
318      itau_phy = 0      itau_phy = 0
     day_ref = dayref  
     annee_ref = anneeref  
319    
320      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
321      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &
322           pbarv)           pbarv)
323      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem0("start.nc", day_ref, phis)
324      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)
325    
326      ! Initialisations :      ! Initialisations :
     tsolsrf(:, is_ter) = tsol  
     tsolsrf(:, is_lic) = tsol  
     tsolsrf(:, is_oce) = tsol  
     tsolsrf(:, is_sic) = tsol  
327      snsrf(:, is_ter) = sn      snsrf(:, is_ter) = sn
328      snsrf(:, is_lic) = sn      snsrf(:, is_lic) = sn
329      snsrf(:, is_oce) = sn      snsrf(:, is_oce) = sn
# Line 323  contains Line 334  contains
334      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
335      alblw = albe      alblw = albe
336      evap = 0.      evap = 0.
337      qsolsrf(:, is_ter) = 150.      qsolsrf = 150.
338      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)  
339      rain_fall = 0.      rain_fall = 0.
340      snow_fall = 0.      snow_fall = 0.
341      solsw = 165.      solsw = 165.
# Line 335  contains Line 343  contains
343      t_ancien = 273.15      t_ancien = 273.15
344      q_ancien = 0.      q_ancien = 0.
345      agesno = 0.      agesno = 0.
     !IM "slab" ocean  
     tslab = tsolsrf(:, is_oce)  
346      seaice = 0.      seaice = 0.
347    
348      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
# Line 351  contains Line 357  contains
357      sig1 = 0.      sig1 = 0.
358      w01 = 0.      w01 = 0.
359    
360      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &      call phyredem("startphy.nc", pctsrf, tsoil(:, 1, :), tsoil, &
361           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &
362           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &           albe, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &
363           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
364           t_ancien, q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)           q_ancien, rnebcon, ratqs, clwcon, run_off_lic_0, sig1, w01)
     CALL histclo  
365    
366    END SUBROUTINE etat0    END SUBROUTINE etat0
367    

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

  ViewVC Help
Powered by ViewVC 1.1.21