/[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.16 - (show annotations) (download)
Tue Apr 28 23:27:24 2009 UTC (15 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61n, checkpoint61o, checkpoint61m, checkpoint61p
Changes since 1.15: +66 -66 lines
call WRITE_0D_RL (instead of WRITE_0D_R8) to print "RL" parameters

1 C $Header: /u/gcmpack/MITgcm/pkg/aim_v23/aim_readparms.F,v 1.15 2009/01/05 15:15:33 dfer 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 #ifdef ALLOW_MNC
30 #include "MNC_PARAMS.h"
31 #endif
32 #ifdef ALLOW_AIM_CO2
33 #include "AIM_CO2.h"
34 #endif
35
36
37 C- Physical constants + functions of sigma and latitude
38 c #include "com_physcon.h"
39 C- Constants for sub-grid-scale physics
40 #include "com_forcon.h"
41 #include "com_sflcon.h"
42 #include "com_cnvcon.h"
43 #include "com_lsccon.h"
44 #include "com_radcon.h"
45 #include "com_vdicon.h"
46
47 C !INPUT/OUTPUT PARAMETERS:
48 C == Routine Arguments ==
49 C myThid :: my Thread Id number
50 INTEGER myThid
51 CEOP
52
53 #ifdef ALLOW_AIM
54
55 C == Local Variables ==
56 C msgBuf :: Informational/error meesage buffer
57 C iUnit :: Work variable for IO unit number
58 CHARACTER*(MAX_LEN_MBUF) msgBuf
59 INTEGER iUnit
60
61 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
62
63 C-- AIM interface parameter (common AIM_PARM_?):
64 C aim_useFMsurfBC :: select surface B.C. from Franco Molteni
65 C aim_useMMsurfFc :: select Monthly Mean surface forcing (e.g., NCEP)
66 C aim_surfForc_TimePeriod :: Length of forcing time period (e.g. 1 month)
67 C aim_surfForc_NppCycle :: Number of time period per Cycle (e.g. 12)
68 C aim_surfForc_TransRatio :: transition ratio from one month to the next
69 C aim_surfPotTemp :: surf.Temp input file is in Pot.Temp (aim_useMMsurfFc)
70 C aim_energPrecip :: account for energy of precipitation (snow & rain temp)
71 C aim_splitSIOsFx :: compute separately Sea-Ice & Ocean surf. Flux
72 C (also land SW & LW) ; default=F as in original version
73 C aim_MMsufx :: sufix for all Monthly Mean surface forcing files
74 C aim_MMsufxLength :: Length of sufix (Monthly Mean surf. forc. files)
75 C aim_LandFile :: file name for Land fraction (F.M. surfBC)
76 C aim_albFile :: file name for Albedo input file (F.M. surfBC)
77 C aim_vegFile :: file name for vegetation fraction (F.M. surfBC)
78 C aim_sstFile :: file name for Sea.Surf.Temp (F.M. surfBC)
79 C aim_lstFile :: file name for Land.Surf.Temp (F.M. surfBC)
80 C aim_oiceFile :: file name for Sea Ice fraction (F.M. surfBC)
81 C aim_snowFile :: file name for Snow depth (F.M. surfBC)
82 C aim_swcFile :: file name for Soil Water content (F.M. surfBC)
83 C aim_dragStrato :: stratospheric-drag damping time scale (s)
84 C aim_clrSkyDiag :: compute clear-sky radiation for diagnostics
85 C aim_taveFreq :: Frequency^-1 for time-average output (s)
86 C aim_diagFreq :: Frequency^-1 for diagnostic output (s)
87 C aim_tendFreq :: Frequency^-1 for tendencies output (s)
88 C aim_selectOceAlbedo :: Ocean albedo(latitude) scheme (integer)
89 C 0 = constant (default)
90 C 1 = Briegleb et al. 1986
91 NAMELIST /AIM_PARAMS/
92 & aim_useFMsurfBC, aim_useMMsurfFc,
93 & aim_surfForc_TimePeriod, aim_surfForc_NppCycle,
94 & aim_surfForc_TransRatio, aim_surfPotTemp,
95 & aim_energPrecip, aim_splitSIOsFx,
96 & aim_MMsufx, aim_MMsufxLength,
97 & aim_LandFile, aim_albFile, aim_vegFile,
98 & aim_sstFile, aim_lstFile, aim_oiceFile, aim_snowFile,
99 & aim_swcFile,
100 & aim_dragStrato,
101 & aim_clrSkyDiag, aim_taveFreq, aim_diagFreq, aim_tendFreq,
102 & aim_timeave_mnc, aim_snapshot_mnc,
103 & aim_pickup_write_mnc, aim_pickup_read_mnc,
104 & aim_selectOceAlbedo
105
106 C-- Physical constants (common PHYCON) :
107 C P0 = reference pressure [Pa=N/m2]
108 C GG = gravity accel. [m/s2]
109 C RD = gas constant for dry air [J/kg/K]
110 C CP = specific heat at constant pressure [J/kg/K]
111 C ALHC = latent heat of condensation [J/g]
112 C ALHF = latent heat of freezing [J/g]
113 C SBC = Stefan-Boltzmann constant
114 C rainCP = heat capacity of liquid water [J/g/K]
115 C tFreeze = freezing temperature of pure water [K]
116
117 C-- Constants for forcing fields (common FORCON) :
118 C SOLC = Solar constant (area averaged) in W/m^2
119 C ALBSEA = Albedo over sea
120 C ALBICE = Albedo over sea ice (for ice fraction = 1)
121 C ALBSN = Albedo over snow (for snow depth > SDALB)
122 C SDALB = Snow depth (mm water) corresponding to maximum albedo
123 C SWCAP = Soil wetness at field capacity (volume fraction)
124 C SWWIL = Soil wetness at wilting point (volume fraction)
125 C hSnowWetness :: snow depth (m) corresponding to maximum wetness
126 NAMELIST /AIM_PAR_FOR/
127 & SOLC, ALBSEA, ALBICE, ALBSN,
128 & SDALB, SWCAP, SWWIL, hSnowWetness
129
130 C-- Constants for surface fluxes (common SFLCON) :
131 C FWIND0 = ratio of near-sfc wind to lowest-level wind
132 C FTEMP0 = weight for near-sfc temperature extrapolation (0-1) :
133 C 1 : linear extrapolation from two lowest levels
134 C 0 : constant potential temperature ( = lowest level)
135 C FHUM0 = weight for near-sfc specific humidity extrapolation (0-1) :
136 C 1 : extrap. with constant relative hum. ( = lowest level)
137 C 0 : constant specific hum. ( = lowest level)
138 C CDL = drag coefficient for momentum over land
139 C CDS = drag coefficient for momentum over sea
140 C CHL = heat exchange coefficient over land
141 C CHS = heat exchange coefficient over sea
142 C VGUST = wind speed for sub-grid-scale gusts
143 C CTDAY = daily-cycle correction (dTskin/dSSRad)
144 C DTHETA = Potential temp. gradient for stability correction
145 C dTstab = potential temp. increment for stability function derivative
146 C FSTAB = Amplitude of stability correction (fraction)
147 C HDRAG = Height scale for orographic correction
148 C FHDRAG = Amplitude of orographic correction (fraction)
149 NAMELIST /AIM_PAR_SFL/
150 & FWIND0, FTEMP0, FHUM0,
151 & CDL, CDS, CHL, CHS, VGUST, CTDAY,
152 & DTHETA, dTstab, FSTAB, HDRAG, FHDRAG
153
154 C-- Convection constants (common CNVCON) :
155 C PSMIN = minimum (norm.) sfc. pressure for the occurrence of convection
156 C TRCNV = time of relaxation (in hours) towards reference state
157 C QBL = specific hum. threshold in the boundary layer
158 C RHBL = relative hum. threshold in the boundary layer
159 C RHIL = rel. hum. threshold in intermed. layers for secondary mass flux
160 C ENTMAX = max. entrainment as a fraction of cloud-base mass flux
161 C SMF = ratio between secondary and primary mass flux at cloud-base
162 NAMELIST /AIM_PAR_CNV/
163 & PSMIN, TRCNV, QBL, RHBL, RHIL, ENTMAX, SMF
164
165
166 C-- Constants for large-scale condendation (common LSCCON) :
167 C TRLSC = Relaxation time (in hours) for specific humidity
168 C RHLSC = Maximum relative humidity threshold (at sigma=1)
169 C DRHLSC = Vertical range of relative humidity threshold
170 C QSMAX = used to define the maximum latent heat release
171 NAMELIST /AIM_PAR_LSC/
172 & TRLSC, RHLSC, DRHLSC, QSMAX
173
174 C-- Radiation constants (common RADCON) :
175 C RHCL1 = relative hum. corresponding to cloud cover = 0
176 C RHCL2 = relative hum. corresponding to cloud cover = 1
177 C QACL1 = specific hum. threshold for cloud cover in the upper troposphere
178 C QACL2 = specific hum. threshold for cloud cover in the upper troposphere
179 C ALBCL = cloud albedo (for cloud cover = 1)
180 C EPSSW = fraction of incoming solar radiation absorbed by ozone
181 C EPSLW = fraction of surface LW radiation emitted directly to space
182 C EMISFC = longwave surface emissivity
183 C--: shortwave absorptivities (for dp = 10^5 Pa) :
184 C ABSDRY = abs. of dry air (visible band)
185 C ABSAER = abs. of aerosols (visible band)
186 C ABSWV1 = abs. of water vapour (visible band, for dq = 1 g/kg)
187 C ABSWV2 = abs. of water vapour (near IR band, for dq = 1 g/kg)
188 C ABSCL1 = abs. of clouds (visible band, constant term)
189 C ABSCL2 = abs. of clouds (visible band, for dw = 1 g/kg)
190 C--: longwave absorptivities (per dp = 10^5 Pa) :
191 C ABLWIN = abs. of air in "window" band
192 C ABLCO2 = abs. of air in CO2 band
193 C ABLWV1 = abs. of water vapour in H2O band 1 (weak), for dq = 1 g/kg
194 C ABLWV2 = abs. of water vapour in H2O band 2 (strong), for dq = 1 g/kg
195 C ABLCL1 = abs. of clouds in "window" band, constant term
196 C ABLCL2 = abs. of clouds in "window" band, for dw = 1 g/kg
197 NAMELIST /AIM_PAR_RAD/
198 & RHCL1, RHCL2, QACL1, QACL2, ALBCL,
199 & EPSSW, EPSLW, EMISFC,
200 & ABSDRY, ABSAER, ABSWV1, ABSWV2, ABSCL1, ABSCL2,
201 & ABLWIN, ABLCO2, ABLWV1, ABLWV2, ABLCL1, ABLCL2
202
203 C-- Constants for vertical dif. and sh. conv. (common VDICON) :
204 C TRSHC = relaxation time (in hours) for shallow convection
205 C TRVDI = relaxation time (in hours) for moisture diffusion
206 C TRVDS = relaxation time (in hours) for super-adiab. conditions
207 C RHGRAD = maximum gradient of relative humidity (d_RH/d_sigma)
208 C SEGRAD = minimum gradient of dry static energy (d_DSE/d_phi)
209 NAMELIST /AIM_PAR_VDI/
210 & TRSHC, TRVDI, TRVDS, RHGRAD, SEGRAD
211
212 #ifdef ALLOW_AIM_CO2
213 NAMELIST /AIM_PAR_CO2/ atm_pCO2, Aim_CO2_Flag
214 #endif
215
216 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
217
218 _BEGIN_MASTER(myThid)
219
220 C-- Set default value for AIM interface code (AIM_PARAMS.h):
221 aim_useFMsurfBC = .TRUE.
222 aim_useMMsurfFc = .FALSE.
223 aim_surfPotTemp = .FALSE.
224 aim_energPrecip = .FALSE.
225 aim_splitSIOsFx = .FALSE.
226 aim_clrSkyDiag = .FALSE.
227 #ifdef ALLOW_MNC
228 aim_timeave_mnc = timeave_mnc .AND. useMNC
229 aim_snapshot_mnc = snapshot_mnc .AND. useMNC
230 aim_pickup_write_mnc = pickup_write_mnc .AND. useMNC
231 aim_pickup_read_mnc = pickup_read_mnc .AND. useMNC
232 #else
233 aim_timeave_mnc = .FALSE.
234 aim_snapshot_mnc = .FALSE.
235 aim_pickup_write_mnc = .FALSE.
236 aim_pickup_read_mnc = .FALSE.
237 #endif
238 aim_MMsufx = '.bin'
239 aim_MMsufxLength = 4
240 C- Length (s) of one time period:
241 aim_surfForc_TimePeriod = 30.*86400.
242 C- Number of time period per Cycle:
243 aim_surfForc_NppCycle = 12
244 aim_selectOceAlbedo = 0
245 C- define how fast the (linear) transition is from one month to the next
246 C = 1 -> linear between 2 midle month
247 C > TimePeriod/deltaT -> jump from one month to the next one
248 aim_surfForc_TransRatio = 1.
249 aim_LandFile = ' '
250 aim_albFile = ' '
251 aim_vegFile = ' '
252 aim_sstFile = ' '
253 aim_lstFile = ' '
254 aim_oiceFile = ' '
255 aim_snowFile = ' '
256 aim_swcFile = ' '
257 aim_dragStrato = 0.
258 aim_taveFreq = taveFreq
259 aim_diagFreq = dumpFreq
260 aim_tendFreq = 0.
261 #ifdef ALLOW_AIM_CO2
262 atm_pCO2 = 326. _d -6
263 Aim_CO2_Flag = 1
264 #endif
265
266 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
267
268 WRITE(msgBuf,'(A)') ' AIM_READ_PHYSPARMS: opening data.aimphys'
269 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
270
271 CALL OPEN_COPY_DATA_FILE( 'data.aimphys', 'AIM_READ_PHYSPARMS',
272 O iUnit, myThid )
273
274 C-- Read parameters from open data file:
275
276 C- Parameters for AIM interface code:
277 READ(UNIT=iUnit,NML=AIM_PARAMS)
278
279 C- Constants for boundary forcing
280 READ(UNIT=iUnit,NML=AIM_PAR_FOR)
281
282 C- Constants for surface fluxes
283 READ(UNIT=iUnit,NML=AIM_PAR_SFL)
284
285 C- Constants for convection
286 READ(UNIT=iUnit,NML=AIM_PAR_CNV)
287
288 C- Constants for large-scale condensation
289 READ(UNIT=iUnit,NML=AIM_PAR_LSC)
290
291 C- Constants for radiation
292 READ(UNIT=iUnit,NML=AIM_PAR_RAD)
293
294 C- Constants for vertical diffusion and sh. conv.
295 READ(UNIT=iUnit,NML=AIM_PAR_VDI)
296
297 #ifdef ALLOW_AIM_CO2
298 C- Constants for CO2
299 READ(UNIT=iUnit,NML=AIM_PAR_CO2)
300 #endif
301
302 WRITE(msgBuf,'(A)')
303 & ' AIM_READ_PHYSPARMS: finished reading data.aimphys'
304 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
305
306 C-- Close the open data file
307 CLOSE(iUnit)
308
309 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
310 C-- Check parameters and model configuration
311
312 #ifndef ALLOW_CLR_SKY_DIAG
313 C- If aim_clrSkyDiag is set, then must compile the Clear-Sky Diagnostic code
314 IF ( aim_clrSkyDiag ) THEN
315 WRITE(msgBuf,'(A)')
316 & 'AIM_READPARMS: aim_clrSkyDiag=T but ALLOW_CLR_SKY_DIAG undef'
317 CALL PRINT_ERROR( msgBuf, myThid)
318 WRITE(msgBuf,'(2A)')
319 & 'Re-compile with: #define ALLOW_CLR_SKY_DIAG (AIM_OPTIONS.h)'
320 CALL PRINT_ERROR( msgBuf, myThid)
321 STOP 'ABNORMAL END: S/R AIM_READPARMS'
322 ENDIF
323 #endif
324
325 C- If aim_taveFreq is positive, then must compile the aim-diagnostics code
326 #ifndef ALLOW_AIM_TAVE
327 IF (aim_taveFreq.GT.0.) THEN
328 WRITE(msgBuf,'(A)')
329 & 'AIM_READPARMS: aim_taveFreq > 0 but ALLOW_AIM_TAVE undefined'
330 CALL PRINT_ERROR( msgBuf, myThid)
331 WRITE(msgBuf,'(2A)')
332 & 'Re-compile with: #define ALLOW_AIM_TAVE (AIM_OPTIONS.h)'
333 CALL PRINT_ERROR( msgBuf, myThid)
334 STOP 'ABNORMAL END: S/R AIM_READPARMS'
335 ENDIF
336 #endif /* ALLOW_AIM_TAVE */
337
338 #ifdef ALLOW_MNC
339 aim_timeave_mnc = useMNC .AND. aim_timeave_mnc
340 aim_snapshot_mnc = useMNC .AND. aim_snapshot_mnc
341 aim_pickup_write_mnc = useMNC .AND. aim_pickup_write_mnc
342 aim_pickup_read_mnc = useMNC .AND. aim_pickup_read_mnc
343 #else /* ALLOW_MNC */
344 aim_timeave_mnc = .FALSE.
345 aim_snapshot_mnc = .FALSE.
346 aim_pickup_write_mnc = .FALSE.
347 aim_pickup_read_mnc = .FALSE.
348 #endif /* ALLOW_MNC */
349 aim_timeave_mdsio = (.NOT. aim_timeave_mnc)
350 & .OR. outputTypesInclusive
351 aim_snapshot_mdsio = (.NOT. aim_snapshot_mnc)
352 & .OR. outputTypesInclusive
353 aim_pickup_write_mdsio = (.NOT. aim_pickup_write_mnc)
354 & .OR. outputTypesInclusive
355 aim_pickup_read_mdsio = (.NOT. aim_pickup_read_mnc)
356 & .OR. outputTypesInclusive
357
358
359 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
360 C-- Print out parameter values :
361
362 WRITE(msgBuf,'(A)') ' '
363 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
364 WRITE(msgBuf,'(A)') '// ==================================='
365 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
366 WRITE(msgBuf,'(A)') '// AIM physics parameters :'
367 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
368 WRITE(msgBuf,'(A)') '// ==================================='
369 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
370
371 CALL WRITE_0D_L( useLand, INDEX_NONE,
372 & 'useLand =',
373 &' /* use Land package for surf.BC over land */')
374
375 C- namelist AIM_PARAMS:
376 CALL WRITE_0D_L( aim_useFMsurfBC, INDEX_NONE,
377 & 'aim_useFMsurfBC =',
378 &' /* F.Molteni surf. BC scheme on/off flag */')
379 CALL WRITE_0D_L( aim_useMMsurfFc, INDEX_NONE,
380 & 'aim_useMMsurfFc =',
381 &' /* Monthly Mean surf. Forcing on/off flag */')
382 CALL WRITE_0D_RL(aim_surfForc_TimePeriod, INDEX_NONE,
383 & 'aim_surfForc_TimePeriod =',
384 & ' /* Length of forcing time period (s) */')
385 CALL WRITE_0D_I( aim_surfForc_NppCycle, INDEX_NONE,
386 & 'aim_surfForc_NppCycle =',
387 & ' /* Number of time period per Cycle */')
388 CALL WRITE_0D_RL(aim_surfForc_TransRatio, INDEX_NONE,
389 & 'aim_surfForc_TransRatio =',
390 & ' /* transition ratio from one month to the next */')
391 CALL WRITE_0D_L( aim_surfPotTemp, INDEX_NONE,
392 & 'aim_surfPotTemp =',
393 &' /* Surf Temp file in Pot.Temp on/off flag */')
394 CALL WRITE_0D_L( aim_energPrecip, INDEX_NONE,
395 & 'aim_energPrecip =',
396 & ' /* account for energy of precip. on/off flag */')
397 CALL WRITE_0D_L( aim_splitSIOsFx, INDEX_NONE,
398 & 'aim_splitSIOsFx =',
399 & ' /* separate Sea-Ice & Ocean Flux on/off flag */')
400 CALL WRITE_0D_RL(aim_dragStrato,INDEX_NONE,'aim_dragStrato=',
401 & ' /* stratospheric-drag damping time scale (s) */')
402 CALL WRITE_0D_L( aim_clrSkyDiag, INDEX_NONE,
403 & 'aim_clrSkyDiag =',
404 & ' /* do clear-sky radiation diagnostics */')
405 CALL WRITE_0D_RL( aim_taveFreq, INDEX_NONE,'aim_taveFreq =',
406 & ' /* Frequency^-1 for time-Aver. output (s) */')
407 CALL WRITE_0D_RL( aim_diagFreq, INDEX_NONE,'aim_diagFreq =',
408 & ' /* Frequency^-1 for diagnostic output (s) */')
409 CALL WRITE_0D_RL( aim_tendFreq, INDEX_NONE,'aim_tendFreq =',
410 & ' /* Frequency^-1 for tendencies output (s) */')
411 CALL WRITE_0D_I( aim_selectOceAlbedo, INDEX_NONE,
412 & 'aim_selectOceAlbedo =',
413 & ' /* Ocean albedo(latitude) flag */')
414
415 C- namelist AIM_PAR_FOR:
416 CALL WRITE_0D_RL( SOLC, INDEX_NONE,'AIM_FOR: SOLC =',
417 & ' /* Solar constant (area averaged) in W/m2 */')
418 CALL WRITE_0D_RL( ALBSEA,INDEX_NONE,'AIM_FOR: ALBSEA =',
419 & ' /* Albedo over sea [0-1] */')
420 CALL WRITE_0D_RL( ALBICE,INDEX_NONE,'AIM_FOR: ALBICE =',
421 & ' /* Albedo over sea ice (for ice fraction =1) */')
422 CALL WRITE_0D_RL( ALBSN, INDEX_NONE,'AIM_FOR: ALBSN =',
423 & ' /* Albedo over snow (for snow depth > SDALB) */')
424 CALL WRITE_0D_RL( SDALB, INDEX_NONE,'AIM_FOR: SDALB =',
425 & ' /* Snow depth (mm H2O) corresp. maximum albedo */')
426 CALL WRITE_0D_RL( SWCAP, INDEX_NONE,'AIM_FOR: SWCAP =',
427 & ' /* Soil wetness at field capacity (Vol.fract.) */')
428 CALL WRITE_0D_RL( SWWIL, INDEX_NONE,'AIM_FOR: SWWIL =',
429 & ' /* Soil wetness at wilting point (Vol.fract.) */')
430 CALL WRITE_0D_RL( hSnowWetness, INDEX_NONE,
431 & 'AIM_FOR: hSnowWetness=',
432 & ' /* snow depth corresp. maximum wetness (m) */')
433
434 C- namelist AIM_PAR_SFL:
435 CALL WRITE_0D_RL( FWIND0,INDEX_NONE,'AIM_SFL: FWIND0 =',
436 & ' /* ratio of near-sfc wind to lowest-level wind */')
437 CALL WRITE_0D_RL( FTEMP0,INDEX_NONE,'AIM_SFL: FTEMP0 =',
438 & ' /* weight for near-sfc temp. extrapolation (0-1)*/')
439 CALL WRITE_0D_RL( FHUM0, INDEX_NONE,'AIM_SFL: FHUM0 =',
440 & ' /* weight for near-sfc spec.humid. extrap. (0-1)*/')
441 CALL WRITE_0D_RL( CDL, INDEX_NONE,'AIM_SFL: CDL =',
442 & ' /* drag coefficient for momentum over land */')
443 CALL WRITE_0D_RL( CDS, INDEX_NONE,'AIM_SFL: CDS =',
444 & ' /* drag coefficient for momentum over sea */')
445 CALL WRITE_0D_RL( CHL, INDEX_NONE,'AIM_SFL: CHL =',
446 & ' /* heat exchange coefficient over land */')
447 CALL WRITE_0D_RL( CHS, INDEX_NONE,'AIM_SFL: CHS =',
448 & ' /* heat exchange coefficient over sea */')
449 CALL WRITE_0D_RL( VGUST, INDEX_NONE,'AIM_SFL: VGUST =',
450 & ' /* wind speed [m/s] for sub-grid-scale gusts */')
451 CALL WRITE_0D_RL( CTDAY, INDEX_NONE,'AIM_SFL: CTDAY =',
452 & ' /* daily-cycle correction (dTskin/dSSRad) */')
453 CALL WRITE_0D_RL( DTHETA,INDEX_NONE,'AIM_SFL: DTHETA =',
454 & ' /* Pot.Temp. gradient for stability correction */')
455 CALL WRITE_0D_RL( dTstab,INDEX_NONE,'AIM_SFL: dTstab =',
456 & ' /* Pot.Temp. increment for stab.funct. derivative */')
457 CALL WRITE_0D_RL( FSTAB, INDEX_NONE,'AIM_SFL: FSTAB =',
458 & ' /* Amplitude of stability correction (fract.) */')
459 CALL WRITE_0D_RL( HDRAG, INDEX_NONE,'AIM_SFL: HDRAG =',
460 & ' /* Height scale for orographic correction */')
461 CALL WRITE_0D_RL( FHDRAG,INDEX_NONE,'AIM_SFL: FHDRAG =',
462 & ' /* Amplitude of orographic correction (fract.)*/')
463
464 C- namelist AIM_PAR_CNV:
465 CALL WRITE_0D_RL( PSMIN, INDEX_NONE,'AIM_CNV: PSMIN =',
466 & ' /* min norm.sfc.P. for occurrence of convect. */')
467 CALL WRITE_0D_RL( TRCNV, INDEX_NONE,'AIM_CNV: TRCNV =',
468 & ' /* time of relaxation [h] towards ref state */')
469 CALL WRITE_0D_RL( QBL, INDEX_NONE,'AIM_CNV: QBL =',
470 & ' /* specific hum. threshold in the Bound.layer */')
471 CALL WRITE_0D_RL( RHBL, INDEX_NONE,'AIM_CNV: RHBL =',
472 & ' /* relative hum. threshold in the Bound.layer */')
473 CALL WRITE_0D_RL( RHIL, INDEX_NONE,'AIM_CNV: RHIL =',
474 & ' /* rel.hum. threshold (intern) for 2nd mass.Flx*/')
475 CALL WRITE_0D_RL( ENTMAX,INDEX_NONE,'AIM_CNV: ENTMAX =',
476 & ' /* time of relaxation [h] towards neutral eq. */')
477 CALL WRITE_0D_RL( SMF, INDEX_NONE,'AIM_CNV: SMF =',
478 & ' /* ratio 2ndary/primary mass.Flx at cloud-base*/')
479
480 C- namelist AIM_PAR_LSC:
481 CALL WRITE_0D_RL( TRLSC, INDEX_NONE,'AIM_LSC: TRLSC =',
482 & ' /* relaxation time [h] for supersat. spec.hum. */')
483 CALL WRITE_0D_RL( RHLSC, INDEX_NONE,'AIM_LSC: RHLSC =',
484 & ' /* Max rel.humidity threshold (at sigma=1) */')
485 CALL WRITE_0D_RL( DRHLSC,INDEX_NONE,'AIM_LSC: DRHLSC =',
486 & ' /* Vertical range of rel.humidity threshold */')
487 CALL WRITE_0D_RL( QSMAX, INDEX_NONE,'AIM_LSC: QSMAX =',
488 & ' /* Define the maximum latent heat release */')
489
490 C- namelist AIM_PAR_RAD:
491 CALL WRITE_0D_RL( RHCL1, INDEX_NONE,'AIM_RAD: RHCL1 =',
492 & ' /* rel.hum. corresponding to cloud cover = 0 */')
493 CALL WRITE_0D_RL( RHCL2, INDEX_NONE,'AIM_RAD: RHCL2 =',
494 & ' /* rel.hum. corresponding to cloud cover = 1 */')
495 CALL WRITE_0D_RL( QACL1, INDEX_NONE,'AIM_RAD: QACL1 =',
496 & ' /* spec.hum. threshold for cloud, upper trop. */')
497 CALL WRITE_0D_RL( QACL2, INDEX_NONE,'AIM_RAD: QACL2 =',
498 & ' /* spec.hum. threshold for cloud, upper trop. */')
499 CALL WRITE_0D_RL( ALBCL, INDEX_NONE,'AIM_RAD: ALBCL =',
500 & ' /* cloud albedo (for cloud cover = 1) */')
501 CALL WRITE_0D_RL( EPSSW, INDEX_NONE,'AIM_RAD: EPSSW =',
502 & ' /* fract. of inc.solar rad. absorbed by ozone */')
503 CALL WRITE_0D_RL( EPSLW, INDEX_NONE,'AIM_RAD: EPSLW =',
504 & ' /* fract. of sfc LW emitted directly to space */')
505 CALL WRITE_0D_RL( EMISFC,INDEX_NONE,'AIM_RAD: EMISFC =',
506 & ' /* longwave surface emissivity */')
507
508 WRITE(msgBuf,'(A)')
509 & ' AIM_RAD : ShortWave absorptivities (for dp = 10^5 Pa) :'
510 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
511 CALL WRITE_0D_RL( ABSDRY,INDEX_NONE,'AIM_RAD: ABSDRY =',
512 & ' /* abs. of dry air (visible band) */')
513 CALL WRITE_0D_RL( ABSAER,INDEX_NONE,'AIM_RAD: ABSAER =',
514 & ' /* abs. of aerosols (visible band) */')
515 CALL WRITE_0D_RL( ABSWV1,INDEX_NONE,'AIM_RAD: ABSWV1 =',
516 & ' /* abs. of water vap. (vis. band)(/dq, 1g/kg) */')
517 CALL WRITE_0D_RL( ABSWV2,INDEX_NONE,'AIM_RAD: ABSWV2 =',
518 & ' /* abs. of water vap.(near IR bd)(/dq, 1g/kg) */')
519 CALL WRITE_0D_RL( ABSCL1,INDEX_NONE,'AIM_RAD: ABSCL1 =',
520 & ' /* abs. of clouds (vis.band)(constant term) */')
521 CALL WRITE_0D_RL( ABSCL2,INDEX_NONE,'AIM_RAD: ABSCL2 =',
522 & ' /* abs. of clouds (vis.band) (/dw, 1g/kg) */')
523
524 WRITE(msgBuf,'(A)')
525 & ' AIM_RAD : LongWave absorptivities (per dp = 10^5 Pa) :'
526 CALL WRITE_0D_RL( ABLWIN,INDEX_NONE,'AIM_RAD: ABLWIN =',
527 & ' /* abs. of air in "window" band */')
528 CALL WRITE_0D_RL( ABLCO2,INDEX_NONE,'AIM_RAD: ABLCO2 =',
529 & ' /* abs. of air in CO2 band */')
530 CALL WRITE_0D_RL( ABLWV1,INDEX_NONE,'AIM_RAD: ABLWV1 =',
531 & ' /* abs. of Water vap. H2O bd-1(weak)(/dq,1g/kg)*/')
532 CALL WRITE_0D_RL( ABLWV2,INDEX_NONE,'AIM_RAD: ABLWV2 =',
533 & ' /* abs. of W. vap., H2O bd-2(strong)(/dq,1g/kg)*/')
534 CALL WRITE_0D_RL( ABLCL1,INDEX_NONE,'AIM_RAD: ABLCL1 =',
535 & ' /* abs. of clouds in window band (const term) */')
536 CALL WRITE_0D_RL( ABLCL2,INDEX_NONE,'AIM_RAD: ABLCL2 =',
537 & ' /* abs. of clouds in window band (/dw, 1g/kg) */')
538
539 C- namelist AIM_PAR_VDI:
540 CALL WRITE_0D_RL( TRSHC, INDEX_NONE,'AIM_VDI: TRSHC =',
541 & ' /* relaxation time [h] for shallow convection */')
542 CALL WRITE_0D_RL( TRVDI, INDEX_NONE,'AIM_VDI: TRVDI =',
543 & ' /* relaxation time [h] for moisture diffusion */')
544 CALL WRITE_0D_RL( TRVDS, INDEX_NONE,'AIM_VDI: TRVDS =',
545 & ' /* relaxation time [h] for super-adiab. cond. */')
546 CALL WRITE_0D_RL( RHGRAD,INDEX_NONE,'AIM_VDI: RHGRAD =',
547 & ' /* max gradient of rel.humidity (d_RH/d_sigma)*/')
548 CALL WRITE_0D_RL( SEGRAD,INDEX_NONE,'AIM_VDI: SEGRAD =',
549 & ' /* max grad. of dry static Energy(d_DSE/d_phi)*/')
550
551 #ifdef ALLOW_AIM_CO2
552 C- namelist AIM_PAR_CO2:
553 CALL WRITE_0D_I( Aim_CO2_Flag, INDEX_NONE,
554 & 'AIM_PAR_CO2: Aim_CO2_Flag =',
555 & ' /* CO2 flag, 1: prescribed, 2: interactive */')
556 CALL WRITE_0D_RL( atm_pCO2, INDEX_NONE,
557 & 'AIM_PAR_CO2: atm_pCO2 =',
558 & ' /* pCO2 when prescribed or IC when interactive */')
559 #endif
560
561 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
562
563 _END_MASTER(myThid)
564
565 C-- Everyone else must wait for the parameters to be loaded
566 _BARRIER
567
568 #endif /* ALLOW_AIM */
569
570 RETURN
571 END

  ViewVC Help
Powered by ViewVC 1.1.22