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

Last change on this file since 2156 was 1974, checked in by mvals, 6 years ago

Mars GCM:
Integration of the detached dust layer parametrizations (rocket dust storm, slope wind lifting, CW, and dust injection scheme, DB).
Still experimental, default behaviour (rdstorm=.false., dustinjection=0) identical to previous revision.
NB: Updated newstart requires an updated "surface.nc" containing the "hmons" field.
EM+MV

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