/[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.13 - (hide annotations) (download)
Wed Oct 18 20:08:15 2006 UTC (17 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58t_post, checkpoint58q_post, checkpoint58r_post, checkpoint58v_post, checkpoint58u_post, checkpoint58s_post
Changes since 1.12: +64 -4 lines
- remove EQUIVALENCE instructions (in AIM_FFIELDS.h)
- clean-up multi-threaded problems (reported by debugger tcheck on ACES)
  by moving time-interpolation weight (aim_sWght0,1) out of common block

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

  ViewVC Help
Powered by ViewVC 1.1.22