/[MITgcm]/MITgcm/pkg/land/land_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/land/land_readparms.F

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


Revision 1.4 - (show annotations) (download)
Thu Mar 11 14:42:00 2004 UTC (20 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint52l_post, checkpoint52m_post, checkpoint53a_post, checkpoint53
Changes since 1.3: +141 -31 lines
new land formulation:
a) use ground enthalpy as prognostic variable to ensure exact
   energy conservation.
b) account for water temperature and for latent heat of freezing
   in all processes (rain, run-off, ground storage)
c) compute surface and ground temperature implicitly.

1 C $Header: /u/gcmpack/MITgcm/pkg/land/land_readparms.F,v 1.3 2004/01/18 18:14:20 jmc Exp $
2 C $Name: $
3
4 #include "LAND_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: LAND_READPARMS
8 C !INTERFACE:
9 SUBROUTINE LAND_READPARMS( myThid )
10
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | S/R LAND_READPARMS
14 C | o Read Land package parameters
15 C *==========================================================*
16 C \ev
17
18 C !USES:
19 IMPLICIT NONE
20
21 C == Global variables ===
22
23 C-- size for MITgcm & Land package :
24 #include "LAND_SIZE.h"
25
26 #include "EEPARAMS.h"
27 #include "PARAMS.h"
28 #include "LAND_PARAMS.h"
29
30 C !INPUT/OUTPUT PARAMETERS:
31 C == Routine Arguments ==
32 C myThid :: Number of this instance
33 INTEGER myThid
34 CEOP
35
36 #ifdef ALLOW_LAND
37
38 C Functions
39 INTEGER ILNBLNK
40
41 C == Local Variables ==
42 C msgBuf :: Informational/error meesage buffer
43 C iUnit :: Work variable for IO unit number
44 C k :: loop counter
45 C iL :: Work variable for length of file-name
46 CHARACTER*(MAX_LEN_MBUF) msgBuf
47 INTEGER iUnit, k, iL
48 _RL tmpvar
49
50 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
51
52 C-- Land model parameters:
53 C land_calc_grT :: step forward ground Temperature
54 C land_calc_grW :: step forward soil moiture
55 C land_impl_grT :: solve ground Temperature implicitly
56 C land_calc_snow :: step forward snow thickness
57 C land_calc_alb :: compute albedo of snow over land
58 C land_oldPickup :: restart from an old pickup (= before checkpoint 52j)
59 C land_grT_iniFile :: File containing initial ground Temp.
60 C land_grW_iniFile :: File containing initial ground Water.
61 C land_snow_iniFile :: File containing initial snow thickness.
62 C land_deltaT :: land model time-step
63 C land_taveFreq :: Frequency^-1 for time-Aver. output (s)
64 C land_diagFreq :: Frequency^-1 for diagnostic output (s)
65 C land_monFreq :: Frequency^-1 for monitor output (s)
66 C land_dzF :: layer thickness
67 NAMELIST /LAND_MODEL_PAR/
68 & land_calc_grT, land_calc_grW,
69 & land_impl_grT, land_calc_snow,
70 & land_calc_alb, land_oldPickup,
71 & land_grT_iniFile, land_grW_iniFile, land_snow_iniFile,
72 & land_deltaT, land_taveFreq, land_diagFreq, land_monFreq,
73 & land_dzF
74
75 C-- Physical constants :
76 C land_grdLambda :: Thermal conductivity of the ground
77 C land_heatCs :: Heat capacity of dry soil (J/m3/K)
78 C land_CpWater :: Heat capacity of water (J/kg/K)
79 C land_wTauDiff :: soil moisture diffusion time scale
80 C land_waterCap :: field capacity per meter of soil
81 C land_fractRunOff:: fraction of water in excess which run-off
82 C land_rhoLiqW :: density of liquid water (kg/m3)
83 C land_rhoSnow :: density of snow (kg/m3)
84 C land_Lfreez :: Latent heat of freezing (J/kg)
85 C timeSnowAge :: snow aging time scale (s)
86 C hNewSnowAge :: new snow thickness that refresh the snow-age (by 1/e)
87 C albColdSnow :: albedo of cold (=dry) new snow (Tsfc < -10)
88 C albWarmSnow :: albedo of warm (=wet) new snow (Tsfc = 0)
89 C albOldSnow :: albedo of old snow (snowAge > 35.d)
90 C hAlbSnow :: snow thickness for albedo transition: snow/ground
91
92 NAMELIST /LAND_PHYS_PAR/
93 & land_grdLambda, land_heatCs, land_CpWater,
94 & land_wTauDiff, land_waterCap, land_fractRunOff,
95 & land_rhoLiqW,
96 & land_rhoSnow, land_Lfreez,
97 & diffKsnow, timeSnowAge, hNewSnowAge,
98 & albColdSnow, albWarmSnow, albOldSnow, hAlbSnow
99
100 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
101
102 C- Set default value:
103 land_calc_grT = .TRUE.
104 land_calc_grW = .TRUE.
105 land_impl_grT = .TRUE.
106 land_calc_snow= .TRUE.
107 land_calc_alb = .TRUE.
108 land_oldPickup= .FALSE.
109 land_grT_iniFile = ' '
110 land_grW_iniFile = ' '
111 land_snow_iniFile= ' '
112 land_deltaT = deltaTclock
113 land_taveFreq = taveFreq
114 land_diagFreq = dumpFreq
115 land_monFreq = monitorFreq
116 land_grdLambda= 0.42 _d 0
117 land_heatCs = 1.13 _d 6
118 land_CpWater = 4.2 _d 3
119 c land_CpWater = HeatCapacity_Cp
120 land_wTauDiff = 48. _d 0*3600. _d 0
121 land_waterCap = 0.24 _d 0
122 land_fractRunOff = 0.5 _d 0
123 land_rhoLiqW = rhoConstFresh
124 C- snow parameters:
125 land_rhoSnow = 330. _d 0
126 land_Lfreez = 334. _d 3
127 diffKsnow = 0.30 _d 0
128 timeSnowAge = 50. _d 0 * 86400. _d 0
129 hNewSnowAge = 2. _d -3
130 albColdSnow = 0.85 _d 0
131 albWarmSnow = 0.70 _d 0
132 albOldSnow = 0.55 _d 0
133 hAlbSnow = 0.30 _d 0
134 C- layer thickness:
135 DO k=1,land_nLev
136 land_dzF(k) = -1.
137 land_rec_dzC(k) = -1.
138 ENDDO
139
140 _BEGIN_MASTER(myThid)
141
142 WRITE(msgBuf,'(A)') ' LAND_READPARMS: opening data.land'
143 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
144
145 CALL OPEN_COPY_DATA_FILE( 'data.land', 'LAND_READPARMS',
146 O iUnit, myThid )
147
148 C-- Read parameters from open data file:
149
150 C- Parameters for Land model:
151 READ(UNIT=iUnit,NML=LAND_MODEL_PAR)
152
153 C- Physical Constants for Land package
154 READ(UNIT=iUnit,NML=LAND_PHYS_PAR)
155
156 WRITE(msgBuf,'(A)')
157 & ' LAND_READPARMS: finished reading data.land'
158 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
159
160 C-- Close the open data file
161 CLOSE(iUnit)
162
163 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
164 C- derive other parameters:
165
166 land_impl_grT = land_calc_grT .AND. land_impl_grT
167
168 tmpvar = 0. _d 0
169 DO k=1,land_nLev
170 tmpvar = tmpvar+land_dzF(k)
171 IF (tmpvar.GT.0. _d 0) land_rec_dzC(k) = 2. _d 0 / tmpvar
172 tmpvar = land_dzF(k)
173 ENDDO
174 IF ( land_Lfreez.NE. 0. _d 0 ) THEN
175 recip_Lfreez = 1. _d 0 / land_Lfreez
176 ELSE
177 recip_Lfreez = 0. _d 0
178 ENDIF
179
180 C-- Check parameters and model configuration
181
182 IF ( land_nLev.NE.2 .AND. land_impl_grT ) THEN
183 WRITE(msgBuf,'(2A,I3)') 'LAND_READPARMS: ',
184 & ' land_impl_grT=.T. but land_nLev=',land_nLev
185 CALL PRINT_ERROR( msgBuf, myThid)
186 WRITE(msgBuf,'(A)')
187 & 'Implicit scheme only implemented for 2 levels land Temp'
188 CALL PRINT_ERROR( msgBuf, myThid)
189 STOP 'ABNORMAL END: S/R LAND_READPARMS'
190 ENDIF
191
192 C- If land_taveFreq is positive, then must compile the land-diagnostics code
193 #ifndef ALLOW_LAND_TAVE
194 IF (land_taveFreq.GT.0.) THEN
195 WRITE(msgBuf,'(2A)') 'LAND_READPARMS:',
196 & ' land_taveFreq > 0 but ALLOW_LAND_TAVE undefined'
197 CALL PRINT_ERROR( msgBuf, myThid)
198 WRITE(msgBuf,'(2A)') 'Re-compile setting: ',
199 & '#define ALLOW_LAND_TAVE (in LAND_OPTIONS.h)'
200 CALL PRINT_ERROR( msgBuf, myThid)
201 STOP 'ABNORMAL END: S/R LAND_READPARMS'
202 ENDIF
203 #endif /* ALLOW_LAND_TAVE */
204
205 C- If land_monFreq is > 0, then must compile the monitor pkg
206 #ifndef ALLOW_MONITOR
207 IF (land_monFreq.GT.0.) THEN
208 WRITE(msgBuf,'(2A)') 'LAND_READPARMS:',
209 & ' land_monFreq > 0 but ALLOW_MONITOR undefined'
210 CALL PRINT_ERROR( msgBuf, myThid)
211 WRITE(msgBuf,'(2A)')
212 & 'Re-compile with pkg monitor (in packages.conf)'
213 CALL PRINT_ERROR( msgBuf, myThid)
214 STOP 'ABNORMAL END: S/R LAND_READPARMS'
215 ENDIF
216 #endif /* ALLOW_MONITOR */
217
218 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
219 C-- Print out parameter values :
220
221 iUnit = standardMessageUnit
222 WRITE(msgBuf,'(A)') ' '
223 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
224 WRITE(msgBuf,'(A)') '// ==================================='
225 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
226 WRITE(msgBuf,'(A)') '// Land package parameters :'
227 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
228 WRITE(msgBuf,'(A)') '// ==================================='
229 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
230
231 C- namelist LAND_MODEL_PAR:
232 CALL WRITE_0D_L( land_calc_grT, INDEX_NONE,
233 & 'land_calc_grT =',
234 & ' /* step forward ground Temp. on/off flag */')
235 CALL WRITE_0D_L( land_calc_grW, INDEX_NONE,
236 & 'land_calc_grW =',
237 & ' /* step forward soil moiture on/off flag */')
238 CALL WRITE_0D_L( land_impl_grT, INDEX_NONE,
239 & 'land_impl_grT =',
240 & ' /* solve ground temperature implicitly */')
241 CALL WRITE_0D_L( land_calc_snow, INDEX_NONE,
242 & 'land_calc_snow =',
243 & ' /* step forward snow thickness */')
244 CALL WRITE_0D_L( land_calc_alb, INDEX_NONE,
245 & 'land_calc_alb =',
246 & ' /* compute land+snow albedo */')
247 iL = ILNBLNK( land_grT_iniFile )
248 c IF ( iL.EQ.LEN(land_grT_iniFile) ) iL=0
249 IF ( iL.GE.1 ) THEN
250 WRITE(msgBuf,'(A,A)') 'land_grT_iniFile = ',
251 & '/* Initial ground-Temp Input-File */'
252 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
253 WRITE(msgBuf,'(16X,A)') land_grT_iniFile(1:iL)
254 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
255 msgBuf=' ;'
256 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
257 ENDIF
258 iL = ILNBLNK( land_grW_iniFile )
259 IF ( iL.GE.1 ) THEN
260 WRITE(msgBuf,'(A,A)') 'land_grW_iniFile = ',
261 & '/* Initial soil-Water Input-File */'
262 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
263 WRITE(msgBuf,'(16X,A)') land_grW_iniFile(1:iL)
264 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
265 msgBuf=' ;'
266 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
267 ENDIF
268 iL = ILNBLNK( land_snow_iniFile )
269 IF ( iL.GE.1 ) THEN
270 WRITE(msgBuf,'(A,A)') 'land_snow_iniFile= ',
271 & '/* Initial snow thickness Input-File */'
272 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
273 WRITE(msgBuf,'(16X,A)') land_grW_iniFile(1:iL)
274 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
275 msgBuf=' ;'
276 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
277 ENDIF
278 CALL WRITE_0D_R8( land_deltaT, INDEX_NONE,'land_deltaT =',
279 & ' /* land model Time-Step (s) */')
280 CALL WRITE_0D_R8( land_taveFreq, INDEX_NONE,'land_taveFreq =',
281 & ' /* Frequency^-1 for time-Aver. output (s) */')
282 CALL WRITE_0D_R8( land_diagFreq, INDEX_NONE,'land_diagFreq =',
283 & ' /* Frequency^-1 for diagnostic output (s) */')
284 CALL WRITE_0D_R8( land_diagFreq, INDEX_NONE,'land_monFreq =',
285 & ' /* Frequency^-1 for monitor output (s) */')
286 CALL WRITE_1D_R8( land_dzF,land_nLev, INDEX_K,'land_dzF = ',
287 & ' /* layer thickness ( m ) */')
288 CALL WRITE_1D_R8(land_rec_dzC,land_nLev,INDEX_K,'land_rec_dzC= '
289 & ,' /* recip. vertical spacing (m-1) */')
290
291 C- namelist LAND_PHYS_PAR:
292 CALL WRITE_0D_R8(land_grdLambda,INDEX_NONE,'land_grdLambda =',
293 & ' /* Thermal conductivity of the ground (W/m/K)*/')
294 CALL WRITE_0D_R8( land_heatCs,INDEX_NONE,'land_heatCs =',
295 & ' /* Heat capacity of dry soil (J/m3/K) */')
296 CALL WRITE_0D_R8( land_CpWater,INDEX_NONE,'land_CpWater =',
297 & ' /* Heat capacity of water (J/kg/K) */')
298 CALL WRITE_0D_R8( land_wTauDiff,INDEX_NONE,'land_wTauDiff =',
299 & ' /* soil moisture diffusion time scale (s) */')
300 CALL WRITE_0D_R8( land_waterCap,INDEX_NONE,'land_waterCap =',
301 & ' /* field capacity per meter of soil (1) */')
302 CALL WRITE_0D_R8(land_fractRunOff,INDEX_NONE,'land_fractRunOff='
303 & ,' /* fraction of water in excess which run-off */')
304 CALL WRITE_0D_R8(land_rhoLiqW,INDEX_NONE,'land_rhoLiqW =',
305 & ' /* density of liquid water (kg/m3) */')
306 CALL WRITE_0D_R8(land_rhoSnow,INDEX_NONE,'land_rhoSnow =',
307 & ' /* density of snow (kg/m3) */')
308 CALL WRITE_0D_R8(land_Lfreez,INDEX_NONE,'land_Lfreez =',
309 & ' /* Latent heat of freezing (J/kg) */')
310 CALL WRITE_0D_R8(diffKsnow,INDEX_NONE,'diffKsnow =',
311 & ' /* thermal conductivity of snow (W/m/K) */')
312 CALL WRITE_0D_R8(timeSnowAge,INDEX_NONE,'timeSnowAge =',
313 & ' /* snow aging time scale (s) */')
314 CALL WRITE_0D_R8(hNewSnowAge,INDEX_NONE,'hNewSnowAge =',
315 & ' /* new snow thickness to refresh snow-age by 1/e */')
316 CALL WRITE_0D_R8(albColdSnow,INDEX_NONE,'albColdSnow =',
317 & ' /* albedo of cold (=dry) new snow */')
318 CALL WRITE_0D_R8(albWarmSnow,INDEX_NONE,'albWarmSnow =',
319 & ' /* albedo of warm (=wet) new snow */')
320 CALL WRITE_0D_R8(albOldSnow, INDEX_NONE,'albOldSnow =',
321 & ' /* albedo of old snow (snowAge >35.d)*/')
322 CALL WRITE_0D_R8(hAlbSnow, INDEX_NONE,'hAlbSnow =',
323 & ' /* snow depth for albedo transition */')
324
325 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
326
327 _END_MASTER(myThid)
328
329 C-- Everyone else must wait for the parameters to be loaded
330 _BARRIER
331
332 #endif /* ALLOW_LAND */
333
334 RETURN
335 END

  ViewVC Help
Powered by ViewVC 1.1.22