source: trunk/LMDZ.GENERIC/libf/phystd/radcommon_h.F90 @ 2613

Last change on this file since 2613 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: 6.3 KB
RevLine 
[1529]1module radcommon_h
[2283]2      use radinc_h, only: L_NSPECTI, L_NSPECTV, NTstart, NTstop, &
[1529]3                          naerkind, nsizemax
[135]4      implicit none
5
6!----------------------------------------------------------------------C
7!
8!                             radcommon.h
9!
10!----------------------------------------------------------------------C
11!
12!  "Include" grid.h and radinc.h before this file in code that uses
13!  some or all of this common data set
14!
15!     WNOI       - Array of wavenumbers at the spectral interval
16!                  centers for the infrared.  Array is NSPECTI
17!                  elements long.
18!     DWNI       - Array of "delta wavenumber", i.e., the width,
19!                  in wavenumbers (cm^-1) of each IR spectral
20!                  interval.  NSPECTI elements long.
21!     WAVEI      - Array (NSPECTI elements long) of the wavelenght
22!                  (in microns) at the center of each IR spectral
23!                  interval.
24!     WNOV       - Array of wavenumbers at the spectral interval
25!                  center for the VISUAL.  Array is NSPECTV
26!                  elements long.
27!     DWNV       - Array of "delta wavenumber", i.e., the width,
28!                  in wavenumbers (cm^-1) of each VISUAL spectral
29!                  interval.  NSPECTV elements long.
30!     WAVEV      - Array (NSPECTV elements long) of the wavelenght
31!                  (in microns) at the center of each VISUAL spectral
32!                  interval.
33!     STELLARF   - Array (NSPECTV elements) of stellar flux (W/M^2) in
34!                  each spectral interval.  Values are for 1 AU,
35!                  scaled to the planetary distance elsewhere.
36!     TAURAY     - Array (NSPECTV elements) of the pressure-independent
37!                  part of Rayleigh scattering optical depth.
[1016]38!     TAURAYVAR  - Array (NSPECTV elements) of the pressure-independent
39!                  part of Rayleigh scattering optical depth for the variable gas.
[135]40!     FZEROI     - Fraction of zeros in the IR CO2 k-coefficients, for
41!                  each temperature, pressure, and spectral interval
42!     FZEROV     - Fraction of zeros in the VISUAL CO2 k-coefficients, for
43!                  each temperature, pressure, and spectral interval
44!
45!     AEROSOL RADIATIVE OPTICAL CONSTANTS
46!
47!   Shortwave
48!   ~~~~~~~~~
49!
50! For the "naerkind" kind of aerosol radiative properties :
51! QVISsQREF  :  Qext / Qext("longrefvis")
52! omegavis   :  single scattering albedo
53! gvis       :  assymetry factor
54!
55!   Longwave
56!   ~~~~~~~~
57!
58! For the "naerkind" kind of aerosol radiative properties :
[2297]59! QIRsQREF :  Qext / Qext("longrefir")
[135]60! omegaIR  :  mean single scattering albedo
61! gIR      :  mean assymetry factor
[2297]62!
63!
64! Note - QIRsQREF in the martian model was scaled to longrefvis,
65! here it is scaled to longrefir, which is actually a dummy parameter,
66! as we do not output scaled aerosol opacity ...
67!
[135]68
[1315]69      REAL*8 BWNI(L_NSPECTI+1), WNOI(L_NSPECTI), DWNI(L_NSPECTI), WAVEI(L_NSPECTI) !BWNI read by master in setspi
70      REAL*8 BWNV(L_NSPECTV+1), WNOV(L_NSPECTV), DWNV(L_NSPECTV), WAVEV(L_NSPECTV) !BWNV read by master in setspv
[1016]71      REAL*8 STELLARF(L_NSPECTV), TAURAY(L_NSPECTV), TAURAYVAR(L_NSPECTV)
[1315]72!$OMP THREADPRIVATE(WNOI,DWNI,WAVEI,&
73        !$OMP WNOV,DWNV,WAVEV,&
74        !$OMP STELLARF,TAURAY,TAURAYVAR)
[135]75
76      REAL*8 blami(L_NSPECTI+1)
77      REAL*8 blamv(L_NSPECTV+1) ! these are needed by suaer.F90
[1315]78!$OMP THREADPRIVATE(blami,blamv)
[135]79
[873]80      !! AS: introduced to avoid doing same computations again for continuum
[878]81      INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: indi
82      INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: indv
[1315]83!$OMP THREADPRIVATE(indi,indv)
[873]84
[470]85      !!! ALLOCATABLE STUFF SO THAT DIMENSIONS ARE READ in *.dat FILES -- AS 12/2011 
86      REAL*8, DIMENSION(:,:,:,:,:), ALLOCATABLE :: gasi, gasv
[2026]87      REAL*8, DIMENSION(:), ALLOCATABLE :: PGASREF, TGASREF, WREFVAR, PFGASREF, GWEIGHT
[135]88      real*8 FZEROI(L_NSPECTI)
89      real*8 FZEROV(L_NSPECTV)
90      real*8 pgasmin, pgasmax
91      real*8 tgasmin, tgasmax
[1315]92!$OMP THREADPRIVATE(gasi,gasv,&  !wrefvar,pgasref,tgasref,pfgasref read by master in sugas_corrk
93        !$OMP FZEROI,FZEROV)     !pgasmin,pgasmax,tgasmin,tgasmax read by master in sugas_corrk
[135]94
95      real QVISsQREF(L_NSPECTV,naerkind,nsizemax)
96      real omegavis(L_NSPECTV,naerkind,nsizemax)
97      real gvis(L_NSPECTV,naerkind,nsizemax)
98      real QIRsQREF(L_NSPECTI,naerkind,nsizemax)
99      real omegair(L_NSPECTI,naerkind,nsizemax)
100      real gir(L_NSPECTI,naerkind,nsizemax)
[1315]101!$OMP THREADPRIVATE(QVISsQREF,omegavis,gvis,QIRsQREF,omegair,gir)
[135]102
103
104! Reference wavelengths used to compute reference optical depth (m)
105! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
106
107      REAL lamrefir(naerkind),lamrefvis(naerkind)
108
109! Actual number of grain size classes in each domain for a
110!   given aerosol:
111
112      INTEGER          :: nsize(naerkind,2)
113
114! Particle size axis (depend on the kind of aerosol and the
115!   radiation domain)
116
117      DOUBLE PRECISION :: radiustab(naerkind,2,nsizemax)
[1315]118!$OMP THREADPRIVATE(lamrefir,lamrefvis,radiustab) !nsize read by suaer_corrk
[135]119
120! Extinction coefficient at reference wavelengths;
121!   These wavelengths are defined in aeroptproperties, and called
122!   longrefvis and longrefir.
123
124      REAL :: QREFvis(naerkind,nsizemax)
125      REAL :: QREFir(naerkind,nsizemax)
[2033]126!      REAL :: omegaREFvis(naerkind,nsizemax)
[135]127      REAL :: omegaREFir(naerkind,nsizemax)
128
[1529]129      REAL,SAVE :: tstellar ! Stellar brightness temperature (SW)
[135]130
[2283]131      REAL*8, DIMENSION(:,:), ALLOCATABLE, SAVE :: planckir
[135]132
[1529]133      real*8,save :: PTOP
[135]134
[1529]135      real*8,parameter :: UBARI = 0.5D0
[135]136
[2142]137!$OMP THREADPRIVATE(QREFvis,QREFir,omegaREFir,&         ! gweight read by master in sugas_corrk
[1715]138                !$OMP tstellar,planckir,PTOP)
[135]139
140!     If the gas optical depth (top to the surface) is less than
141!     this value, we place that Gauss-point into the "zeros"
142!     channel.
143      real*8, parameter :: TLIMIT =  1.0D-30
144
145!     Factor to convert pressures from millibars to Pascals
146      real*8, parameter :: SCALEP = 1.00D+2
147
[959]148      real*8, parameter :: sigma = 5.67032D-8
[1194]149      real*8, parameter :: grav = 6.672E-11
[135]150
[1529]151      real*8,save :: Cmk
152      real*8,save :: glat_ig
[1315]153!$OMP THREADPRIVATE(Cmk,glat_ig)
[135]154
[1133]155      ! extinction of incoming sunlight (Saturn's rings, eclipses, etc...)
[1529]156      REAL, DIMENSION(:), ALLOCATABLE ,SAVE :: eclipse
[135]157
[1194]158      !Latitude-dependent gravity
[1529]159      REAL, DIMENSION(:), ALLOCATABLE , SAVE :: glat
[1315]160!$OMP THREADPRIVATE(glat,eclipse)
[1194]161
[1529]162end module radcommon_h
Note: See TracBrowser for help on using the repository browser.