source: palm/tags/release-5.0/LIB/rrtmg/rrlw_wvn.f90 @ 2977

Last change on this file since 2977 was 1585, checked in by maronga, 9 years ago

Added support for RRTMG radiation code

File size: 3.7 KB
Line 
1      module rrlw_wvn
2
3      use parkind, only : im => kind_im, rb => kind_rb
4      use parrrtm, only : nbndlw, mg, ngptlw, maxinpx
5
6      implicit none
7      save
8
9!------------------------------------------------------------------
10! rrtmg_lw spectral information
11
12! Initial version:  JJMorcrette, ECMWF, jul1998
13! Revised: MJIacono, AER, jun2006
14! Revised: MJIacono, AER, aug2008
15!------------------------------------------------------------------
16
17!  name     type     purpose
18! -----  :  ----   : ----------------------------------------------
19! ng     :  integer: Number of original g-intervals in each spectral band
20! nspa   :  integer: For the lower atmosphere, the number of reference
21!                    atmospheres that are stored for each spectral band
22!                    per pressure level and temperature.  Each of these
23!                    atmospheres has different relative amounts of the
24!                    key species for the band (i.e. different binary
25!                    species parameters).
26! nspb   :  integer: Same as nspa for the upper atmosphere
27!wavenum1:  real   : Spectral band lower boundary in wavenumbers
28!wavenum2:  real   : Spectral band upper boundary in wavenumbers
29! delwave:  real   : Spectral band width in wavenumbers
30! totplnk:  real   : Integrated Planck value for each band; (band 16
31!                    includes total from 2600 cm-1 to infinity)
32!                    Used for calculation across total spectrum
33!totplk16:  real   : Integrated Planck value for band 16 (2600-3250 cm-1)
34!                    Used for calculation in band 16 only if
35!                    individual band output requested
36!totplnkderiv: real: Integrated Planck function derivative with respect
37!                    to temperature for each band; (band 16
38!                    includes total from 2600 cm-1 to infinity)
39!                    Used for calculation across total spectrum
40!totplk16deriv:real: Integrated Planck function derivative with respect
41!                    to temperature for band 16 (2600-3250 cm-1)
42!                    Used for calculation in band 16 only if
43!                    individual band output requested
44!
45! ngc    :  integer: The number of new g-intervals in each band
46! ngs    :  integer: The cumulative sum of new g-intervals for each band
47! ngm    :  integer: The index of each new g-interval relative to the
48!                    original 16 g-intervals in each band
49! ngn    :  integer: The number of original g-intervals that are
50!                    combined to make each new g-intervals in each band
51! ngb    :  integer: The band index for each new g-interval
52! wt     :  real   : RRTM weights for the original 16 g-intervals
53! rwgt   :  real   : Weights for combining original 16 g-intervals
54!                    (256 total) into reduced set of g-intervals
55!                    (140 total)
56! nxmol  :  integer: Number of cross-section molecules
57! ixindx :  integer: Flag for active cross-sections in calculation
58!------------------------------------------------------------------
59
60      integer(kind=im) :: ng(nbndlw)
61      integer(kind=im) :: nspa(nbndlw)
62      integer(kind=im) :: nspb(nbndlw)
63
64      real(kind=rb) :: wavenum1(nbndlw)
65      real(kind=rb) :: wavenum2(nbndlw)
66      real(kind=rb) :: delwave(nbndlw)
67
68      real(kind=rb) :: totplnk(181,nbndlw)
69      real(kind=rb) :: totplk16(181)
70
71      real(kind=rb) :: totplnkderiv(181,nbndlw)
72      real(kind=rb) :: totplk16deriv(181)
73
74      integer(kind=im) :: ngc(nbndlw)
75      integer(kind=im) :: ngs(nbndlw)
76      integer(kind=im) :: ngn(ngptlw)
77      integer(kind=im) :: ngb(ngptlw)
78      integer(kind=im) :: ngm(nbndlw*mg)
79
80      real(kind=rb) :: wt(mg)
81      real(kind=rb) :: rwgt(nbndlw*mg)
82
83      integer(kind=im) :: nxmol
84      integer(kind=im) :: ixindx(maxinpx)
85
86      end module rrlw_wvn
Note: See TracBrowser for help on using the repository browser.