/[MITgcm]/MITgcm/pkg/aim_v23/aim_readparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/aim_v23/aim_readparms.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.5 - (hide annotations) (download)
Thu Jul 31 18:40:57 2003 UTC (20 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint51k_post, checkpoint52l_pre, hrcube4, hrcube5, checkpoint52d_pre, checkpoint52j_pre, checkpoint51o_pre, checkpoint51l_post, checkpoint52k_post, checkpoint52, checkpoint52f_post, checkpoint51f_post, checkpoint51t_post, checkpoint51n_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint51s_post, checkpoint51j_post, checkpoint52e_pre, checkpoint52e_post, checkpoint51n_pre, checkpoint52b_pre, checkpoint51l_pre, checkpoint51q_post, checkpoint52b_post, checkpoint52c_post, checkpoint51h_pre, checkpoint52f_pre, branchpoint-genmake2, checkpoint51r_post, checkpoint51i_post, checkpoint52d_post, checkpoint52a_pre, checkpoint52i_post, checkpoint51i_pre, checkpoint52h_pre, checkpoint52j_post, branch-netcdf, checkpoint51e_post, checkpoint51o_post, checkpoint51f_pre, checkpoint52a_post, checkpoint51g_post, ecco_c52_e35, checkpoint51m_post, checkpoint51p_post, checkpoint51u_post
Branch point for: branch-genmake2, branch-nonh, tg2-branch, netcdf-sm0, checkpoint51n_branch
Changes since 1.4: +5 -1 lines
add stratospheric drag in the upper level (new parameter: aim_dragStrato)

1 jmc 1.5 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_readparms.F,v 1.4 2003/06/12 17:59:05 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "AIM_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: AIM_READPARMS
8     C !INTERFACE:
9     SUBROUTINE AIM_READPARMS( myThid )
10    
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13     C | S/R AIM_READPARMS
14     C | o Read AIM physics package parameters
15     C *==========================================================*
16     C | Initialized parameter in common blocks:
17     C | FORCON, SFLCON, CNVCON, LSCCON, RADCON, VDICON
18     C *==========================================================*
19     C \ev
20    
21     C !USES:
22     IMPLICIT NONE
23    
24     C == Global variables ===
25     #include "AIM_SIZE.h"
26     #include "EEPARAMS.h"
27 jmc 1.4 #include "PARAMS.h"
28 jmc 1.2 #include "AIM_PARAMS.h"
29 jmc 1.1
30     C- Physical constants + functions of sigma and latitude
31     c #include "com_physcon.h"
32     C- Constants for sub-grid-scale physics
33     #include "com_forcon.h"
34     #include "com_sflcon.h"
35     #include "com_cnvcon.h"
36     #include "com_lsccon.h"
37     #include "com_radcon.h"
38     #include "com_vdicon.h"
39    
40     C !INPUT/OUTPUT PARAMETERS:
41     C == Routine Arguments ==
42     C myThid - Number of this instance
43     INTEGER myThid
44     CEOP
45    
46     #ifdef ALLOW_AIM
47    
48     C == Local Variables ==
49     C msgBuf - Informational/error meesage buffer
50     C iUnit - Work variable for IO unit number
51     CHARACTER*(MAX_LEN_MBUF) msgBuf
52     INTEGER iUnit
53    
54     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
55    
56 jmc 1.2 C-- AIM interface parameter (common AIM_PARM_?):
57     C aim_useFMsurfBC :: select surface B.C. from Franco Molteni
58     C aim_useMMsurfFc :: select Monthly Mean surface forcing (e.g., NCEP)
59     C aim_surfPotTemp :: surf.Temp input file is in Pot.Temp (aim_useMMsurfFc)
60     C aim_MMsufx :: sufix for all Monthly Mean surface forcing files
61     C aim_MMsufxLength :: Length of sufix (Monthly Mean surf. forc. files)
62     C aim_LandFile :: file name for Land fraction (F.M. surfBC)
63     C aim_albFile :: file name for Albedo input file (F.M. surfBC)
64     C aim_vegFile :: file name for vegetation fraction (F.M. surfBC)
65     C aim_sstFile :: file name for Sea.Surf.Temp (F.M. surfBC)
66     C aim_lstFile :: file name for Land.Surf.Temp (F.M. surfBC)
67     C aim_oiceFile :: file name for Sea Ice fraction (F.M. surfBC)
68     C aim_snowFile :: file name for Snow depth (F.M. surfBC)
69     C aim_swcFile :: file name for Soil Water content (F.M. surfBC)
70 jmc 1.5 C aim_dragStrato :: stratospheric-drag damping time scale (s)
71 jmc 1.3 C aim_taveFreq :: Frequency^-1 for time-average output (s)
72 jmc 1.2 C aim_diagFreq :: Frequency^-1 for diagnostic output (s)
73     C aim_tendFreq :: Frequency^-1 for tendencies output (s)
74     NAMELIST /AIM_PARAMS/
75     & aim_useFMsurfBC, aim_useMMsurfFc, aim_surfPotTemp,
76     & aim_MMsufx, aim_MMsufxLength,
77     & aim_LandFile, aim_albFile, aim_vegFile,
78     & aim_sstFile, aim_lstFile, aim_oiceFile, aim_snowFile,
79     & aim_swcFile,
80 jmc 1.5 & aim_dragStrato,
81 jmc 1.3 & aim_taveFreq, aim_diagFreq, aim_tendFreq
82 jmc 1.2
83 jmc 1.1 C-- Physical constants (common PHYCON) :
84     C P0 = reference pressure
85     C GG = gravity accel.
86     C RD = gas constant for dry air
87     C CP = specific heat at constant pressure
88     C ALHC = latent heat of condensation
89     C SBC = Stefan-Boltzmann constant
90    
91     C-- Constants for forcing fields (common FORCON) :
92     C SOLC = Solar constant (area averaged) in W/m^2
93     C ALBSEA = Albedo over sea
94     C ALBICE = Albedo over sea ice (for ice fraction = 1)
95     C ALBSN = Albedo over snow (for snow depth > SDALB)
96     C SDALB = Snow depth (mm water) corresponding to maximum albedo
97     C SWCAP = Soil wetness at field capacity (volume fraction)
98     C SWWIL = Soil wetness at wilting point (volume fraction)
99     NAMELIST /AIM_PAR_FOR/
100     & SOLC, ALBSEA, ALBICE, ALBSN,
101     & SDALB, SWCAP, SWWIL
102    
103     C-- Constants for surface fluxes (common SFLCON) :
104     C FWIND0 = ratio of near-sfc wind to lowest-level wind
105     C FTEMP0 = weight for near-sfc temperature extrapolation (0-1) :
106     C 1 : linear extrapolation from two lowest levels
107     C 0 : constant potential temperature ( = lowest level)
108     C FHUM0 = weight for near-sfc specific humidity extrapolation (0-1) :
109     C 1 : extrap. with constant relative hum. ( = lowest level)
110     C 0 : constant specific hum. ( = lowest level)
111     C CDL = drag coefficient for momentum over land
112     C CDS = drag coefficient for momentum over sea
113     C CHL = heat exchange coefficient over land
114     C CHS = heat exchange coefficient over sea
115     C VGUST = wind speed for sub-grid-scale gusts
116     C CTDAY = daily-cycle correction (dTskin/dSSRad)
117     C DTHETA = Potential temp. gradient for stability correction
118     C FSTAB = Amplitude of stability correction (fraction)
119     C HDRAG = Height scale for orographic correction
120     C FHDRAG = Amplitude of orographic correction (fraction)
121     NAMELIST /AIM_PAR_SFL/
122     & FWIND0, FTEMP0, FHUM0,
123     & CDL, CDS, CHL, CHS, VGUST, CTDAY,
124     & DTHETA, FSTAB, HDRAG, FHDRAG
125    
126     C-- Convection constants (common CNVCON) :
127     C PSMIN = minimum (norm.) sfc. pressure for the occurrence of convection
128     C TRCNV = time of relaxation (in hours) towards reference state
129     C QBL = specific hum. threshold in the boundary layer
130     C RHBL = relative hum. threshold in the boundary layer
131     C RHIL = rel. hum. threshold in intermed. layers for secondary mass flux
132     C ENTMAX = max. entrainment as a fraction of cloud-base mass flux
133     C SMF = ratio between secondary and primary mass flux at cloud-base
134     NAMELIST /AIM_PAR_CNV/
135     & PSMIN, TRCNV, QBL, RHBL, RHIL, ENTMAX, SMF
136    
137    
138     C-- Constants for large-scale condendation (common LSCCON) :
139     C TRLSC = Relaxation time (in hours) for specific humidity
140     C RHLSC = Maximum relative humidity threshold (at sigma=1)
141     C DRHLSC = Vertical range of relative humidity threshold
142     C QSMAX = used to define the maximum latent heat release
143     NAMELIST /AIM_PAR_LSC/
144     & TRLSC, RHLSC, DRHLSC, QSMAX
145    
146     C-- Radiation constants (common RADCON) :
147     C RHCL1 = relative hum. corresponding to cloud cover = 0
148     C RHCL2 = relative hum. corresponding to cloud cover = 1
149     C QACL1 = specific hum. threshold for cloud cover in the upper troposphere
150     C QACL2 = specific hum. threshold for cloud cover in the upper troposphere
151     C ALBCL = cloud albedo (for cloud cover = 1)
152     C EPSSW = fraction of incoming solar radiation absorbed by ozone
153     C EPSLW = fraction of surface LW radiation emitted directly to space
154     C EMISFC = longwave surface emissivity
155     C--: shortwave absorptivities (for dp = 10^5 Pa) :
156     C ABSDRY = abs. of dry air (visible band)
157     C ABSAER = abs. of aerosols (visible band)
158     C ABSWV1 = abs. of water vapour (visible band, for dq = 1 g/kg)
159     C ABSWV2 = abs. of water vapour (near IR band, for dq = 1 g/kg)
160     C ABSCL1 = abs. of clouds (visible band, constant term)
161     C ABSCL2 = abs. of clouds (visible band, for dw = 1 g/kg)
162     C--: longwave absorptivities (per dp = 10^5 Pa) :
163     C ABLWIN = abs. of air in "window" band
164     C ABLCO2 = abs. of air in CO2 band
165     C ABLWV1 = abs. of water vapour in H2O band 1 (weak), for dq = 1 g/kg
166     C ABLWV2 = abs. of water vapour in H2O band 2 (strong), for dq = 1 g/kg
167     C ABLCL1 = abs. of clouds in "window" band, constant term
168     C ABLCL2 = abs. of clouds in "window" band, for dw = 1 g/kg
169     NAMELIST /AIM_PAR_RAD/
170     & RHCL1, RHCL2, QACL1, QACL2, ALBCL,
171     & EPSSW, EPSLW, EMISFC,
172     & ABSDRY, ABSAER, ABSWV1, ABSWV2, ABSCL1, ABSCL2,
173     & ABLWIN, ABLCO2, ABLWV1, ABLWV2, ABLCL1, ABLCL2
174    
175     C-- Constants for vertical dif. and sh. conv. (common VDICON) :
176     C TRSHC = relaxation time (in hours) for shallow convection
177     C TRVDI = relaxation time (in hours) for moisture diffusion
178     C TRVDS = relaxation time (in hours) for super-adiab. conditions
179     C RHGRAD = maximum gradient of relative humidity (d_RH/d_sigma)
180     C SEGRAD = minimum gradient of dry static energy (d_DSE/d_phi)
181     NAMELIST /AIM_PAR_VDI/
182     & TRSHC, TRVDI, TRVDS, RHGRAD, SEGRAD
183    
184     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
185    
186     _BEGIN_MASTER(myThid)
187    
188     WRITE(msgBuf,'(A)') ' AIM_READ_PHYSPARMS: opening data.aimphys'
189     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
190    
191     CALL OPEN_COPY_DATA_FILE( 'data.aimphys', 'AIM_READ_PHYSPARMS',
192     O iUnit, myThid )
193    
194     C-- Read parameters from open data file:
195    
196 jmc 1.2 C- Parameters for AIM interface code:
197     READ(UNIT=iUnit,NML=AIM_PARAMS)
198    
199 jmc 1.1 C- Constants for boundary forcing
200     READ(UNIT=iUnit,NML=AIM_PAR_FOR)
201    
202     C- Constants for surface fluxes
203     READ(UNIT=iUnit,NML=AIM_PAR_SFL)
204    
205     C- Constants for convection
206     READ(UNIT=iUnit,NML=AIM_PAR_CNV)
207    
208     C- Constants for large-scale condensation
209     READ(UNIT=iUnit,NML=AIM_PAR_LSC)
210    
211     C- Constants for radiation
212     READ(UNIT=iUnit,NML=AIM_PAR_RAD)
213    
214     C- Constants for vertical diffusion and sh. conv.
215     READ(UNIT=iUnit,NML=AIM_PAR_VDI)
216    
217     WRITE(msgBuf,'(A)')
218     & ' AIM_READ_PHYSPARMS: finished reading data.aimphys'
219     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
220    
221     C-- Close the open data file
222     CLOSE(iUnit)
223    
224     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
225 jmc 1.3 C-- Check parameters and model configuration
226    
227     C- If aim_taveFreq is positive, then must compile the aim-diagnostics code
228     #ifndef ALLOW_AIM_TAVE
229     IF (aim_taveFreq.GT.0.) THEN
230     WRITE(msgBuf,'(A)')
231     & 'AIM_READPARMS: aim_taveFreq > 0 but ALLOW_AIM_TAVE undefined'
232     CALL PRINT_ERROR( msgBuf, myThid)
233     WRITE(msgBuf,'(2A)')
234     & 'Re-compile with: #define ALLOW_AIM_TAVE',
235     & ' or -DALLOW_AIM_TAVE'
236     CALL PRINT_ERROR( msgBuf, myThid)
237     STOP 'ABNORMAL END: S/R AIM_READPARMS'
238     ENDIF
239     #endif /* ALLOW_AIM_TAVE */
240    
241     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
242 jmc 1.1 C-- Print out parameter values :
243    
244     WRITE(msgBuf,'(A)') ' '
245     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
246     WRITE(msgBuf,'(A)') '// ==================================='
247     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
248     WRITE(msgBuf,'(A)') '// AIM physics parameters :'
249     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
250     WRITE(msgBuf,'(A)') '// ==================================='
251     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
252 jmc 1.4
253     CALL WRITE_0D_L( useLand, INDEX_NONE,
254     & 'useLand =',
255     &' /* use Land package for surf.BC over land */')
256 jmc 1.2
257     C- namelist AIM_PARAMS:
258     CALL WRITE_0D_L( aim_useFMsurfBC, INDEX_NONE,
259     & 'aim_useFMsurfBC =',
260     &' /* F.Molteni surf. BC scheme on/off flag */')
261     CALL WRITE_0D_L( aim_useMMsurfFc, INDEX_NONE,
262     & 'aim_useMMsurfFc =',
263     &' /* Monthly Mean surf. Forcing on/off flag */')
264     CALL WRITE_0D_L( aim_surfPotTemp, INDEX_NONE,
265     & 'aim_surfPotTemp =',
266     &' /* Surf Temp file in Pot.Temp on/off flag */')
267 jmc 1.5 CALL WRITE_0D_R8(aim_dragStrato,INDEX_NONE,'aim_dragStrato=',
268     & ' /* stratospheric-drag damping time scale (s) */')
269 jmc 1.3 CALL WRITE_0D_R8( aim_taveFreq, INDEX_NONE,'aim_taveFreq =',
270     & ' /* Frequency^-1 for time-Aver. output (s) */')
271 jmc 1.2 CALL WRITE_0D_R8( aim_diagFreq, INDEX_NONE,'aim_diagFreq =',
272     & ' /* Frequency^-1 for diagnostic output (s) */')
273     CALL WRITE_0D_R8( aim_tendFreq, INDEX_NONE,'aim_tendFreq =',
274     & ' /* Frequency^-1 for tendencies output (s) */')
275 jmc 1.1
276     C- namelist AIM_PAR_FOR:
277     CALL WRITE_0D_R8( SOLC, INDEX_NONE,'AIM_FOR: SOLC =',
278     & ' /* Solar constant (area averaged) in W/m2 */')
279     CALL WRITE_0D_R8( ALBSEA,INDEX_NONE,'AIM_FOR: ALBSEA =',
280     & ' /* Albedo over sea [0-1] */')
281     CALL WRITE_0D_R8( ALBICE,INDEX_NONE,'AIM_FOR: ALBICE =',
282     & ' /* Albedo over sea ice (for ice fraction =1) */')
283     CALL WRITE_0D_R8( ALBSN, INDEX_NONE,'AIM_FOR: ALBSN =',
284     & ' /* Albedo over snow (for snow depth > SDALB) */')
285     CALL WRITE_0D_R8( SDALB, INDEX_NONE,'AIM_FOR: SDALB =',
286     & ' /* Snow depth (mm H2O) corresp. maximum albedo */')
287     CALL WRITE_0D_R8( SWCAP, INDEX_NONE,'AIM_FOR: SWCAP =',
288     & ' /* Soil wetness at field capacity (Vol.fract.) */')
289     CALL WRITE_0D_R8( SWWIL, INDEX_NONE,'AIM_FOR: SWWIL =',
290     & ' /* Soil wetness at wilting point (Vol.fract.) */')
291    
292     C- namelist AIM_PAR_SFL:
293     CALL WRITE_0D_R8( FWIND0,INDEX_NONE,'AIM_SFL: FWIND0 =',
294     & ' /* ratio of near-sfc wind to lowest-level wind */')
295     CALL WRITE_0D_R8( FTEMP0,INDEX_NONE,'AIM_SFL: FTEMP0 =',
296     & ' /* weight for near-sfc temp. extrapolation (0-1)*/')
297     CALL WRITE_0D_R8( FHUM0, INDEX_NONE,'AIM_SFL: FHUM0 =',
298     & ' /* weight for near-sfc spec.humid. extrap. (0-1)*/')
299     CALL WRITE_0D_R8( CDL, INDEX_NONE,'AIM_SFL: CDL =',
300     & ' /* drag coefficient for momentum over land */')
301     CALL WRITE_0D_R8( CDS, INDEX_NONE,'AIM_SFL: CDS =',
302     & ' /* drag coefficient for momentum over sea */')
303     CALL WRITE_0D_R8( CHL, INDEX_NONE,'AIM_SFL: CHL =',
304     & ' /* heat exchange coefficient over land */')
305     CALL WRITE_0D_R8( CHS, INDEX_NONE,'AIM_SFL: CHS =',
306     & ' /* heat exchange coefficient over sea */')
307     CALL WRITE_0D_R8( VGUST, INDEX_NONE,'AIM_SFL: VGUST =',
308     & ' /* wind speed [m/s] for sub-grid-scale gusts */')
309     CALL WRITE_0D_R8( CTDAY, INDEX_NONE,'AIM_SFL: CTDAY =',
310     & ' /* daily-cycle correction (dTskin/dSSRad) */')
311     CALL WRITE_0D_R8( DTHETA,INDEX_NONE,'AIM_SFL: DTHETA =',
312     & ' /* Pot.Temp. gradient for stability correction */')
313     CALL WRITE_0D_R8( FSTAB, INDEX_NONE,'AIM_SFL: FSTAB =',
314     & ' /* Amplitude of stability correction (fract.) */')
315     CALL WRITE_0D_R8( HDRAG, INDEX_NONE,'AIM_SFL: HDRAG =',
316     & ' /* Height scale for orographic correction */')
317     CALL WRITE_0D_R8( FHDRAG,INDEX_NONE,'AIM_SFL: FHDRAG =',
318     & ' /* Amplitude of orographic correction (fract.)*/')
319    
320     C- namelist AIM_PAR_CNV:
321     CALL WRITE_0D_R8( PSMIN, INDEX_NONE,'AIM_CNV: PSMIN =',
322     & ' /* min norm.sfc.P. for occurrence of convect. */')
323     CALL WRITE_0D_R8( TRCNV, INDEX_NONE,'AIM_CNV: TRCNV =',
324     & ' /* time of relaxation [h] towards ref state */')
325     CALL WRITE_0D_R8( QBL, INDEX_NONE,'AIM_CNV: QBL =',
326     & ' /* specific hum. threshold in the Bound.layer */')
327     CALL WRITE_0D_R8( RHBL, INDEX_NONE,'AIM_CNV: RHBL =',
328     & ' /* relative hum. threshold in the Bound.layer */')
329     CALL WRITE_0D_R8( RHIL, INDEX_NONE,'AIM_CNV: RHIL =',
330     & ' /* rel.hum. threshold (intern) for 2nd mass.Flx*/')
331     CALL WRITE_0D_R8( ENTMAX,INDEX_NONE,'AIM_CNV: ENTMAX =',
332     & ' /* time of relaxation [h] towards neutral eq. */')
333     CALL WRITE_0D_R8( SMF, INDEX_NONE,'AIM_CNV: SMF =',
334     & ' /* ratio 2ndary/primary mass.Flx at cloud-base*/')
335    
336     C- namelist AIM_PAR_LSC:
337     CALL WRITE_0D_R8( TRLSC, INDEX_NONE,'AIM_LSC: TRLSC =',
338     & ' /* relaxation time [h] for supersat. spec.hum. */')
339     CALL WRITE_0D_R8( RHLSC, INDEX_NONE,'AIM_LSC: RHLSC =',
340     & ' /* Max rel.humidity threshold (at sigma=1) */')
341     CALL WRITE_0D_R8( DRHLSC,INDEX_NONE,'AIM_LSC: DRHLSC =',
342     & ' /* Vertical range of rel.humidity threshold */')
343     CALL WRITE_0D_R8( QSMAX, INDEX_NONE,'AIM_LSC: QSMAX =',
344     & ' /* Define the maximum latent heat release */')
345    
346     C- namelist AIM_PAR_RAD:
347     CALL WRITE_0D_R8( RHCL1, INDEX_NONE,'AIM_RAD: RHCL1 =',
348     & ' /* rel.hum. corresponding to cloud cover = 0 */')
349     CALL WRITE_0D_R8( RHCL2, INDEX_NONE,'AIM_RAD: RHCL2 =',
350     & ' /* rel.hum. corresponding to cloud cover = 1 */')
351     CALL WRITE_0D_R8( QACL1, INDEX_NONE,'AIM_RAD: QACL1 =',
352     & ' /* spec.hum. threshold for cloud, upper trop. */')
353     CALL WRITE_0D_R8( QACL2, INDEX_NONE,'AIM_RAD: QACL2 =',
354     & ' /* spec.hum. threshold for cloud, upper trop. */')
355     CALL WRITE_0D_R8( ALBCL, INDEX_NONE,'AIM_RAD: ALBCL =',
356     & ' /* cloud albedo (for cloud cover = 1) */')
357     CALL WRITE_0D_R8( EPSSW, INDEX_NONE,'AIM_RAD: EPSSW =',
358     & ' /* fract. of inc.solar rad. absorbed by ozone */')
359     CALL WRITE_0D_R8( EPSLW, INDEX_NONE,'AIM_RAD: EPSLW =',
360     & ' /* fract. of sfc LW emitted directly to space */')
361     CALL WRITE_0D_R8( EMISFC,INDEX_NONE,'AIM_RAD: EMISFC =',
362     & ' /* longwave surface emissivity */')
363    
364     WRITE(msgBuf,'(A)')
365     & ' AIM_RAD : ShortWave absorptivities (for dp = 10^5 Pa) :'
366     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
367     CALL WRITE_0D_R8( ABSDRY,INDEX_NONE,'AIM_RAD: ABSDRY =',
368     & ' /* abs. of dry air (visible band) */')
369     CALL WRITE_0D_R8( ABSAER,INDEX_NONE,'AIM_RAD: ABSAER =',
370     & ' /* abs. of aerosols (visible band) */')
371     CALL WRITE_0D_R8( ABSWV1,INDEX_NONE,'AIM_RAD: ABSWV1 =',
372     & ' /* abs. of water vap. (vis. band)(/dq, 1g/kg) */')
373     CALL WRITE_0D_R8( ABSWV1,INDEX_NONE,'AIM_RAD: ABSWV1 =',
374     & ' /* abs. of water vap. (vis. band)(/dq, 1g/kg) */')
375     CALL WRITE_0D_R8( ABSWV2,INDEX_NONE,'AIM_RAD: ABSWV2 =',
376     & ' /* abs. of water vap.(near IR bd)(/dq, 1g/kg) */')
377     CALL WRITE_0D_R8( ABSCL1,INDEX_NONE,'AIM_RAD: ABSCL1 =',
378     & ' /* abs. of clouds (vis.band)(constant term) */')
379     CALL WRITE_0D_R8( ABSCL2,INDEX_NONE,'AIM_RAD: ABSCL2 =',
380     & ' /* abs. of clouds (vis.band) (/dw, 1g/kg) */')
381    
382     WRITE(msgBuf,'(A)')
383     & ' AIM_RAD : LongWave absorptivities (per dp = 10^5 Pa) :'
384     CALL WRITE_0D_R8( ABLWIN,INDEX_NONE,'AIM_RAD: ABLWIN =',
385     & ' /* abs. of air in "window" band */')
386     CALL WRITE_0D_R8( ABLCO2,INDEX_NONE,'AIM_RAD: ABLCO2 =',
387     & ' /* abs. of air in CO2 band */')
388     CALL WRITE_0D_R8( ABLWV1,INDEX_NONE,'AIM_RAD: ABLWV1 =',
389     & ' /* abs. of Water vap. H2O bd-1(weak)(/dq,1g/kg)*/')
390     CALL WRITE_0D_R8( ABLWV2,INDEX_NONE,'AIM_RAD: ABLWV2 =',
391     & ' /* abs. of W. vap., H2O bd-2(strong)(/dq,1g/kg)*/')
392     CALL WRITE_0D_R8( ABLCL1,INDEX_NONE,'AIM_RAD: ABLCL1 =',
393     & ' /* abs. of clouds in window band (const term) */')
394     CALL WRITE_0D_R8( ABLCL2,INDEX_NONE,'AIM_RAD: ABLCL2 =',
395     & ' /* abs. of clouds in window band (/dw, 1g/kg) */')
396    
397     C- namelist AIM_PAR_VDI:
398     CALL WRITE_0D_R8( TRSHC, INDEX_NONE,'AIM_VDI: TRSHC =',
399     & ' /* relaxation time [h] for shallow convection */')
400     CALL WRITE_0D_R8( TRVDI, INDEX_NONE,'AIM_VDI: TRVDI =',
401     & ' /* relaxation time [h] for moisture diffusion */')
402     CALL WRITE_0D_R8( TRVDS, INDEX_NONE,'AIM_VDI: TRVDS =',
403     & ' /* relaxation time [h] for super-adiab. cond. */')
404     CALL WRITE_0D_R8( RHGRAD,INDEX_NONE,'AIM_VDI: RHGRAD =',
405     & ' /* max gradient of rel.humidity (d_RH/d_sigma)*/')
406     CALL WRITE_0D_R8( RHGRAD,INDEX_NONE,'AIM_VDI: RHGRAD =',
407     & ' /* max grad. of dry static Energy(d_DSE/d_phi)*/')
408    
409     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
410    
411     _END_MASTER(myThid)
412    
413     C-- Everyone else must wait for the parameters to be loaded
414     _BARRIER
415    
416     #endif /* ALLOW_AIM */
417    
418     RETURN
419     END

  ViewVC Help
Powered by ViewVC 1.1.22