source: trunk/LMDZ.MARS/libf/phymars/phys_state_var_init_mod.F90 @ 2628

Last change on this file since 2628 was 2628, checked in by abierjon, 3 years ago

Mars GCM:
Big changes on mountain top dust flows for GCM6:

  • the scheme now activates only in grid meshes that contain a mountain among a hard-written list, instead of every meshes. This is done to prevent strong artificial reinjections of dust in places that don't present huge converging slopes enabling the concentration of dust (ex: Valles Marineris, Hellas). Topdust is now also detrained as soon as it leaves the column it originated from.
  • the list of the 19 allowed mountains is used by the subroutine topmons_setup in module topmons_mod, to compute a logical array contains_mons(ngrid). alpha_hmons and hsummit are also set up once and for all by this subroutine, which is called in physiq_mod's firstcall.
  • contains_mons, alpha_hmons and hsummit are now saved variables of the module surfdat_h, and are called as such and not as arguments in the subroutines using them.
  • the logical flag "slpwind" and the comments in the code have also been updated to the new terminology "mountain top dust flows", accordingly to ticket #71. The new flag read in callphys.def is "topflows".

AB

File size: 5.1 KB
Line 
1MODULE phys_state_var_init_mod
2
3CONTAINS
4
5      SUBROUTINE phys_state_var_init(ngrid,nlayer,nq,tname, &
6                                     day_ini,day_end,hour_ini,pdaysec,ptimestep, &
7                                     prad,pg,pr,pcpp, &
8                                     dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
9
10!=======================================================================
11!
12!   purpose:
13!   -------
14!
15!   Allocate arrays in modules
16!   Fill geometrical arrays
17!   Fill a first set of physical constants
18!   -- was done previously in inifis
19!
20!=======================================================================
21!   
22!   authors: Ehouarn Millour and Aymeric Spiga
23!            14/04/2014
24!
25!   arguments:
26!   ----------
27!
28!   input:
29!   ------
30!
31!    ngrid                 Size of the horizontal grid.
32!    nlayer                Number of vertical layers.
33!    nq                    Number of tracers.
34!
35!=======================================================================
36
37      use init_print_control_mod, only: init_print_control
38      use slope_mod, only: ini_slope_mod,end_slope_mod
39      use comsaison_h, only: ini_comsaison_h,end_comsaison_h
40      use surfdat_h, only: ini_surfdat_h,end_surfdat_h
41      use comgeomfi_h, only: ini_comgeomfi_h,end_comgeomfi_h
42      use comsoil_h, only: ini_comsoil_h,end_comsoil_h
43      use dimradmars_mod, only: ini_dimradmars_mod,end_dimradmars_mod
44      use yomlw_h, only: ini_yomlw_h,end_yomlw_h
45      use conc_mod, only: ini_conc_mod,end_conc_mod
46      use turb_mod, only: ini_turb_mod,end_turb_mod
47      use comcstfi_h, only: pi,rad,cpp,g,r,rcp
48      use tracer_mod, only: ini_tracer_mod,end_tracer_mod
49      use time_phylmdz_mod, only: init_time
50      use compute_dtau_mod, only: ini_compute_dtau_mod, &
51                                  end_compute_dtau_mod
52      use rocketduststorm_mod, only: ini_rocketduststorm_mod, &
53                                     end_rocketduststorm_mod
54      use calchim_mod, only: ini_calchim_mod,end_calchim_mod
55      use watercloud_mod, only: ini_watercloud_mod, &
56                                end_watercloud_mod
57      use nonoro_gwd_ran_mod, only: ini_nonoro_gwd_ran, &
58                                    end_nonoro_gwd_ran
59      use dust_param_mod, only: ini_dust_param_mod, &
60                                end_dust_param_mod
61      use dust_rad_adjust_mod, only: ini_dust_rad_adjust_mod, &
62                                     end_dust_rad_adjust_mod
63      IMPLICIT NONE
64     
65      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
66      CHARACTER(len=*),INTENT(IN) :: tname(nq)
67      INTEGER,INTENT(IN) :: day_ini, day_end
68      REAL,INTENT(IN) :: hour_ini
69      REAL,INTENT(IN) :: pdaysec,ptimestep,prad,pg,pr,pcpp
70!MVals isotopes
71      INTEGER,INTENT(in) :: dyn_nqperes
72      INTEGER,INTENT(in) :: dyn_nqfils(nq)
73
74      ! set dimension and allocate arrays in tracer_mod
75      call end_tracer_mod
76      call ini_tracer_mod(nq,tname,dyn_nqperes,dyn_nqfils)! MVals: variables isotopes
77
78
79      ! initialize "print_control" constants/flags ("prt_level","lunout", etc.)
80      call init_print_control
81     
82      ! set parameters in comcstfi_h
83      pi=2.*asin(1.)
84      rad=prad
85      cpp=pcpp
86      g=pg
87      r=pr
88      rcp=r/cpp
89
90      ! Initialize some "temporal and calendar" related variables
91      call init_time(day_ini,day_end,hour_ini,pdaysec,ptimestep)
92
93      ! allocate "slope_mod" arrays
94      call end_slope_mod
95      call ini_slope_mod(ngrid)
96
97      ! allocate "comsaison_h" arrays
98      call end_comsaison_h
99      call ini_comsaison_h(ngrid)
100
101      ! allocate "surfdat_h" arrays
102      call end_surfdat_h
103      call ini_surfdat_h(ngrid,nq)
104
105      ! allocate "comgeomfi_h" arrays
106      call end_comgeomfi_h
107      call ini_comgeomfi_h(ngrid)
108
109      ! allocate "comsoil_h" arrays
110      call end_comsoil_h
111      call ini_comsoil_h(ngrid)
112
113      ! set some variables in "dimradmars_mod"
114      call end_dimradmars_mod
115      call ini_dimradmars_mod(ngrid,nlayer)
116
117      ! allocate arrays in "yomlw_h"
118      call end_yomlw_h
119      call ini_yomlw_h(ngrid)
120
121      ! allocate arrays in "conc_mod" (aeronomars)
122      call end_conc_mod
123      call ini_conc_mod(ngrid,nlayer)
124
125      ! allocate arrays in "turb_mod"
126      call end_turb_mod
127      call ini_turb_mod(ngrid,nlayer)
128
129      ! allocate arrays in "compute_dtau_mod":
130      call end_compute_dtau_mod
131      call ini_compute_dtau_mod(ngrid)
132
133      ! allocate arrays in "rocketduststorm_mod":
134      call end_rocketduststorm_mod
135      call ini_rocketduststorm_mod(ngrid)
136
137      ! allocate arrays in "calchim_mod" (aeronomars)
138      call end_calchim_mod
139      call ini_calchim_mod(ngrid,nlayer,nq)
140
141      ! allocate arrays in "watercloud_mod"
142      call end_watercloud_mod
143      call ini_watercloud_mod(ngrid,nlayer,nq)
144
145      ! allocate arrays in "nonoro_gwd_ran_mod"
146      call end_nonoro_gwd_ran
147      call ini_nonoro_gwd_ran(ngrid,nlayer)
148
149      ! allocate arrays in "dust_param_mod"
150      call end_dust_param_mod
151      call ini_dust_param_mod(ngrid)
152     
153      ! allocate arrays in "dust_rad_adjust_mod"
154      call end_dust_rad_adjust_mod
155      call ini_dust_rad_adjust_mod(ngrid)
156
157      END SUBROUTINE phys_state_var_init
158
159END MODULE phys_state_var_init_mod
Note: See TracBrowser for help on using the repository browser.