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

Last change on this file since 2616 was 2578, checked in by romain.vande, 3 years ago

First stage of implementing Open_MP in the physic.
So far it can initialyse physic and run with all routines at .FALSE.

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