/[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.1 - (hide annotations) (download)
Fri Nov 22 17:17:03 2002 UTC (21 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47a_post, checkpoint47b_post
new aim pkg: adapted from Franco Molteni SPEEDY code, ver23

1 jmc 1.1 C $Header: $
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     c #include "PARAMS.h"
28    
29     C- Physical constants + functions of sigma and latitude
30     c #include "com_physcon.h"
31     C- Constants for sub-grid-scale physics
32     #include "com_forcon.h"
33     #include "com_sflcon.h"
34     #include "com_cnvcon.h"
35     #include "com_lsccon.h"
36     #include "com_radcon.h"
37     #include "com_vdicon.h"
38    
39     C !INPUT/OUTPUT PARAMETERS:
40     C == Routine Arguments ==
41     C myThid - Number of this instance
42     INTEGER myThid
43     CEOP
44    
45     #ifdef ALLOW_AIM
46    
47     C == Local Variables ==
48     C msgBuf - Informational/error meesage buffer
49     C iUnit - Work variable for IO unit number
50     CHARACTER*(MAX_LEN_MBUF) msgBuf
51     INTEGER iUnit
52    
53     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
54    
55     C-- Physical constants (common PHYCON) :
56     C P0 = reference pressure
57     C GG = gravity accel.
58     C RD = gas constant for dry air
59     C CP = specific heat at constant pressure
60     C ALHC = latent heat of condensation
61     C SBC = Stefan-Boltzmann constant
62    
63     C-- Constants for forcing fields (common FORCON) :
64     C SOLC = Solar constant (area averaged) in W/m^2
65     C ALBSEA = Albedo over sea
66     C ALBICE = Albedo over sea ice (for ice fraction = 1)
67     C ALBSN = Albedo over snow (for snow depth > SDALB)
68     C SDALB = Snow depth (mm water) corresponding to maximum albedo
69     C SWCAP = Soil wetness at field capacity (volume fraction)
70     C SWWIL = Soil wetness at wilting point (volume fraction)
71     NAMELIST /AIM_PAR_FOR/
72     & SOLC, ALBSEA, ALBICE, ALBSN,
73     & SDALB, SWCAP, SWWIL
74    
75     C-- Constants for surface fluxes (common SFLCON) :
76     C FWIND0 = ratio of near-sfc wind to lowest-level wind
77     C FTEMP0 = weight for near-sfc temperature extrapolation (0-1) :
78     C 1 : linear extrapolation from two lowest levels
79     C 0 : constant potential temperature ( = lowest level)
80     C FHUM0 = weight for near-sfc specific humidity extrapolation (0-1) :
81     C 1 : extrap. with constant relative hum. ( = lowest level)
82     C 0 : constant specific hum. ( = lowest level)
83     C CDL = drag coefficient for momentum over land
84     C CDS = drag coefficient for momentum over sea
85     C CHL = heat exchange coefficient over land
86     C CHS = heat exchange coefficient over sea
87     C VGUST = wind speed for sub-grid-scale gusts
88     C CTDAY = daily-cycle correction (dTskin/dSSRad)
89     C DTHETA = Potential temp. gradient for stability correction
90     C FSTAB = Amplitude of stability correction (fraction)
91     C HDRAG = Height scale for orographic correction
92     C FHDRAG = Amplitude of orographic correction (fraction)
93     NAMELIST /AIM_PAR_SFL/
94     & FWIND0, FTEMP0, FHUM0,
95     & CDL, CDS, CHL, CHS, VGUST, CTDAY,
96     & DTHETA, FSTAB, HDRAG, FHDRAG
97    
98     C-- Convection constants (common CNVCON) :
99     C PSMIN = minimum (norm.) sfc. pressure for the occurrence of convection
100     C TRCNV = time of relaxation (in hours) towards reference state
101     C QBL = specific hum. threshold in the boundary layer
102     C RHBL = relative hum. threshold in the boundary layer
103     C RHIL = rel. hum. threshold in intermed. layers for secondary mass flux
104     C ENTMAX = max. entrainment as a fraction of cloud-base mass flux
105     C SMF = ratio between secondary and primary mass flux at cloud-base
106     NAMELIST /AIM_PAR_CNV/
107     & PSMIN, TRCNV, QBL, RHBL, RHIL, ENTMAX, SMF
108    
109    
110     C-- Constants for large-scale condendation (common LSCCON) :
111     C TRLSC = Relaxation time (in hours) for specific humidity
112     C RHLSC = Maximum relative humidity threshold (at sigma=1)
113     C DRHLSC = Vertical range of relative humidity threshold
114     C QSMAX = used to define the maximum latent heat release
115     NAMELIST /AIM_PAR_LSC/
116     & TRLSC, RHLSC, DRHLSC, QSMAX
117    
118     C-- Radiation constants (common RADCON) :
119     C RHCL1 = relative hum. corresponding to cloud cover = 0
120     C RHCL2 = relative hum. corresponding to cloud cover = 1
121     C QACL1 = specific hum. threshold for cloud cover in the upper troposphere
122     C QACL2 = specific hum. threshold for cloud cover in the upper troposphere
123     C ALBCL = cloud albedo (for cloud cover = 1)
124     C EPSSW = fraction of incoming solar radiation absorbed by ozone
125     C EPSLW = fraction of surface LW radiation emitted directly to space
126     C EMISFC = longwave surface emissivity
127     C--: shortwave absorptivities (for dp = 10^5 Pa) :
128     C ABSDRY = abs. of dry air (visible band)
129     C ABSAER = abs. of aerosols (visible band)
130     C ABSWV1 = abs. of water vapour (visible band, for dq = 1 g/kg)
131     C ABSWV2 = abs. of water vapour (near IR band, for dq = 1 g/kg)
132     C ABSCL1 = abs. of clouds (visible band, constant term)
133     C ABSCL2 = abs. of clouds (visible band, for dw = 1 g/kg)
134     C--: longwave absorptivities (per dp = 10^5 Pa) :
135     C ABLWIN = abs. of air in "window" band
136     C ABLCO2 = abs. of air in CO2 band
137     C ABLWV1 = abs. of water vapour in H2O band 1 (weak), for dq = 1 g/kg
138     C ABLWV2 = abs. of water vapour in H2O band 2 (strong), for dq = 1 g/kg
139     C ABLCL1 = abs. of clouds in "window" band, constant term
140     C ABLCL2 = abs. of clouds in "window" band, for dw = 1 g/kg
141     NAMELIST /AIM_PAR_RAD/
142     & RHCL1, RHCL2, QACL1, QACL2, ALBCL,
143     & EPSSW, EPSLW, EMISFC,
144     & ABSDRY, ABSAER, ABSWV1, ABSWV2, ABSCL1, ABSCL2,
145     & ABLWIN, ABLCO2, ABLWV1, ABLWV2, ABLCL1, ABLCL2
146    
147     C-- Constants for vertical dif. and sh. conv. (common VDICON) :
148     C TRSHC = relaxation time (in hours) for shallow convection
149     C TRVDI = relaxation time (in hours) for moisture diffusion
150     C TRVDS = relaxation time (in hours) for super-adiab. conditions
151     C RHGRAD = maximum gradient of relative humidity (d_RH/d_sigma)
152     C SEGRAD = minimum gradient of dry static energy (d_DSE/d_phi)
153     NAMELIST /AIM_PAR_VDI/
154     & TRSHC, TRVDI, TRVDS, RHGRAD, SEGRAD
155    
156     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
157    
158     _BEGIN_MASTER(myThid)
159    
160     WRITE(msgBuf,'(A)') ' AIM_READ_PHYSPARMS: opening data.aimphys'
161     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
162    
163     CALL OPEN_COPY_DATA_FILE( 'data.aimphys', 'AIM_READ_PHYSPARMS',
164     O iUnit, myThid )
165    
166     C-- Read parameters from open data file:
167    
168     C- Constants for boundary forcing
169     READ(UNIT=iUnit,NML=AIM_PAR_FOR)
170    
171     C- Constants for surface fluxes
172     READ(UNIT=iUnit,NML=AIM_PAR_SFL)
173    
174     C- Constants for convection
175     READ(UNIT=iUnit,NML=AIM_PAR_CNV)
176    
177     C- Constants for large-scale condensation
178     READ(UNIT=iUnit,NML=AIM_PAR_LSC)
179    
180     C- Constants for radiation
181     READ(UNIT=iUnit,NML=AIM_PAR_RAD)
182    
183     C- Constants for vertical diffusion and sh. conv.
184     READ(UNIT=iUnit,NML=AIM_PAR_VDI)
185    
186     WRITE(msgBuf,'(A)')
187     & ' AIM_READ_PHYSPARMS: finished reading data.aimphys'
188     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
189    
190     C-- Close the open data file
191     CLOSE(iUnit)
192    
193     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
194     C-- Print out parameter values :
195    
196     WRITE(msgBuf,'(A)') ' '
197     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
198     WRITE(msgBuf,'(A)') '// ==================================='
199     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
200     WRITE(msgBuf,'(A)') '// AIM physics parameters :'
201     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
202     WRITE(msgBuf,'(A)') '// ==================================='
203     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
204    
205     C- namelist AIM_PAR_FOR:
206     CALL WRITE_0D_R8( SOLC, INDEX_NONE,'AIM_FOR: SOLC =',
207     & ' /* Solar constant (area averaged) in W/m2 */')
208     CALL WRITE_0D_R8( ALBSEA,INDEX_NONE,'AIM_FOR: ALBSEA =',
209     & ' /* Albedo over sea [0-1] */')
210     CALL WRITE_0D_R8( ALBICE,INDEX_NONE,'AIM_FOR: ALBICE =',
211     & ' /* Albedo over sea ice (for ice fraction =1) */')
212     CALL WRITE_0D_R8( ALBSN, INDEX_NONE,'AIM_FOR: ALBSN =',
213     & ' /* Albedo over snow (for snow depth > SDALB) */')
214     CALL WRITE_0D_R8( SDALB, INDEX_NONE,'AIM_FOR: SDALB =',
215     & ' /* Snow depth (mm H2O) corresp. maximum albedo */')
216     CALL WRITE_0D_R8( SWCAP, INDEX_NONE,'AIM_FOR: SWCAP =',
217     & ' /* Soil wetness at field capacity (Vol.fract.) */')
218     CALL WRITE_0D_R8( SWWIL, INDEX_NONE,'AIM_FOR: SWWIL =',
219     & ' /* Soil wetness at wilting point (Vol.fract.) */')
220    
221     C- namelist AIM_PAR_SFL:
222     CALL WRITE_0D_R8( FWIND0,INDEX_NONE,'AIM_SFL: FWIND0 =',
223     & ' /* ratio of near-sfc wind to lowest-level wind */')
224     CALL WRITE_0D_R8( FTEMP0,INDEX_NONE,'AIM_SFL: FTEMP0 =',
225     & ' /* weight for near-sfc temp. extrapolation (0-1)*/')
226     CALL WRITE_0D_R8( FHUM0, INDEX_NONE,'AIM_SFL: FHUM0 =',
227     & ' /* weight for near-sfc spec.humid. extrap. (0-1)*/')
228     CALL WRITE_0D_R8( CDL, INDEX_NONE,'AIM_SFL: CDL =',
229     & ' /* drag coefficient for momentum over land */')
230     CALL WRITE_0D_R8( CDS, INDEX_NONE,'AIM_SFL: CDS =',
231     & ' /* drag coefficient for momentum over sea */')
232     CALL WRITE_0D_R8( CHL, INDEX_NONE,'AIM_SFL: CHL =',
233     & ' /* heat exchange coefficient over land */')
234     CALL WRITE_0D_R8( CHS, INDEX_NONE,'AIM_SFL: CHS =',
235     & ' /* heat exchange coefficient over sea */')
236     CALL WRITE_0D_R8( VGUST, INDEX_NONE,'AIM_SFL: VGUST =',
237     & ' /* wind speed [m/s] for sub-grid-scale gusts */')
238     CALL WRITE_0D_R8( CTDAY, INDEX_NONE,'AIM_SFL: CTDAY =',
239     & ' /* daily-cycle correction (dTskin/dSSRad) */')
240     CALL WRITE_0D_R8( DTHETA,INDEX_NONE,'AIM_SFL: DTHETA =',
241     & ' /* Pot.Temp. gradient for stability correction */')
242     CALL WRITE_0D_R8( FSTAB, INDEX_NONE,'AIM_SFL: FSTAB =',
243     & ' /* Amplitude of stability correction (fract.) */')
244     CALL WRITE_0D_R8( HDRAG, INDEX_NONE,'AIM_SFL: HDRAG =',
245     & ' /* Height scale for orographic correction */')
246     CALL WRITE_0D_R8( FHDRAG,INDEX_NONE,'AIM_SFL: FHDRAG =',
247     & ' /* Amplitude of orographic correction (fract.)*/')
248    
249     C- namelist AIM_PAR_CNV:
250     CALL WRITE_0D_R8( PSMIN, INDEX_NONE,'AIM_CNV: PSMIN =',
251     & ' /* min norm.sfc.P. for occurrence of convect. */')
252     CALL WRITE_0D_R8( TRCNV, INDEX_NONE,'AIM_CNV: TRCNV =',
253     & ' /* time of relaxation [h] towards ref state */')
254     CALL WRITE_0D_R8( QBL, INDEX_NONE,'AIM_CNV: QBL =',
255     & ' /* specific hum. threshold in the Bound.layer */')
256     CALL WRITE_0D_R8( RHBL, INDEX_NONE,'AIM_CNV: RHBL =',
257     & ' /* relative hum. threshold in the Bound.layer */')
258     CALL WRITE_0D_R8( RHIL, INDEX_NONE,'AIM_CNV: RHIL =',
259     & ' /* rel.hum. threshold (intern) for 2nd mass.Flx*/')
260     CALL WRITE_0D_R8( ENTMAX,INDEX_NONE,'AIM_CNV: ENTMAX =',
261     & ' /* time of relaxation [h] towards neutral eq. */')
262     CALL WRITE_0D_R8( SMF, INDEX_NONE,'AIM_CNV: SMF =',
263     & ' /* ratio 2ndary/primary mass.Flx at cloud-base*/')
264    
265     C- namelist AIM_PAR_LSC:
266     CALL WRITE_0D_R8( TRLSC, INDEX_NONE,'AIM_LSC: TRLSC =',
267     & ' /* relaxation time [h] for supersat. spec.hum. */')
268     CALL WRITE_0D_R8( RHLSC, INDEX_NONE,'AIM_LSC: RHLSC =',
269     & ' /* Max rel.humidity threshold (at sigma=1) */')
270     CALL WRITE_0D_R8( DRHLSC,INDEX_NONE,'AIM_LSC: DRHLSC =',
271     & ' /* Vertical range of rel.humidity threshold */')
272     CALL WRITE_0D_R8( QSMAX, INDEX_NONE,'AIM_LSC: QSMAX =',
273     & ' /* Define the maximum latent heat release */')
274    
275     C- namelist AIM_PAR_RAD:
276     CALL WRITE_0D_R8( RHCL1, INDEX_NONE,'AIM_RAD: RHCL1 =',
277     & ' /* rel.hum. corresponding to cloud cover = 0 */')
278     CALL WRITE_0D_R8( RHCL2, INDEX_NONE,'AIM_RAD: RHCL2 =',
279     & ' /* rel.hum. corresponding to cloud cover = 1 */')
280     CALL WRITE_0D_R8( QACL1, INDEX_NONE,'AIM_RAD: QACL1 =',
281     & ' /* spec.hum. threshold for cloud, upper trop. */')
282     CALL WRITE_0D_R8( QACL2, INDEX_NONE,'AIM_RAD: QACL2 =',
283     & ' /* spec.hum. threshold for cloud, upper trop. */')
284     CALL WRITE_0D_R8( ALBCL, INDEX_NONE,'AIM_RAD: ALBCL =',
285     & ' /* cloud albedo (for cloud cover = 1) */')
286     CALL WRITE_0D_R8( EPSSW, INDEX_NONE,'AIM_RAD: EPSSW =',
287     & ' /* fract. of inc.solar rad. absorbed by ozone */')
288     CALL WRITE_0D_R8( EPSLW, INDEX_NONE,'AIM_RAD: EPSLW =',
289     & ' /* fract. of sfc LW emitted directly to space */')
290     CALL WRITE_0D_R8( EMISFC,INDEX_NONE,'AIM_RAD: EMISFC =',
291     & ' /* longwave surface emissivity */')
292    
293     WRITE(msgBuf,'(A)')
294     & ' AIM_RAD : ShortWave absorptivities (for dp = 10^5 Pa) :'
295     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
296     CALL WRITE_0D_R8( ABSDRY,INDEX_NONE,'AIM_RAD: ABSDRY =',
297     & ' /* abs. of dry air (visible band) */')
298     CALL WRITE_0D_R8( ABSAER,INDEX_NONE,'AIM_RAD: ABSAER =',
299     & ' /* abs. of aerosols (visible band) */')
300     CALL WRITE_0D_R8( ABSWV1,INDEX_NONE,'AIM_RAD: ABSWV1 =',
301     & ' /* abs. of water vap. (vis. band)(/dq, 1g/kg) */')
302     CALL WRITE_0D_R8( ABSWV1,INDEX_NONE,'AIM_RAD: ABSWV1 =',
303     & ' /* abs. of water vap. (vis. band)(/dq, 1g/kg) */')
304     CALL WRITE_0D_R8( ABSWV2,INDEX_NONE,'AIM_RAD: ABSWV2 =',
305     & ' /* abs. of water vap.(near IR bd)(/dq, 1g/kg) */')
306     CALL WRITE_0D_R8( ABSCL1,INDEX_NONE,'AIM_RAD: ABSCL1 =',
307     & ' /* abs. of clouds (vis.band)(constant term) */')
308     CALL WRITE_0D_R8( ABSCL2,INDEX_NONE,'AIM_RAD: ABSCL2 =',
309     & ' /* abs. of clouds (vis.band) (/dw, 1g/kg) */')
310    
311     WRITE(msgBuf,'(A)')
312     & ' AIM_RAD : LongWave absorptivities (per dp = 10^5 Pa) :'
313     CALL WRITE_0D_R8( ABLWIN,INDEX_NONE,'AIM_RAD: ABLWIN =',
314     & ' /* abs. of air in "window" band */')
315     CALL WRITE_0D_R8( ABLCO2,INDEX_NONE,'AIM_RAD: ABLCO2 =',
316     & ' /* abs. of air in CO2 band */')
317     CALL WRITE_0D_R8( ABLWV1,INDEX_NONE,'AIM_RAD: ABLWV1 =',
318     & ' /* abs. of Water vap. H2O bd-1(weak)(/dq,1g/kg)*/')
319     CALL WRITE_0D_R8( ABLWV2,INDEX_NONE,'AIM_RAD: ABLWV2 =',
320     & ' /* abs. of W. vap., H2O bd-2(strong)(/dq,1g/kg)*/')
321     CALL WRITE_0D_R8( ABLCL1,INDEX_NONE,'AIM_RAD: ABLCL1 =',
322     & ' /* abs. of clouds in window band (const term) */')
323     CALL WRITE_0D_R8( ABLCL2,INDEX_NONE,'AIM_RAD: ABLCL2 =',
324     & ' /* abs. of clouds in window band (/dw, 1g/kg) */')
325    
326     C- namelist AIM_PAR_VDI:
327     CALL WRITE_0D_R8( TRSHC, INDEX_NONE,'AIM_VDI: TRSHC =',
328     & ' /* relaxation time [h] for shallow convection */')
329     CALL WRITE_0D_R8( TRVDI, INDEX_NONE,'AIM_VDI: TRVDI =',
330     & ' /* relaxation time [h] for moisture diffusion */')
331     CALL WRITE_0D_R8( TRVDS, INDEX_NONE,'AIM_VDI: TRVDS =',
332     & ' /* relaxation time [h] for super-adiab. cond. */')
333     CALL WRITE_0D_R8( RHGRAD,INDEX_NONE,'AIM_VDI: RHGRAD =',
334     & ' /* max gradient of rel.humidity (d_RH/d_sigma)*/')
335     CALL WRITE_0D_R8( RHGRAD,INDEX_NONE,'AIM_VDI: RHGRAD =',
336     & ' /* max grad. of dry static Energy(d_DSE/d_phi)*/')
337    
338     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
339    
340     _END_MASTER(myThid)
341    
342     C-- Everyone else must wait for the parameters to be loaded
343     _BARRIER
344    
345     #endif /* ALLOW_AIM */
346    
347     RETURN
348     END

  ViewVC Help
Powered by ViewVC 1.1.22