source: trunk/LMDZ.TITAN/libf/phytitan/radcommon_h.F90 @ 1715

Last change on this file since 1715 was 1648, checked in by jvatant, 8 years ago

Modifications to custom radiative transfer to Titan
+ Enables an altitude dependant gfrac for CIA computations

-> many radical changes in su_gases and co ..
-> read vertical CH4 profile with call_profilgases
-> Now you need a 'profile.def' that I will add in the deftank

+ Added interpolate CIA routines for CH4
+ Added temporary mean aerosol profile opacity routine (disr_haze)

File size: 6.2 KB
Line 
1module radcommon_h
2      use radinc_h, only: L_NSPECTI, L_NSPECTV, L_NGAUSS, NTstar, NTstop, &
3                          naerkind, nsizemax
4      implicit none
5
6!----------------------------------------------------------------------C
7!
8!                             radcommon.h
9!v
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.
38!     FZEROI     - Fraction of zeros in the IR CO2 k-coefficients, for
39!                  each temperature, pressure, and spectral interval
40!     FZEROV     - Fraction of zeros in the VISUAL CO2 k-coefficients, for
41!                  each temperature, pressure, and spectral interval
42!
43!     AEROSOL RADIATIVE OPTICAL CONSTANTS
44!
45!   Shortwave
46!   ~~~~~~~~~
47!
48! For the "naerkind" kind of aerosol radiative properties :
49! QVISsQREF  :  Qext / Qext("longrefvis")
50! omegavis   :  single scattering albedo
51! gvis       :  assymetry factor
52!
53!   Longwave
54!   ~~~~~~~~
55!
56! For the "naerkind" kind of aerosol radiative properties :
57! QIRsQREF :  Qext / Qext("longrefvis")
58! omegaIR  :  mean single scattering albedo
59! gIR      :  mean assymetry factor
60
61      REAL*8 BWNI(L_NSPECTI+1), WNOI(L_NSPECTI), DWNI(L_NSPECTI), WAVEI(L_NSPECTI) !BWNI read by master in setspi
62      REAL*8 BWNV(L_NSPECTV+1), WNOV(L_NSPECTV), DWNV(L_NSPECTV), WAVEV(L_NSPECTV) !BWNV read by master in setspv
63      REAL*8 STELLARF(L_NSPECTV), TAURAY(L_NSPECTV)
64!$OMP THREADPRIVATE(WNOI,DWNI,WAVEI,&
65        !$OMP WNOV,DWNV,WAVEV,&
66        !$OMP STELLARF,TAURAY)
67
68      REAL*8 blami(L_NSPECTI+1)
69      REAL*8 blamv(L_NSPECTV+1) ! these are needed by suaer.F90
70!$OMP THREADPRIVATE(blami,blamv)
71
72      !! AS: introduced to avoid doing same computations again for continuum
73      INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: indi
74      INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: indv
75!$OMP THREADPRIVATE(indi,indv)
76
77      !!! ALLOCATABLE STUFF SO THAT DIMENSIONS ARE READ in *.dat FILES -- AS 12/2011 
78      REAL*8, DIMENSION(:,:,:,:,:), ALLOCATABLE :: gasi, gasv
79      REAL*8, DIMENSION(:), ALLOCATABLE :: PGASREF, TGASREF, PFGASREF
80      real*8 FZEROI(L_NSPECTI)
81      real*8 FZEROV(L_NSPECTV)
82      real*8 pgasmin, pgasmax
83      real*8 tgasmin, tgasmax
84!$OMP THREADPRIVATE(gasi,gasv,&  !pgasref,tgasref,pfgasref read by master in sugas_corrk
85        !$OMP FZEROI,FZEROV)     !pgasmin,pgasmax,tgasmin,tgasmax read by master in sugas_corrk
86
87      real QVISsQREF(L_NSPECTV,naerkind,nsizemax)
88      real omegavis(L_NSPECTV,naerkind,nsizemax)
89      real gvis(L_NSPECTV,naerkind,nsizemax)
90      real QIRsQREF(L_NSPECTI,naerkind,nsizemax)
91      real omegair(L_NSPECTI,naerkind,nsizemax)
92      real gir(L_NSPECTI,naerkind,nsizemax)
93!$OMP THREADPRIVATE(QVISsQREF,omegavis,gvis,QIRsQREF,omegair,gir)
94
95
96! Reference wavelengths used to compute reference optical depth (m)
97! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
98
99      REAL lamrefir(naerkind),lamrefvis(naerkind)
100
101! Actual number of grain size classes in each domain for a
102!   given aerosol:
103
104      INTEGER          :: nsize(naerkind,2)
105
106! Particle size axis (depend on the kind of aerosol and the
107!   radiation domain)
108
109      DOUBLE PRECISION :: radiustab(naerkind,2,nsizemax)
110!$OMP THREADPRIVATE(lamrefir,lamrefvis,radiustab) !nsize read by suaer_corrk
111
112! Extinction coefficient at reference wavelengths;
113!   These wavelengths are defined in aeroptproperties, and called
114!   longrefvis and longrefir.
115
116      REAL :: QREFvis(naerkind,nsizemax)
117      REAL :: QREFir(naerkind,nsizemax)
118      REAL :: omegaREFvis(naerkind,nsizemax)
119      REAL :: omegaREFir(naerkind,nsizemax)
120
121      REAL,SAVE :: tstellar ! Stellar brightness temperature (SW)
122
123      real*8,save :: planckir(L_NSPECTI,NTstop-NTstar+1)
124
125      real*8,save :: PTOP
126      real*8,save,allocatable :: TAUREF(:)
127
128      real*8,parameter :: UBARI = 0.5D0
129
130      real*8,save :: gweight(L_NGAUSS)
131!$OMP THREADPRIVATE(QREFvis,QREFir,omegaREFvis,omegaREFir,&     ! gweight read by master in sugas_corrk
132                !$OMP tstellar,planckir,PTOP,TAUREF)
133
134!     If the gas optical depth (top to the surface) is less than
135!     this value, we place that Gauss-point into the "zeros"
136!     channel.
137      real*8, parameter :: TLIMIT =  1.0D-30
138
139!     Factor to convert pressures from millibars to Pascals
140      real*8, parameter :: SCALEP = 1.00D+2
141
142      real*8, parameter :: sigma = 5.67032D-8
143      real*8, parameter :: grav = 6.672E-11
144
145      real*8,save :: Cmk
146      real*8,save :: glat_ig
147!$OMP THREADPRIVATE(Cmk,glat_ig)
148
149      ! extinction of incoming sunlight (Saturn's rings, eclipses, etc...)
150      REAL, DIMENSION(:), ALLOCATABLE ,SAVE :: eclipse
151
152      !Latitude-dependent gravity
153      REAL, DIMENSION(:), ALLOCATABLE , SAVE :: glat
154!$OMP THREADPRIVATE(glat,eclipse)
155
156contains
157
158      subroutine ini_radcommon_h
159      use radinc_h, only: L_LEVELS
160      implicit none
161     
162        allocate(TAUREF(L_LEVELS+1))
163     
164      end subroutine ini_radcommon_h
165
166end module radcommon_h
Note: See TracBrowser for help on using the repository browser.