source: trunk/LMDZ.MARS/libf/phymars/dimradmars_mod.F90 @ 2199

Last change on this file since 2199 was 2199, checked in by mvals, 5 years ago

Mars GCM:
Implementation of a new parametrization of the dust entrainment by slope winds above the sub-grid scale topography. The parametrization is activated with the flag slpwind=.true. (set to "false" by
default) in callphys.def. The new parametrization involves the new tracers topdust_mass and topdust_number.
MV

File size: 9.3 KB
Line 
1module dimradmars_mod
2!   Declaration and settings for radiative transfer calculations
3!   Initializations and allocations are done in phys_state_var_init
4implicit none
5  ! nflev: number of vertical layer
6  ! ndlon,ndlo2: number of horizontal points
7  ! Splitting of horizontal grid
8  ! NDLO2 and ndomainsz for the splitting in the physics call
9  ! WARNING:  One must have  1 < ndomainsz =< ngrid
10  integer,save :: NFLEV !=nlayer   ! with splitting
11  integer,save :: ndomainsz !=(ngrid-1)/20 + 1
12  integer,save :: NDLON !=ndomainsz  ! with splitting
13  integer,save :: NDLO2 !=NDLON
14
15
16! Number of kind of tracer radiative properties
17! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
18! naerkind is set by reading callphys.def
19! -- see conf_phys
20! -- value of nsizemax below is comfortably high
21!    but beware in case you add a lot of scatterers
22  INTEGER, SAVE :: naerkind
23
24  ! AS: previously in aerkind.h
25  character*20, SAVE, ALLOCATABLE :: name_iaer(:)  ! name of the scatterers
26  integer iaer_dust_conrath ! Typical dust profiles using a
27                            ! Conrath type analytical equation
28  integer iaer_dust_doubleq ! Dust profile is given by the
29                            ! mass mixing ratio of the two-
30                            ! moment scheme method (doubleq)
31  integer iaer_dust_submicron ! Dust profile is given by a
32                              ! submicron population of dust
33                              ! particles
34  integer iaer_stormdust_doubleq ! Storm dust profile is given by the
35                              ! mass mixing ratio of the two moment scheme
36                              ! method (doubleq)
37  integer iaer_topdust_doubleq ! top dust profile is given by the
38                              ! mass mixing ratio of the two moment scheme
39                              ! method (doubleq)
40  integer iaer_h2o_ice ! Water ice particles
41
42  ! AS: was in aeropacity
43  INTEGER,SAVE,ALLOCATABLE :: iaerdust(:)
44
45  ! AS: was in suaer
46  CHARACTER(LEN=30), SAVE, ALLOCATABLE :: file_id(:,:)
47
48! Reference wavelengths used to compute reference optical depth (m)
49! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
50  REAL,SAVE,ALLOCATABLE :: longrefir(:),longrefvis(:)
51 
52! Definition of spectral intervals at thermal infrared wavelengths (LW)
53! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
54  integer,parameter :: nir=4 ! Total number of thermal IR bands
55  integer,parameter :: nuco2=2 ! number of bands in CO2 bands
56  real,parameter :: long1ir=5.E-6 , long2ir=200.E-6
57  real,parameter :: long1co2=1.E+0 / 865.E+2 , long2co2=1.E+0 / 500.E+2
58
59!  Warning : the "nir" thermal IR bands are not ordered by wavelength:
60!      iir=1 : central 15um CO2 bands     
61!      iir=2 : CO2 band wings    [long1co2-long2co2] MINUS central band
62!      iir=3 : 9 um band [long1ir - long1co2]
63!      iir=4 : Far IR    [long2co2 - long2ir]
64   
65!  Definition of spectral interval at solar wavelengths (SW)
66!  ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
67  integer,parameter :: NSUN=2   ! do not change that !
68!  Boundaries of spectral intervals (m) :
69  real,parameter :: long1vis=0.1E-6 , long2vis=0.5E-6 , long3vis=5.E-6
70!  Fraction of solar energy in solar band #1 [long1vis-long2vis] : 0.274490
71!  Fraction of solar energy in solar band #2 [long2vis-long3vis] : 0.725509
72  real,save :: sunfr(2) = (/ 0.274490 , 0.725509 /)
73
74! Maximum number of grain size classes
75! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
76! This parameter has to be set to the maximum number of particle
77!   sizes contained in the optical parameter database; For example,
78!   if only one grain size is used to describe dust, and 30 are used
79!   to describe water-ice crystals in the visible and 15 in the IR,
80!   nsizemax has to be set to 30.
81! If only one grain size is considered for all the aerosols, set
82!   this parameter to 1 and convolution will be turned off during
83!   the radiative calculations.
84
85  integer, parameter :: nsizemax = 60
86! integer, parameter :: nsizemax = 1
87
88! Various initialisation for LW radiative code
89! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
90! npademx : number of Pade coefficients
91! nabsmx : ?
92! nt_pademx : number of temperature intervals for Pade
93
94  integer,parameter :: npademx=4
95  integer,parameter :: nabsmx=2
96  integer,parameter :: nt_pademx=19
97
98!!
99!! variables
100!!
101  REAL,SAVE,ALLOCATABLE :: dtrad(:,:) ! Net atm. radiative heating rate (K.s-1)
102  REAL,SAVE,ALLOCATABLE :: fluxrad_sky(:) ! rad. flux from sky absorbed by surface (W.m-2)
103  REAL,SAVE,ALLOCATABLE :: fluxrad(:) ! Net radiative surface flux (W.m-2)
104  REAL,SAVE,ALLOCATABLE :: albedo(:,:) ! Surface albedo in each solar band
105  REAL,SAVE,ALLOCATABLE :: tauscaling(:)   ! Convertion factor for qdust and Ndust
106  REAL,SAVE,ALLOCATABLE :: totcloudfrac(:) ! total cloud fraction over the column
107! aerosol (dust or ice) extinction optical depth  at reference wavelength
108! "longrefvis" set in dimradmars_mod , for one of the "naerkind"  kind of
109! aerosol optical properties  :
110  REAL,SAVE,ALLOCATABLE :: aerosol(:,:,:)
111  REAL,SAVE,ALLOCATABLE :: nueffdust(:,:) ! Dust effective variance
112
113!! ------------------------------------------------------
114!! AS: what was previously in yomaer
115!   Shortwave
116!   ~~~~~~~~~
117!
118! tauvis: dust optical depth at reference wavelength  ("longrefvis" set
119! in dimradmars_mod : typically longrefvis = 0.67E-6 m, as measured by Viking )
120
121! For the "naerkind" kind of aerosol radiative properties :
122! QVISsQREF  :  Qext / Qext("longrefvis")   <--- For both solar bands
123! omegavis   :  sinle scattering albedo     <--- For both solar bands
124! gvis       :  assymetry factor            <--- For both solar bands
125!
126!   Longwave
127!   ~~~~~~~~
128!
129! For the "naerkind" kind of aerosol radiative properties :
130! QIRsQREF :  Qext / Qext("longrefvis")     <--- For the nir bandes IR
131! omegaIR  :  mean single scattering albedo <--- For the nir bandes IR
132! gIR      :  mean assymetry factor         <--- For the nir bandes IR
133!
134  real,save :: tauvis
135  real,save,allocatable :: QVISsQREF(:,:,:)
136  real,save,allocatable :: omegavis(:,:,:)
137  real,save,allocatable :: gvis(:,:,:)
138  real,save,allocatable :: QIRsQREF(:,:,:)
139  real,save,allocatable :: omegaIR(:,:,:)
140  real,save,allocatable :: gIR(:,:,:)
141! Actual number of grain size classes in each domain for a
142!   given aerosol:
143  integer,save,allocatable :: nsize(:,:)
144! Particle size axis (depend on the kind of aerosol and the
145!   radiation domain)
146  real,save,allocatable :: radiustab(:,:,:)
147! Extinction coefficient at reference wavelengths;
148!   These wavelengths are defined in dimradmars_mod, and called
149!   longrefvis and longrefir.
150  real,save,allocatable :: QREFvis(:,:)
151  real,save,allocatable :: QREFir(:,:)
152  real,save,allocatable :: omegaREFvis(:,:)
153  real,save,allocatable :: omegaREFir(:,:)
154!! ------------------------------------------------------
155
156contains
157
158  subroutine ini_dimradmars_mod(ngrid,nlayer)
159 
160  implicit none
161 
162  integer,intent(in) :: ngrid ! number of atmospheric columns
163  integer,intent(in) :: nlayer ! number of atmospheric layers
164
165   nflev=nlayer
166!  ndomainsz=ngrid
167   ndomainsz=(ngrid-1)/20 + 1
168!  ndomainsz=(ngrid-1)/5 + 1
169   ndlon=ndomainsz
170   ndlo2=ndlon
171
172   allocate(albedo(ngrid,2))
173   allocate(dtrad(ngrid,nlayer))
174   allocate(fluxrad_sky(ngrid))
175   allocate(fluxrad(ngrid))
176   allocate(tauscaling(ngrid))
177   allocate(nueffdust(ngrid,nlayer))
178   allocate(totcloudfrac(ngrid))
179
180  end subroutine ini_dimradmars_mod
181
182  subroutine end_dimradmars_mod
183
184  implicit none
185
186   if (allocated(albedo))      deallocate(albedo)
187   if (allocated(dtrad))       deallocate(dtrad)
188   if (allocated(fluxrad_sky)) deallocate(fluxrad_sky)
189   if (allocated(fluxrad))     deallocate(fluxrad)
190   if (allocated(tauscaling))  deallocate(tauscaling)
191   if (allocated(nueffdust))   deallocate(nueffdust)
192   if (allocated(totcloudfrac))   deallocate(totcloudfrac)
193
194  end subroutine end_dimradmars_mod
195
196 
197  subroutine ini_scatterers(ngrid,nlayer)
198
199  implicit none
200
201  integer,intent(in) :: ngrid ! number of atmospheric columns
202  integer,intent(in) :: nlayer ! number of atmospheric layers
203
204   !! domain-dependent
205   !! -- only used in physiq_mod & intent(out) in callradite
206   if (allocated(aerosol)) deallocate(aerosol)
207   allocate(aerosol(ngrid,nlayer,naerkind))
208
209   !! not domain-dependent
210   if (.not.allocated(name_iaer)) allocate(name_iaer(naerkind))
211   if (.not.allocated(longrefir)) allocate(longrefir(naerkind))
212   if (.not.allocated(longrefvis)) allocate(longrefvis(naerkind))
213   if (.not.allocated(iaerdust)) allocate(iaerdust(naerkind))
214   if (.not.allocated(file_id)) allocate(file_id(naerkind,2))
215   if (.not.allocated(QVISsQREF)) allocate(QVISsQREF(nsun,naerkind,nsizemax))
216   if (.not.allocated(omegavis)) allocate(omegavis(nsun,naerkind,nsizemax))
217   if (.not.allocated(gvis)) allocate(gvis(nsun,naerkind,nsizemax))
218   if (.not.allocated(QIRsQREF)) allocate(QIRsQREF(nir,naerkind,nsizemax))
219   if (.not.allocated(omegaIR)) allocate(omegaIR(nir,naerkind,nsizemax))
220   if (.not.allocated(gIR)) allocate(gIR(nir,naerkind,nsizemax))
221   if (.not.allocated(nsize)) allocate(nsize(naerkind,2))
222   if (.not.allocated(radiustab)) allocate(radiustab(naerkind,2,nsizemax))
223   if (.not.allocated(QREFvis)) allocate(QREFvis(naerkind,nsizemax))
224   if (.not.allocated(QREFir)) allocate(QREFir(naerkind,nsizemax))
225   if (.not.allocated(omegaREFvis)) allocate(omegaREFvis(naerkind,nsizemax))
226   if (.not.allocated(omegaREFir)) allocate(omegaREFir(naerkind,nsizemax))
227
228  end subroutine ini_scatterers
229
230end module dimradmars_mod
Note: See TracBrowser for help on using the repository browser.