/[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.21 - (show annotations) (download)
Thu Jan 11 01:55:53 2018 UTC (6 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint66o, checkpoint66n, HEAD
Changes since 1.20: +132 -61 lines
- merge namelist "AIM_PAR_CO2" into "AIM_PARAMS" and replace Aim_CO2_Flag=2
  option with aim_select_pCO2=2 (using #define ALLOW_AIM_CO2);
- add option to derive LW absorption in CO2 band as function of pCO2,
  using either prescried pCO2 (aim_select_pCO2=1), or computed pCO2
  from well mixed atm-box (aim_select_pCO2=3).

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

  ViewVC Help
Powered by ViewVC 1.1.22