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

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

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


Revision 1.7 - (show annotations) (download)
Fri May 14 16:08:38 2004 UTC (20 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint53d_post, checkpoint53c_post, checkpoint53b_pre, checkpoint53b_post, checkpoint53d_pre
Changes since 1.6: +6 -2 lines
set soil wetness availability to 1. over snow covered area

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

  ViewVC Help
Powered by ViewVC 1.1.22