/[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 90 by guez, Wed Mar 12 21:16:36 2014 UTC trunk/Sources/dyn3d/etat0.f revision 156 by guez, Thu Jul 16 17:39:10 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)
     REAL alblw(klon, nbsrf)  
76      REAL tsoil(klon, nsoilmx, nbsrf)      REAL tsoil(klon, nsoilmx, nbsrf)
77      REAL radsol(klon), rain_fall(klon), snow_fall(klon)      REAL radsol(klon), rain_fall(klon), snow_fall(klon)
78      REAL solsw(klon), sollw(klon), fder(klon)      REAL solsw(klon), sollw(klon), fder(klon)
79      !IM "slab" ocean      !IM "slab" ocean
     REAL tslab(klon)  
80      real seaice(klon) ! kg m-2      real seaice(klon) ! kg m-2
81      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)      REAL frugs(klon, nbsrf), agesno(klon, nbsrf)
82      REAL rugmer(klon)      REAL rugmer(klon)
     REAL phis(iim + 1, jjm + 1) ! surface geopotential, in m2 s-2  
83      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
84      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d      real, dimension(iim + 1, jjm + 1):: zthe_2d, zpic_2d, zval_2d
85      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps      real, dimension(iim + 1, jjm + 1):: tsol_2d, qsol_2d, ps
# Line 108  contains Line 106  contains
106      REAL masse(iim + 1, jjm + 1, llm)      REAL masse(iim + 1, jjm + 1, llm)
107      REAL phi(iim + 1, jjm + 1, llm)      REAL phi(iim + 1, jjm + 1, llm)
108      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
109      REAL w(ip1jmp1, llm)      REAL w(iim + 1, jjm + 1, llm)
110    
111      real sig1(klon, llm) ! section adiabatic updraft      real sig1(klon, llm) ! section adiabatic updraft
112      real w01(klon, llm) ! vertical velocity within adiabatic updraft      real w01(klon, llm) ! vertical velocity within adiabatic updraft
113    
114        real pls(iim + 1, jjm + 1, llm)
115        ! (pressure at mid-layer of LMDZ grid, in Pa)
116        ! "pls(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
117        ! for layer "l")
118    
119        REAL p3d(iim + 1, jjm + 1, llm+1) ! pressure at layer interfaces, in Pa
120        ! ("p3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)",
121        ! for interface "l")
122    
123        namelist /etat0_nml/ day_ref, annee_ref
124    
125      !---------------------------------      !---------------------------------
126    
127      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
128    
129        print *, "Enter namelist 'etat0_nml'."
130        read(unit=*, nml=etat0_nml)
131        write(unit_nml, nml=etat0_nml)
132    
133      CALL iniconst      CALL iniconst
134    
135      ! Construct a grid:      ! Construct a grid:
136    
137      pa = 5e4      pa = 5e4
138      CALL disvert      CALL disvert
139        call test_disvert
140    
141        CALL fyhyp(rlatu, rlatv, rlatu2, yprimu2, rlatu1, yprimu1)
142        CALL fxhyp(xprimm025, rlonv, xprimv, rlonu, xprimu, xprimp025)
143    
144        rlatu(1) = pi / 2.
145        rlatu(jjm + 1) = -rlatu(1)
146    
147      CALL inigeom      CALL inigeom
148      CALL inifilr      CALL inifilr
149    
150      latfi(1) = 90.      rlat(1) = 90.
151      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
152      ! (with conversion to degrees)      ! (with conversion to degrees)
153      latfi(klon) = - 90.      rlat(klon) = - 90.
154    
155      lonfi(1) = 0.      rlon(1) = 0.
156      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
157      ! (with conversion to degrees)      ! (with conversion to degrees)
158      lonfi(klon) = 0.      rlon(klon) = 0.
159    
160      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, &
161           zpic_2d, zval_2d) ! also compute "mask"           zpic_2d, zval_2d) ! also compute "mask"
# Line 195  contains Line 216  contains
216      if (nqmx >= 5) then      if (nqmx >= 5) then
217         ! Ozone:         ! Ozone:
218         call regr_lat_time_coefoz         call regr_lat_time_coefoz
219         call regr_pr_o3(q(:, :, :, 5))         call regr_pr_o3(p3d, q(:, :, :, 5))
220         ! Convert from mole fraction to mass fraction:         ! Convert from mole fraction to mass fraction:
221         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5) * 48. / 29.
222      end if      end if
223    
     tsol = pack(tsol_2d, dyn_phy)  
     qsol = pack(qsol_2d, dyn_phy)  
224      sn = 0. ! snow      sn = 0. ! snow
225      radsol = 0.      radsol = 0.
     tslab = 0. ! IM "slab" ocean  
226      seaice = 0.      seaice = 0.
227      rugmer = 0.001      rugmer = 0.001
228      zmea = pack(zmea_2d, dyn_phy)      zmea = pack(zmea_2d, dyn_phy)
# Line 282  contains Line 300  contains
300      ! V\'erification que somme des sous-surfaces vaut 1 :      ! V\'erification que somme des sous-surfaces vaut 1 :
301      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)      ji = count(abs(sum(pctsrf, dim = 2) - 1.) > EPSFRA)
302      IF (ji /= 0) then      IF (ji /= 0) then
303         PRINT *, 'Probl\`eme r\'epartition sous maille pour ', ji, 'points'         PRINT *, 'Bad surface percentages for ', ji, 'points'
304      end IF      end IF
305    
306      ! Calcul interm\'ediaire :      ! Calcul interm\'ediaire :
307      CALL massdair(p3d, masse)      CALL massdair(p3d, masse)
308    
     print *, 'ALPHAX = ', alphax  
   
309      forall (l = 1:llm)      forall (l = 1:llm)
310         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
311         masse(:, jjm + 1, l) = &         masse(:, jjm + 1, l) = &
# Line 299  contains Line 315  contains
315      ! Initialisation pour traceurs:      ! Initialisation pour traceurs:
316      call iniadvtrac      call iniadvtrac
317      itau_phy = 0      itau_phy = 0
     day_ref = dayref  
     annee_ref = anneeref  
318    
319      CALL geopot(teta, pk , pks, phis, phi)      CALL geopot(teta, pk , pks, phis, phi)
320      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, teta, ps, masse, pk, phis, phi, w, pbaru, &
321           pbarv)           pbarv)
322      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem0("start.nc", day_ref, phis)
323      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)      CALL dynredem1("start.nc", vcov, ucov, teta, q, masse, ps, itau=0)
324    
325      ! Initialisations :      ! Initialisations :
     tsolsrf(:, is_ter) = tsol  
     tsolsrf(:, is_lic) = tsol  
     tsolsrf(:, is_oce) = tsol  
     tsolsrf(:, is_sic) = tsol  
326      snsrf(:, is_ter) = sn      snsrf(:, is_ter) = sn
327      snsrf(:, is_lic) = sn      snsrf(:, is_lic) = sn
328      snsrf(:, is_oce) = sn      snsrf(:, is_oce) = sn
# Line 321  contains Line 331  contains
331      albe(:, is_lic) = 0.6      albe(:, is_lic) = 0.6
332      albe(:, is_oce) = 0.5      albe(:, is_oce) = 0.5
333      albe(:, is_sic) = 0.6      albe(:, is_sic) = 0.6
     alblw = albe  
334      evap = 0.      evap = 0.
335      qsolsrf(:, is_ter) = 150.      qsolsrf = 150.
336      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)  
337      rain_fall = 0.      rain_fall = 0.
338      snow_fall = 0.      snow_fall = 0.
339      solsw = 165.      solsw = 165.
# Line 335  contains Line 341  contains
341      t_ancien = 273.15      t_ancien = 273.15
342      q_ancien = 0.      q_ancien = 0.
343      agesno = 0.      agesno = 0.
     !IM "slab" ocean  
     tslab = tsolsrf(:, is_oce)  
344      seaice = 0.      seaice = 0.
345    
346      frugs(:, is_oce) = rugmer      frugs(:, is_oce) = rugmer
# Line 351  contains Line 355  contains
355      sig1 = 0.      sig1 = 0.
356      w01 = 0.      w01 = 0.
357    
358      call phyredem("startphy.nc", latfi, lonfi, pctsrf, &      call phyredem("startphy.nc", pctsrf, tsoil(:, 1, :), tsoil, &
359           tsolsrf, tsoil, tslab, seaice, qsolsrf, qsol, snsrf, albe, alblw, &           tsoil(:, 1, is_oce), seaice, qsolsrf, pack(qsol_2d, dyn_phy), snsrf, &
360           evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &           albe, evap, rain_fall, snow_fall, solsw, sollw, fder, radsol, frugs, &
361           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, &           agesno, zmea, zstd, zsig, zgam, zthe, zpic, zval, t_ancien, &
362           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  
363    
364    END SUBROUTINE etat0    END SUBROUTINE etat0
365    

Legend:
Removed from v.90  
changed lines
  Added in v.156

  ViewVC Help
Powered by ViewVC 1.1.21