/[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.3 - (show annotations) (download)
Sun Jan 18 18:14:20 2004 UTC (20 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, checkpoint52j_post, checkpoint52k_post, hrcube5, checkpoint52i_post, checkpoint52j_pre, checkpoint52i_pre, checkpoint52h_pre, hrcube_2, hrcube_3
Changes since 1.2: +3 -3 lines
1 line was longer than 72c (but rarely compiled): fixed

1 C $Header: /u/gcmpack/MITgcm/pkg/land/land_readparms.F,v 1.2 2003/07/31 18:22:10 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_grT_iniFile :: File containing initial ground Temp.
56 C land_grW_iniFile :: File containing initial ground Water.
57 C land_deltaT :: land model time-step
58 C land_taveFreq :: Frequency^-1 for time-Aver. output (s)
59 C land_diagFreq :: Frequency^-1 for diagnostic output (s)
60 C land_dzF :: layer thickness
61 NAMELIST /LAND_MODEL_PAR/
62 & land_calc_grT, land_calc_grW,
63 & land_grT_iniFile, land_grW_iniFile,
64 & land_deltaT, land_taveFreq, land_diagFreq,
65 & land_dzF
66
67 C-- Physical constants :
68 C land_grdLambda :: Thermal conductivity of the ground
69 C land_heatCs :: Heat capacity of dry soil
70 C land_heatCw :: Heat capacity of water
71 C land_wTauDiff :: soil moisture diffusion time scale
72 C land_waterCap :: field capacity per meter of soil
73 C land_fractRunOff:: fraction of water in excess which run-off
74
75 NAMELIST /LAND_PHYS_PAR/
76 & land_grdLambda, land_heatCs, land_heatCw,
77 & land_wTauDiff, land_waterCap, land_fractRunOff
78
79 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
80
81 C- Set default value:
82 land_calc_grT = .TRUE.
83 land_calc_grW = .TRUE.
84 land_grT_iniFile = ' '
85 land_grW_iniFile = ' '
86 land_deltaT = deltaTclock
87 land_taveFreq = taveFreq
88 land_diagFreq = dumpFreq
89 land_grdLambda= 0.42 _d 0
90 land_heatCs = 1.13 _d 6
91 land_heatCw = 4.2 _d 6
92 land_wTauDiff = 48. _d 0*3600. _d 0
93 land_waterCap = 0.24 _d 0
94 land_fractRunOff = 0.5 _d 0
95 DO k=1,land_nLev
96 land_dzF(k) = -1.
97 land_rec_dzC(k) = -1.
98 ENDDO
99
100 _BEGIN_MASTER(myThid)
101
102 WRITE(msgBuf,'(A)') ' LAND_READPARMS: opening data.land'
103 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
104
105 CALL OPEN_COPY_DATA_FILE( 'data.land', 'LAND_READPARMS',
106 O iUnit, myThid )
107
108 C-- Read parameters from open data file:
109
110 C- Parameters for Land model:
111 READ(UNIT=iUnit,NML=LAND_MODEL_PAR)
112
113 C- Physical Constants for Land package
114 READ(UNIT=iUnit,NML=LAND_PHYS_PAR)
115
116 WRITE(msgBuf,'(A)')
117 & ' LAND_READPARMS: finished reading data.land'
118 CALL PRINT_MESSAGE(msgBuf,standardMessageUnit,SQUEEZE_RIGHT,1)
119
120 C-- Close the open data file
121 CLOSE(iUnit)
122
123 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
124 C-- Check parameters and model configuration
125
126 C- If land_taveFreq is positive, then must compile the land-diagnostics code
127 #ifndef ALLOW_LAND_TAVE
128 IF (land_taveFreq.GT.0.) THEN
129 WRITE(msgBuf,'(2A)') 'LAND_READPARMS:',
130 & ' land_taveFreq > 0 but ALLOW_LAND_TAVE undefined'
131 CALL PRINT_ERROR( msgBuf, myThid)
132 WRITE(msgBuf,'(2A)')
133 & 'Re-compile with: #define ALLOW_LAND_TAVE',
134 & ' or -DALLOW_LAND_TAVE'
135 CALL PRINT_ERROR( msgBuf, myThid)
136 STOP 'ABNORMAL END: S/R LAND_READPARMS'
137 ENDIF
138 #endif /* ALLOW_LAND_TAVE */
139
140 C- derive other parameters:
141 tmpvar = 0. _d 0
142 DO k=1,land_nLev
143 tmpvar = tmpvar+land_dzF(k)
144 IF (tmpvar.GT.0. _d 0) land_rec_dzC(k) = 2. _d 0 / tmpvar
145 tmpvar = land_dzF(k)
146 ENDDO
147
148 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
149 C-- Print out parameter values :
150
151 iUnit = standardMessageUnit
152 WRITE(msgBuf,'(A)') ' '
153 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
154 WRITE(msgBuf,'(A)') '// ==================================='
155 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
156 WRITE(msgBuf,'(A)') '// Land package parameters :'
157 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
158 WRITE(msgBuf,'(A)') '// ==================================='
159 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
160
161 C- namelist LAND_MODEL_PAR:
162 CALL WRITE_0D_L( land_calc_grT, INDEX_NONE,
163 & 'land_calc_grT =',
164 & ' /* step forward ground Temp. on/off flag */')
165 CALL WRITE_0D_L( land_calc_grW, INDEX_NONE,
166 & 'land_calc_grW =',
167 & ' /* step forward soil moiture on/off flag */')
168 iL = ILNBLNK( land_grT_iniFile )
169 c IF ( iL.EQ.LEN(land_grT_iniFile) ) iL=0
170 IF ( iL.GE.1 ) THEN
171 WRITE(msgBuf,'(A,A)') 'land_grT_iniFile = ',
172 & '/* Initial ground-Temp Input-File */'
173 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
174 WRITE(msgBuf,'(16X,A)') land_grT_iniFile(1:iL)
175 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
176 msgBuf=' ;'
177 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
178 ENDIF
179 iL = ILNBLNK( land_grW_iniFile )
180 c IF ( iL.EQ.LEN(land_grW_iniFile) ) iL=0
181 IF ( iL.GE.1 ) THEN
182 WRITE(msgBuf,'(A,A)') 'land_grW_iniFile = ',
183 & '/* Initial soil-Water Input-File */'
184 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
185 WRITE(msgBuf,'(16X,A)') land_grW_iniFile(1:iL)
186 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
187 msgBuf=' ;'
188 CALL PRINT_MESSAGE(msgBuf,iUnit,SQUEEZE_RIGHT,1)
189 ENDIF
190 CALL WRITE_0D_R8( land_deltaT, INDEX_NONE,'land_deltaT =',
191 & ' /* land model Time-Step (s) */')
192 CALL WRITE_0D_R8( land_taveFreq, INDEX_NONE,'land_taveFreq =',
193 & ' /* Frequency^-1 for time-Aver. output (s) */')
194 CALL WRITE_0D_R8( land_diagFreq, INDEX_NONE,'land_diagFreq =',
195 & ' /* Frequency^-1 for diagnostic output (s) */')
196 CALL WRITE_1D_R8( land_dzF,land_nLev, INDEX_K,'land_dzF = ',
197 & ' /* layer thickness ( m ) */')
198 CALL WRITE_1D_R8(land_rec_dzC,land_nLev,INDEX_K,'land_rec_dzC= '
199 & ,' /* recip. vertical spacing (m-1) */')
200
201 C- namelist LAND_PHYS_PAR:
202 CALL WRITE_0D_R8(land_grdLambda,INDEX_NONE,'land_grdLambda =',
203 & ' /* Thermal conductivity of the ground (W/m/K)*/')
204 CALL WRITE_0D_R8( land_heatCs,INDEX_NONE,'land_heatCs =',
205 & ' /* Heat capacity of dry soil (J.m-3.K-1) */')
206 CALL WRITE_0D_R8( land_heatCw,INDEX_NONE,'land_heatCw =',
207 & ' /* Heat capacity of water (J.m-3.K-1) */')
208 CALL WRITE_0D_R8( land_wTauDiff,INDEX_NONE,'land_wTauDiff =',
209 & ' /* soil moisture diffusion time scale (s) */')
210 CALL WRITE_0D_R8( land_waterCap,INDEX_NONE,'land_waterCap =',
211 & ' /* field capacity per meter of soil (1) */')
212 CALL WRITE_0D_R8(land_fractRunOff,INDEX_NONE,'land_fractRunOff='
213 & ,' /* fraction of water in excess which run-off */')
214
215 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
216
217 _END_MASTER(myThid)
218
219 C-- Everyone else must wait for the parameters to be loaded
220 _BARRIER
221
222 #endif /* ALLOW_LAND */
223
224 RETURN
225 END

  ViewVC Help
Powered by ViewVC 1.1.22