/[MITgcm]/MITgcm/pkg/aim/aim_read_physparms.F
ViewVC logotype

Annotation of /MITgcm/pkg/aim/aim_read_physparms.F

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


Revision 1.2 - (hide annotations) (download)
Mon Aug 1 19:34:57 2005 UTC (18 years, 10 months ago) by cnh
Branch: MAIN
CVS Tags: HEAD
Changes since 1.1: +1 -1 lines
FILE REMOVED
Emptying aim/ since aim_v23 is now "the one" for all experiements.

1 cnh 1.2 C $Header: /u/gcmpack/MITgcm/pkg/aim/aim_read_physparms.F,v 1.1 2002/10/09 01:01:24 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "AIM_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: AIM_READ_PHYSPARMS
8     C !INTERFACE:
9     SUBROUTINE AIM_READ_PHYSPARMS( myThid )
10    
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13     C | S/R AIM_READ_PHYSPARMS
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 corresponding to maximum albedo
69     C SWCAP = Soil wetness capacity
70     C SWWIL = Soil wetness at wilting point
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 SWMAX = Soil wetness (in mm) corresp. to potential evapotranspiration
89     NAMELIST /AIM_PAR_SFL/
90     & FWIND0, FTEMP0, FHUM0,
91     & CDL, CDS, CHL, CHS, VGUST,
92     & SWMAX
93    
94     C-- Convection constants (common CNVCON) :
95     C RHBL = relative hum. threshold in the boundary (lowest) layer
96     C TRCNV = time of relaxation (in hours) towards neutral equilibrium
97     C ENTMAX = max. entrainment as a fraction of cloud-base mass flux
98     NAMELIST /AIM_PAR_CNV/
99     & RHBL, TRCNV, ENTMAX
100    
101     C-- Constants for large-scale condendation (common LSCCON) :
102     C RHLSC = Relative humidity threshold
103     C TRLSC = Relaxation time (in hours) for supersat. specific humidity
104     NAMELIST /AIM_PAR_LSC/
105     & RHLSC, TRLSC
106    
107     C-- Radiation constants (common RADCON) :
108     C ABSSW = shortwave absorptivity for dry air (per dp = 10^5 Pa)
109     C ABSLW = longwave absorptivity for dry air (per dp = 10^5 Pa)
110     C ABWSW = shortwave absorptivity for water vapour (per dq = 1 g/kg)
111     C ABWLW = longwave absorptivity for water vapour (per dq = 1 g/kg)
112     C ABCSW = shortwave absorptivity for cloud fraction
113     C ABCLW = longwave absorptivity for cloud fraction
114     C EPSSW = fraction of incoming solar radiation absorbed by ozone
115     C EPSLW = fraction of surface LW radiation emitted directly to space
116     C ALBCL = cloud albedo (for cloud cover = 1)
117     C RHCL1 = relative hum. corresponding to cloud cover = 0
118     C RHCL2 = relative hum. corresponding to cloud cover = 1
119     C QACL = specific hum. threshold for cloud cover
120     NAMELIST /AIM_PAR_RAD/
121     & ABSSW, ABSLW, ABWSW, ABWLW, ABCSW, ABCLW,
122     & EPSSW, EPSLW,
123     & ALBCL, RHCL1, RHCL2, QACL
124    
125     C-- Constants for vertical dif. and sh. conv. (common VDICON) :
126     C TRVDI = relaxation time (in hours) for moisture diffusion
127     C TRSHC = relaxation time (in hours) for shallow convection
128     NAMELIST /AIM_PAR_VDI/
129     & TRVDI, TRSHC
130    
131     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
132    
133     _BEGIN_MASTER(myThid)
134    
135     WRITE(msgBuf,'(A)') ' AIM_READ_PHYSPARMS: opening data.aimphys'
136     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
137    
138     CALL OPEN_COPY_DATA_FILE( 'data.aimphys', 'AIM_READ_PHYSPARMS',
139     O iUnit, myThid )
140    
141     C-- Read parameters from open data file:
142    
143     C- Constants for boundary forcing
144     READ(UNIT=iUnit,NML=AIM_PAR_FOR)
145    
146     C- Constants for surface fluxes
147     READ(UNIT=iUnit,NML=AIM_PAR_SFL)
148    
149     C- Constants for convection
150     READ(UNIT=iUnit,NML=AIM_PAR_CNV)
151    
152     C- Constants for large-scale condensation
153     READ(UNIT=iUnit,NML=AIM_PAR_LSC)
154    
155     C- Constants for radiation
156     READ(UNIT=iUnit,NML=AIM_PAR_RAD)
157    
158     C- Constants for vertical diffusion and sh. conv.
159     READ(UNIT=iUnit,NML=AIM_PAR_VDI)
160    
161     WRITE(msgBuf,'(A)')
162     & ' AIM_READ_PHYSPARMS: finished reading data.aimphys'
163     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
164    
165     C-- Close the open data file
166     CLOSE(iUnit)
167    
168     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
169     C-- Print out parameter values :
170    
171     WRITE(msgBuf,'(A)') ' '
172     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
173     WRITE(msgBuf,'(A)') '// ==================================='
174     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
175     WRITE(msgBuf,'(A)') '// AIM physics parameters :'
176     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
177     WRITE(msgBuf,'(A)') '// ==================================='
178     CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
179    
180     C- namelist AIM_PAR_FOR:
181     CALL WRITE_0D_R8( SOLC, INDEX_NONE,'AIM_FOR: SOLC =',
182     & ' /* Solar constant (area averaged) in W/m2 */')
183    
184     C- namelist AIM_PAR_SFL:
185     CALL WRITE_0D_R8( FWIND0,INDEX_NONE,'AIM_SFL: FWIND0 =',
186     & ' /* ratio of near-sfc wind to lowest-level wind */')
187     CALL WRITE_0D_R8( FTEMP0,INDEX_NONE,'AIM_SFL: FTEMP0 =',
188     & ' /* weight for near-sfc temp. extrapolation (0-1)*/')
189     CALL WRITE_0D_R8( FHUM0, INDEX_NONE,'AIM_SFL: FHUM0 =',
190     & ' /* weight for near-sfc spec.humid. extrap. (0-1)*/')
191     CALL WRITE_0D_R8( CDL, INDEX_NONE,'AIM_SFL: CDL =',
192     & ' /* drag coefficient for momentum over land */')
193     CALL WRITE_0D_R8( CDS, INDEX_NONE,'AIM_SFL: CDS =',
194     & ' /* drag coefficient for momentum over sea */')
195     CALL WRITE_0D_R8( CHL, INDEX_NONE,'AIM_SFL: CHL =',
196     & ' /* heat exchange coefficient over land */')
197     CALL WRITE_0D_R8( CHS, INDEX_NONE,'AIM_SFL: CHS =',
198     & ' /* heat exchange coefficient over sea */')
199     CALL WRITE_0D_R8( VGUST, INDEX_NONE,'AIM_SFL: VGUST =',
200     & ' /* wind speed [m/s] for sub-grid-scale gusts */')
201    
202     C- namelist AIM_PAR_CNV:
203     CALL WRITE_0D_R8( RHBL, INDEX_NONE,'AIM_CNV: RHBL =',
204     & ' /* rel. hum. threshold in the B.(lowest) layer */')
205     CALL WRITE_0D_R8( TRCNV, INDEX_NONE,'AIM_CNV: TRCNV =',
206     & ' /* time of relaxation [h] towards neutral eq. */')
207     CALL WRITE_0D_R8( ENTMAX,INDEX_NONE,'AIM_CNV: ENTMAX =',
208     & ' /* time of relaxation [h] towards neutral eq. */')
209    
210     C- namelist AIM_PAR_LSC:
211     CALL WRITE_0D_R8( RHLSC, INDEX_NONE,'AIM_LSC: RHLSC =',
212     & ' /* Relative humidity threshold */')
213     CALL WRITE_0D_R8( TRLSC, INDEX_NONE,'AIM_LSC: TRLSC =',
214     & ' /* relaxation time [h] for supersat. spec.hum. */')
215    
216     C- namelist AIM_PAR_RAD:
217     CALL WRITE_0D_R8( ABSSW, INDEX_NONE,'AIM_RAD: ABSSW =',
218     & ' /* ShortW. absorptivity for dry air (/dp, 1e5 Pa)*/')
219     CALL WRITE_0D_R8( ABSLW, INDEX_NONE,'AIM_RAD: ABSLW =',
220     & ' /* LongW. absorptivity for dry air (/dp, 1e5 Pa)*/')
221     CALL WRITE_0D_R8( ABWSW, INDEX_NONE,'AIM_RAD: ABWSW =',
222     & ' /* ShortW. absorptivity for WaterVap.(/dq, 1g/kg)*/')
223     CALL WRITE_0D_R8( ABWLW, INDEX_NONE,'AIM_RAD: ABWLW =',
224     & ' /* LongW. absorptivity for WaterVap.(/dq, 1g/kg)*/')
225     CALL WRITE_0D_R8( ABCSW, INDEX_NONE,'AIM_RAD: ABCSW =',
226     & ' /* ShortW. absorptivity for cloud fraction */')
227     CALL WRITE_0D_R8( ABCLW, INDEX_NONE,'AIM_RAD: ABCLW =',
228     & ' /* LongW. absorptivity for cloud fraction */')
229     CALL WRITE_0D_R8( EPSSW, INDEX_NONE,'AIM_RAD: EPSSW =',
230     & ' /* fraction of inc.solar rad. absorbed by ozone */')
231     CALL WRITE_0D_R8( EPSLW, INDEX_NONE,'AIM_RAD: EPSLW =',
232     & ' /* fraction of sfc LW emitted directly to space */')
233     CALL WRITE_0D_R8( ALBCL, INDEX_NONE,'AIM_RAD: ALBCL =',
234     & ' /* cloud albedo (for cloud cover = 1) */')
235     CALL WRITE_0D_R8( RHCL1, INDEX_NONE,'AIM_RAD: RHCL1 =',
236     & ' /* rel.hum. corresponding to cloud cover = 0 */')
237     CALL WRITE_0D_R8( RHCL2, INDEX_NONE,'AIM_RAD: RHCL2 =',
238     & ' /* rel.hum. corresponding to cloud cover = 1 */')
239     CALL WRITE_0D_R8( QACL, INDEX_NONE,'AIM_RAD: QACL =',
240     & ' /* specific hum. threshold for cloud cover */')
241    
242     C- namelist AIM_PAR_VDI:
243     CALL WRITE_0D_R8( TRVDI, INDEX_NONE,'AIM_VDI: TRVDI =',
244     & ' /* relaxation time [h] for moisture diffusion */')
245     CALL WRITE_0D_R8( TRSHC, INDEX_NONE,'AIM_VDI: TRSHC =',
246     & ' /* relaxation time [h] for shallow convection */')
247    
248     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
249    
250     _END_MASTER(myThid)
251    
252     C-- Everyone else must wait for the parameters to be loaded
253     _BARRIER
254    
255     #endif /* ALLOW_AIM */
256    
257     RETURN
258     END

  ViewVC Help
Powered by ViewVC 1.1.22