source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/config/ppsrc/phys/radinc_h.f90 @ 224

Last change on this file since 224 was 224, checked in by ymipsl, 10 years ago
File size: 4.7 KB
Line 
1      module radinc_h
2
3      implicit none
4
5!-----------------------------------------------------------------------
6!   INCLUDE 'dimensions.h'
7!
8!   dimensions.h contient les dimensions du modele
9!   ndm est tel que iim=2**ndm
10!-----------------------------------------------------------------------
11
12      INTEGER iim,jjm,llm,ndm
13
14      PARAMETER (iim= 128,jjm=96,llm=64,ndm=1)
15
16!-----------------------------------------------------------------------
17!-----------------------------------------------------------------------
18!   INCLUDE 'bands.h'
19!
20!   bands.h contains the visible & infrared bands in the model
21!
22!   NBinfrared = L_NSPECTI in the model
23!   NBvisible  = L_NSPECTV in the model
24!-----------------------------------------------------------------------
25
26      INTEGER, parameter :: NBinfrared=20
27      INTEGER, parameter :: NBvisible=30
28
29
30!-----------------------------------------------------------------------
31!-----------------------------------------------------------------------
32!   INCLUDE 'scatterers.h'
33!
34! Number of radiatively active species
35! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
36!
37!-----------------------------------------------------------------------
38
39      integer, parameter :: naerkind=1
40
41!-----------------------------------------------------------------------
42
43!======================================================================
44!
45!     RADINC.H
46!
47!     Includes for the radiation code; RADIATION LAYERS, LEVELS,
48!     number of spectral intervals. . .
49!
50!======================================================================
51
52!     RADIATION parameters
53
54!     In radiation code, layer 1 corresponds to the stratosphere.  Level
55!     1 is the top of the stratosphere.  The dummy layer is at the same
56!     temperature as the (vertically isothermal) stratosphere, and
57!     any time it is explicitly needed, the appropriate quantities will
58!     be dealt with (aka "top". . .)
59
60!     L_NLEVRAD corresponds to the surface - i.e., the GCM Level that
61!     is at the surface.  PLEV(L_NLEVRAD) = P(J,I)+PTROP,
62!     PLEV(2) = PTROP, PLEV(1) = ptop
63
64!     L_NLAYRAD is the number of radiation code layers
65!     L_NLEVRAD is the number of radiation code levels.  Level N is the
66!               top of layer N.
67!
68!     L_NSPECTI is the number of IR spectral intervals
69!     L_NSPECTV is the number of Visual(or Solar) spectral intervals
70!     L_NGAUSS  is the number of Gauss points for K-coefficients
71!               GAUSS POINT 17 (aka the last one) is the special case
72!
73!     L_NPREF   is the number of reference pressures that the
74!               k-coefficients are calculated on
75!     L_PINT    is the number of Lagrange interpolated reference
76!               pressures for the gas k-coefficients - now for a
77!               smaller p-grid than before
78!     L_NTREF   is the number of reference temperatures for the
79!               k-coefficients
80!     L_TAUMAX  is the largest optical depth - larger ones are set
81!               to this value
82!
83!     L_REFVAR  The number of different mixing ratio values for
84!               the k-coefficients. Variable component of the mixture
85!               can in princple be anything: currently it's H2O.
86!
87!     NAERKIND  The number of radiatively active aerosol types
88!
89!     NSIZEMAX  The maximum number of aerosol particle sizes
90!
91!----------------------------------------------------------------------
92
93      integer, parameter :: L_NLAYRAD  = llm
94      integer, parameter :: L_LEVELS   = 2*(llm-1)+3
95      integer, parameter :: L_NLEVRAD  = llm+1
96
97      ! These are set in sugas_corrk
98      ! [uses allocatable arrays] -- AS 12/2011
99      integer :: L_NPREF, L_NTREF, L_REFVAR, L_PINT
100
101      integer, parameter :: L_NGAUSS  = 17
102
103      integer, parameter :: L_NSPECTI = NBinfrared
104      integer, parameter :: L_NSPECTV = NBvisible
105
106!      integer, parameter :: NAERKIND  = 2 ! set in scatterers.h
107      real,    parameter :: L_TAUMAX  = 35
108
109      ! For Planck function integration:
110      ! equivalent temperatures are 1/NTfac of these values
111      integer, parameter :: NTstar = 500
112      integer, parameter :: NTstop = 15000 ! new default for all non hot Jupiter runs
113      real*8, parameter :: NTfac = 1.0D+1 
114      !integer, parameter :: NTstar = 1000
115      !integer, parameter :: NTstop = 25000
116      !real*8,parameter :: NTfac = 5.0D+1   
117      !integer, parameter :: NTstar = 2000
118      !integer, parameter :: NTstop = 50000
119      !real*8,parameter :: NTfac = 1.0D+2   
120
121      ! Maximum number of grain size classes for aerosol convolution:
122      ! This must correspond to size of largest dataset used for aerosol
123      ! optical properties in datagcm folder.
124      integer, parameter :: nsizemax = 60
125
126      character (len=100) :: corrkdir
127      save corrkdir
128
129      character (len=100) :: banddir
130      save banddir
131
132      end module radinc_h
Note: See TracBrowser for help on using the repository browser.