source: trunk/LMDZ.GENERIC/libf/phystd/callkeys_mod.F90 @ 2297

Last change on this file since 2297 was 2297, checked in by jvatant, 5 years ago

Add a generic n-layer aerosol scheme to replace the former buggy 2-layer scheme as well as the hard-coded NH3 cloud.

It can be called using 'aeronlay=.true.' in callphys.def, and set the number of layers (up to 4) with 'nlayaero'.
Then, the following parameters are read as arrays of size nlayaero in callphys.def (separated by blank space)


*aeronlay_tauref (Optical depth of aerosol layer at ref wavelenght)
*aeronlay_lamref (Ref wavelenght (m))
*aeronlay_choice (Choice for vertical profile - 1:tau follows atm scale height btwn top and bottom - 2:tau follows it own scale height)
*aeronlay_pbot (Bottom pressure (Pa))
*aeronlay_ptop (Top pressure (Pa) - useful only if choice=1)
*aeronlay_sclhght (Ratio of aerosol layer scale height / atmospheric scale height - useful only if choice=2 )
*aeronlay_size (Particle size (m))
*optprop_aeronlay_vis File for VIS opt properties.
*optprop_aeronlay_ir File for IR opt properties.

+Extra info :

+ In addition of solving the bug from 2-layer it enables different optical properties.
+ The former scheme are left for retrocompatibility (for now) but you should use the new one.
+ See aeropacity.F90 for the calculations

+ Each layer can have different optical properties, size of particle ...
+ You have different choices for vertical profile of the aerosol layers :

  • aeronlay_choice = 1 : Layer tau is spread between ptop and pbot following atm scale height.
  • aeronlay_choice = 2 : Layer tau follows its own scale height above cloud deck (pbot).

In this case ptop is dummy and sclhght gives the ratio H_cl/H_atm.

+ The reference wavelenght for input optical depth is now read as input (aeronlay_lamref)
+ Following the last point some comment is added in suaer_corrk about the 'not-really-dummy'ness of IR lamref..

File size: 5.7 KB
Line 
1MODULE callkeys_mod
2IMPLICIT NONE 
3
4      logical,save :: callrad,corrk,calldifv,UseTurbDiff
5!$OMP THREADPRIVATE(callrad,corrk,calldifv,UseTurbDiff)
6      logical,save :: calladj,calltherm,co2cond,callsoil
7!$OMP THREADPRIVATE(calladj,calltherm,co2cond,callsoil)
8      logical,save :: season,diurnal,tlocked,rings_shadow,lwrite
9!$OMP THREADPRIVATE(season,diurnal,tlocked,rings_shadow,lwrite)
10      logical,save :: callstats,calleofdump
11!$OMP THREADPRIVATE(callstats,calleofdump)
12      logical,save :: callgasvis,continuum,H2Ocont_simple,graybody
13!$OMP THREADPRIVATE(callgasvis,continuum,H2Ocont_simple,graybody)
14      logical,save :: strictboundcorrk                                     
15!$OMP THREADPRIVATE(strictboundcorrk)
16
17      logical,save :: enertest
18      logical,save :: nonideal
19      logical,save :: meanOLR
20      logical,save :: specOLR
21      logical,save :: kastprof
22      logical,save :: diagdtau
23!$OMP THREADPRIVATE(enertest,nonideal,meanOLR,kastprof,diagdtau)
24      logical,save :: newtonian
25      logical,save :: check_cpp_match
26      logical,save :: force_cpp
27      logical,save :: testradtimes
28      logical,save :: rayleigh
29!$OMP THREADPRIVATE(newtonian,check_cpp_match,force_cpp,testradtimes,rayleigh)
30      logical,save :: stelbbody
31      logical,save :: ozone
32      logical,save :: nearco2cond
33      logical,save :: tracer
34      logical,save :: mass_redistrib
35!$OMP THREADPRIVATE(stelbbody,ozone,nearco2cond,tracer,mass_redistrib)
36      logical,save :: varactive
37      logical,save :: varfixed
38      logical,save :: radfixed
39      logical,save :: sedimentation
40!$OMP THREADPRIVATE(varactive,varfixed,radfixed,sedimentation)
41      logical,save :: water,watercond,waterrain
42!$OMP THREADPRIVATE(water,watercond,waterrain)
43      logical,save :: aeroco2,aeroh2o,aeroh2so4,aeroback2lay
44!$OMP THREADPRIVATE(aeroco2,aeroh2o,aeroh2so4,aeroback2lay)
45      logical,save :: aeronh3, aeronlay, aeroaurora
46!$OMP THREADPRIVATE(aeronh3,aeronlay,aeroaurora)
47      logical,save :: aerofixco2,aerofixh2o
48!$OMP THREADPRIVATE(aerofixco2,aerofixh2o)
49      logical,save :: hydrology
50      logical,save :: sourceevol
51      logical,save :: CLFvarying
52      logical,save :: nosurf
53      logical,save :: oblate
54!$OMP THREADPRIVATE(hydrology,sourceevol,CLFvarying,nosurf,oblate)
55      logical,save :: ok_slab_ocean
56      logical,save :: ok_slab_sic
57      logical,save :: ok_slab_heat_transp
58      logical,save :: albedo_spectral_mode
59!$OMP THREADPRIVATE(ok_slab_ocean,ok_slab_sic,ok_slab_heat_transp,albedo_spectral_mode)
60      logical,save :: photochem
61      logical,save :: haze
62!$OMP THREADPRIVATE(photochem)
63
64      integer,save :: iddist
65      integer,save :: iaervar
66      integer,save :: iradia
67      integer,save :: startype
68      integer,save :: versH2H2cia
69      integer,save :: nlayaero
70!$OMP THREADPRIVATE(iddist,iaervar,iradia,startype,versH2H2cia,nlayaero)
71      integer,dimension(:),allocatable,save :: aeronlay_choice
72!$OMP THREADPRIVATE(aeronlay_choice)
73
74      character(64),save :: optprop_back2lay_vis
75      character(64),save :: optprop_back2lay_ir
76      character(64),dimension(:),allocatable,save :: optprop_aeronlay_vis
77      character(64),dimension(:),allocatable,save :: optprop_aeronlay_ir
78!$OMP THREADPRIVATE(optprop_back2lay_vis,optprop_back2lay_ir,optprop_aeronlay_vis,optprop_aeronlay_ir)
79
80      real,save :: tplanckmin
81      real,save :: tplanckmax
82      real,save :: dtplanck
83!$OMP THREADPRIVATE(tplanckmin,tplanckmax,dtplanck)
84      real,save :: topdustref
85      real,save :: Nmix_co2
86      real,save :: dusttau
87      real,save :: Fat1AU
88      real,save :: stelTbb
89!$OMP THREADPRIVATE(topdustref,Nmix_co2,dusttau,Fat1AU,stelTbb)
90      real,save :: Tstrat
91      real,save :: tplanet
92      real,save :: obs_tau_col_tropo
93      real,save :: obs_tau_col_strato
94!$OMP THREADPRIVATE(Tstrat,tplanet,obs_tau_col_tropo,obs_tau_col_strato)
95      real,save :: pres_bottom_tropo
96      real,save :: pres_top_tropo
97      real,save :: pres_bottom_strato
98      real,save :: pres_top_strato
99!$OMP THREADPRIVATE(pres_bottom_tropo,pres_top_tropo,pres_bottom_strato,pres_top_strato)
100      real,save :: size_tropo
101      real,save :: size_strato
102      real,save :: satval
103      real,save :: CLFfixval
104      real,save :: n2mixratio
105!$OMP THREADPRIVATE(size_tropo,size_strato,satval,CLFfixval,n2mixratio)
106      real,save :: size_nh3_cloud
107      real,save :: pres_nh3_cloud
108      real,save :: tau_nh3_cloud
109!$OMP THREADPRIVATE(size_nh3_cloud, pres_nh3_cloud, tau_nh3_cloud)
110      real,dimension(:),allocatable,save :: aeronlay_tauref
111      real,dimension(:),allocatable,save :: aeronlay_lamref
112      real,dimension(:),allocatable,save :: aeronlay_ptop
113      real,dimension(:),allocatable,save :: aeronlay_pbot
114      real,dimension(:),allocatable,save :: aeronlay_sclhght
115      real,dimension(:),allocatable,save :: aeronlay_size
116!$OMP THREADPRIVATE(aeronlay_tauref,aeronlay_lamref,aeronlay_ptop,aeronlay_pbot,aeronlay_sclhght,aeronlay_size)
117      real,save :: co2supsat
118      real,save :: pceil
119      real,save :: albedosnow
120      real,save :: albedoco2ice
121      real,save :: maxicethick
122!$OMP THREADPRIVATE(co2supsat,pceil,albedosnow,albedoco2ice,maxicethick)
123      real,save :: Tsaldiff
124      real,save :: tau_relax
125      real,save :: cloudlvl
126      real,save :: icetstep
127      real,save :: intheat
128!$OMP THREADPRIVATE(Tsaldiff,tau_relax,cloudlvl,icetstep,intheat)
129      real,save :: flatten
130      real,save :: Rmean
131      real,save :: J2
132      real,save :: MassPlanet
133!$OMP THREADPRIVATE(flatten,Rmean,J2,MassPlanet)
134      real,save :: surfalbedo
135      real,save :: surfemis
136!$OMP THREADPRIVATE(surfalbedo,surfemis)
137
138      logical,save :: iscallphys=.false.!existence of callphys.def
139!$OMP THREADPRIVATE(iscallphys)
140
141      ! do we read a startphy.nc file (default=.true.)
142      logical,save :: startphy_file=.true.
143!$OMP THREADPRIVATE(startphy_file)
144
145END MODULE callkeys_mod
Note: See TracBrowser for help on using the repository browser.