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

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

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


Revision 1.3 - (show annotations) (download)
Fri May 14 16:14:48 2004 UTC (20 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint53b_pre, checkpoint53b_post
Changes since 1.2: +117 -59 lines
* only liquid water diffuse or run-off.
* threshold on snow thickness (excess goes into run-off).

1 C $Header: /u/gcmpack/MITgcm/pkg/land/land_stepfwd.F,v 1.2 2004/03/11 14:42:00 jmc Exp $
2 C $Name: $
3
4 #include "LAND_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: LAND_STEPFWD
8 C !INTERFACE:
9 SUBROUTINE LAND_STEPFWD(
10 I land_frc, bi, bj, myTime, myIter, myThid)
11
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | S/R LAND_STEPFWD
15 C | o Land model main S/R: step forward land variables
16 C *==========================================================*
17 C \ev
18
19 C !USES:
20 IMPLICIT NONE
21
22 C == Global variables ===
23 C-- size for MITgcm & Land package :
24 #include "LAND_SIZE.h"
25
26 #include "EEPARAMS.h"
27 #include "LAND_PARAMS.h"
28 #include "LAND_VARS.h"
29
30 C !INPUT/OUTPUT PARAMETERS:
31 C == Routine arguments ==
32 C land_frc :: land fraction [0-1]
33 C bi,bj :: Tile index
34 C myTime :: Current time of simulation ( s )
35 C myIter :: Current iteration number in simulation
36 C myThid :: Number of this instance of the routine
37 _RS land_frc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
38 INTEGER bi, bj, myIter, myThid
39 _RL myTime
40 CEOP
41
42 #ifdef ALLOW_LAND
43 C == Local variables ==
44 C i,j,k :: loop counters
45 C kp1 :: k+1
46 C grd_HeatCp :: Heat capacity of the ground [J/m3/K]
47 C enthalpGrdW :: enthalpy of ground water [J/m3]
48 C fieldCapac :: field capacity (of water) [m]
49 C mWater :: water content of the ground [kg/m3]
50 C groundWnp1 :: hold temporary future soil moisture []
51 C grdWexcess :: ground water in excess [m/s]
52 C fractRunOff :: fraction of water in excess which leaves as runoff
53 C flxkup :: downward flux of water, upper interface (k-1,k)
54 C flxdwn :: downward flux of water, lower interface (k,k+1)
55 C flxEngU :: downward energy flux associated with water flux (W/m2)
56 C upper interface (k-1,k)
57 C flxEngL :: downward energy flux associated with water flux (W/m2)
58 C lower interface (k,k+1)
59 C temp_af :: ground temperature if above freezing
60 C temp_bf :: ground temperature if below freezing
61 C mPmE :: hold temporary (liquid) Precip minus Evap [kg/m2/s]
62 C enWfx :: hold temporary energy flux of Precip [W/m2]
63 C enGr1 :: ground enthalpy of level 1 [J/m2]
64 C mSnow :: mass of snow [kg/m2]
65 C dMsn :: mass of melting snow [kg/m2]
66 C snowPrec :: snow precipitation [kg/m2/s]
67 C hNewSnow :: fresh snow accumulation [m]
68 C dhSnowMx :: potential snow increase [m]
69 C dhSnow :: effective snow increase [m]
70 C mIceDt :: ground-ice growth rate (<- excess of snow) [kg/m2/s]
71 C ageFac :: snow aging factor [1]
72 _RL grd_HeatCp, enthalpGrdW
73 _RL fieldCapac, mWater
74 _RL groundWnp1, grdWexcess, fractRunOff
75 _RL flxkup(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
76 _RL flxkdw(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77 _RL flxEngU(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78 _RL flxEngL, temp_af, temp_bf, mPmE, enWfx, enGr1
79 _RL mSnow, dMsn, snowPrec
80 _RL hNewSnow, dhSnowMx, dhSnow, mIceDt, ageFac
81 INTEGER i,j,k,kp1
82
83 IF (land_calc_grT .AND. .NOT.land_impl_grT ) THEN
84 C-- Step forward ground temperature:
85
86 DO k=1,land_nLev
87 kp1 = MIN(k+1,land_nLev)
88
89 IF (k.EQ.1) THEN
90 DO j=1,sNy
91 DO i=1,sNx
92 flxkup(i,j) = land_HeatFlx(i,j,bi,bj)
93 ENDDO
94 ENDDO
95 ELSE
96 DO j=1,sNy
97 DO i=1,sNx
98 flxkup(i,j) = flxkdw(i,j)
99 ENDDO
100 ENDDO
101 ENDIF
102
103 DO j=1,sNy
104 DO i=1,sNx
105 IF ( land_frc(i,j,bi,bj).GT.0. ) THEN
106 C- Thermal conductivity flux, lower interface (k,k+1):
107 flxkdw(i,j) = land_grdLambda*
108 & ( land_groundT(i,j,k,bi,bj)
109 & -land_groundT(i,j,kp1,bi,bj) )
110 & *land_rec_dzC(kp1)
111
112 C- Step forward ground enthalpy, level k :
113 land_enthalp(i,j,k,bi,bj) = land_enthalp(i,j,k,bi,bj)
114 & + land_deltaT * (flxkup(i,j)-flxkdw(i,j))/land_dzF(k)
115
116 ENDIF
117 ENDDO
118 ENDDO
119
120 ENDDO
121 C-- step forward ground temperature: end
122 ENDIF
123
124 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
125
126 #ifdef LAND_OLD_VERSION
127 IF ( .TRUE. ) THEN
128 #else
129 IF ( land_calc_grW ) THEN
130 #endif
131 C-- Initialize run-off arrays.
132 DO j=1,sNy
133 DO i=1,sNx
134 land_runOff(i,j,bi,bj) = 0. _d 0
135 land_enRnOf(i,j,bi,bj) = 0. _d 0
136 ENDDO
137 ENDDO
138 C-- need (later on) ground temp. to be consistent with updated enthalpy:
139 DO k=1,land_nLev
140 DO j=1,sNy
141 DO i=1,sNx
142 IF ( land_frc(i,j,bi,bj).GT.0. ) THEN
143 mWater = land_rhoLiqW*land_waterCap
144 & *land_groundW(i,j,k,bi,bj)
145 grd_HeatCp = land_heatCs + land_CpWater*mWater
146 temp_bf = (land_enthalp(i,j,k,bi,bj)+land_Lfreez*mWater)
147 & / grd_HeatCp
148 temp_af = land_enthalp(i,j,k,bi,bj) / grd_HeatCp
149 land_groundT(i,j,k,bi,bj) =
150 & MIN( temp_bf, MAX(temp_af, 0. _d 0) )
151 ENDIF
152 ENDDO
153 ENDDO
154 ENDDO
155 ENDIF
156
157 IF ( land_calc_snow ) THEN
158 C-- Step forward Snow thickness (also account for rain temperature)
159 ageFac = 1. _d 0 - land_deltaT/timeSnowAge
160 DO j=1,sNy
161 DO i=1,sNx
162 IF ( land_frc(i,j,bi,bj).GT.0. ) THEN
163 mPmE = land_Pr_m_Ev(i,j,bi,bj)
164 enWfx = land_EnWFlux(i,j,bi,bj)
165 enGr1 = land_enthalp(i,j,1,bi,bj)*land_dzF(1)
166 C- snow aging:
167 land_snowAge(i,j,bi,bj) =
168 & ( land_deltaT + land_snowAge(i,j,bi,bj)*ageFac )
169 IF ( enWfx.LT.0. ) THEN
170 C- snow precip in excess (Snow > Evap) :
171 C => start to melt (until ground at freezing point) and then accumulate
172 snowPrec = -enWfx -MAX( enGr1/land_deltaT, 0. _d 0 )
173 snowPrec = MAX( snowPrec*recip_Lfreez , 0. _d 0 )
174 mPmE = mPmE - snowPrec
175 flxEngU(i,j) = enWfx + land_Lfreez*snowPrec
176 hNewSnow = land_deltaT * snowPrec / land_rhoSnow
177 C- refresh snow age:
178 land_snowAge(i,j,bi,bj) = land_snowAge(i,j,bi,bj)
179 & *EXP( -hNewSnow/hNewSnowAge )
180 C- update snow thickness:
181 c land_hSnow(i,j,bi,bj) = land_hSnow(i,j,bi,bj) + hNewSnow
182 C glacier & ice-sheet missing: excess of snow put directly into run-off
183 dhSnowMx = MAX( 0. _d 0,
184 & land_hMaxSnow - land_hSnow(i,j,bi,bj) )
185 dhSnow = MIN( hNewSnow, dhSnowMx )
186 land_hSnow(i,j,bi,bj) = land_hSnow(i,j,bi,bj) + dhSnow
187 mIceDt = land_rhoSnow * (hNewSnow-dhSnow) / land_deltaT
188 land_runOff(i,j,bi,bj) = mIceDt/land_rhoLiqW
189 land_enRnOf(i,j,bi,bj) = -mIceDt*land_Lfreez
190 ELSE
191 C- rain precip (whatever Evap is) or Evap exceeds snow precip :
192 C => snow melts or sublimates
193 c snowMelt = MIN( enWfx*recip_Lfreez ,
194 c & land_hSnow(i,j,bi,bj)*land_rhoSnow/land_deltaT )
195 mSnow = land_hSnow(i,j,bi,bj)*land_rhoSnow
196 dMsn = enWfx*recip_Lfreez*land_deltaT
197 IF ( dMsn .GE. mSnow ) THEN
198 dMsn = mSnow
199 land_hSnow(i,j,bi,bj) = 0. _d 0
200 flxEngU(i,j) = enWfx - land_Lfreez*mSnow/land_deltaT
201 ELSE
202 flxEngU(i,j) = 0. _d 0
203 land_hSnow(i,j,bi,bj) = land_hSnow(i,j,bi,bj)
204 & - dMsn / land_rhoSnow
205 ENDIF
206 c IF (mPmE.GT.0.) land_snowAge(i,j,bi,bj) = timeSnowAge
207 mPmE = mPmE + dMsn/land_deltaT
208 ENDIF
209 flxkup(i,j) = mPmE/land_rhoLiqW
210 c land_Pr_m_Ev(i,j,bi,bj) = mPmE
211 IF ( land_hSnow(i,j,bi,bj).LE. 0. _d 0 )
212 & land_snowAge(i,j,bi,bj) = 0. _d 0
213 C- avoid negative (but very small, < 1.e-34) hSnow that occurs because
214 C of truncation error. Might need to rewrite this part.
215 c IF ( land_hSnow(i,j,bi,bj).LE. 0. _d 0 ) THEN
216 c land_hSnow(i,j,bi,bj) = 0. _d 0
217 c land_snowAge(i,j,bi,bj) = 0. _d 0
218 c ENDIF
219 ENDIF
220 ENDDO
221 ENDDO
222 ELSE
223 DO j=1,sNy
224 DO i=1,sNx
225 flxkup(i,j) = land_Pr_m_Ev(i,j,bi,bj)/land_rhoLiqW
226 flxEngU(i,j) = 0. _d 0
227 ENDDO
228 ENDDO
229 ENDIF
230
231 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
232
233 IF (land_calc_grW) THEN
234 C-- Step forward ground Water:
235
236 DO k=1,land_nLev
237 IF (k.EQ.land_nLev) THEN
238 kp1 = k
239 fractRunOff = 1. _d 0
240 ELSE
241 kp1 = k+1
242 fractRunOff = land_fractRunOff
243 ENDIF
244 fieldCapac = land_waterCap*land_dzF(k)
245
246 DO j=1,sNy
247 DO i=1,sNx
248 IF ( land_frc(i,j,bi,bj).GT.0. ) THEN
249
250 #ifdef LAND_OLD_VERSION
251 IF ( .TRUE. ) THEN
252 IF ( k.EQ.land_nLev ) THEN
253 #else
254 IF ( land_groundT(i,j,k,bi,bj).LT.0. _d 0 ) THEN
255 C- Frozen level: only account for upper level fluxes
256 IF ( flxkup(i,j) .LT. 0. _d 0 ) THEN
257 C- Step forward soil moisture (& enthapy), level k :
258 land_groundW(i,j,k,bi,bj) = land_groundW(i,j,k,bi,bj)
259 & + land_deltaT * flxkup(i,j) / fieldCapac
260 IF ( land_calc_snow )
261 & land_enthalp(i,j,k,bi,bj) = land_enthalp(i,j,k,bi,bj)
262 & + land_deltaT * flxEngU(i,j) / land_dzF(k)
263 ELSE
264 C- Frozen level: incoming water flux goes directly into run-off
265 land_runOff(i,j,bi,bj) = land_runOff(i,j,bi,bj)
266 & + flxkup(i,j)
267 land_enRnOf(i,j,bi,bj) = land_enRnOf(i,j,bi,bj)
268 & + flxEngU(i,j)
269 ENDIF
270 C- prepare fluxes for next level:
271 flxkup(i,j) = 0. _d 0
272 flxEngU(i,j) = 0. _d 0
273
274 ELSE
275
276 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
277 C- Diffusion flux of water, lower interface (k,k+1):
278 IF ( k.EQ.land_nLev .OR.
279 & land_groundT(i,j,kp1,bi,bj).LT.0. _d 0 ) THEN
280 #endif /* LAND_OLD_VERSION */
281 C- no Diffusion of water if one level is frozen :
282 flxkdw(i,j) = 0. _d 0
283 flxEngL = 0. _d 0
284 ELSE
285 flxkdw(i,j) = fieldCapac*
286 & ( land_groundW(i,j,k,bi,bj)
287 & -land_groundW(i,j,kp1,bi,bj) )
288 & / land_wTauDiff
289 C- energy flux associated with water flux: take upwind Temp
290 IF ( flxkdw(i,j).GE.0. ) THEN
291 flxEngL = flxkdw(i,j)*land_rhoLiqW*land_CpWater
292 & *land_groundT(i,j,k,bi,bj)
293 ELSE
294 flxEngL = flxkdw(i,j)*land_rhoLiqW*land_CpWater
295 & *land_groundT(i,j,kp1,bi,bj)
296 ENDIF
297 ENDIF
298
299 C- Step forward soil moisture, level k :
300 groundWnp1 = land_groundW(i,j,k,bi,bj)
301 & + land_deltaT * (flxkup(i,j)-flxkdw(i,j)) / fieldCapac
302
303 C- Water in excess will leave as run-off or go to level below
304 land_groundW(i,j,k,bi,bj) = MIN(1. _d 0, groundWnp1)
305 grdWexcess = ( groundWnp1 - MIN(1. _d 0, groundWnp1) )
306 & *fieldCapac/land_deltaT
307
308 C- Run off: fraction 1-fractRunOff enters level below
309 land_runOff(i,j,bi,bj) = land_runOff(i,j,bi,bj)
310 & + fractRunOff*grdWexcess
311 C- prepare fluxes for next level:
312 flxkup(i,j) = flxkdw(i,j)
313 & + (1. _d 0-fractRunOff)*grdWexcess
314
315 IF ( land_calc_snow ) THEN
316 enthalpGrdW = land_rhoLiqW*land_CpWater
317 & *land_groundT(i,j,k,bi,bj)
318 C-- Account for water fluxes in energy budget: update ground Enthalpy
319 land_enthalp(i,j,k,bi,bj) = land_enthalp(i,j,k,bi,bj)
320 & + ( flxEngU(i,j) - flxEngL - grdWexcess*enthalpGrdW
321 & )*land_deltaT/land_dzF(k)
322
323 land_enRnOf(i,j,bi,bj) = land_enRnOf(i,j,bi,bj)
324 & + fractRunOff*grdWexcess*enthalpGrdW
325 C- prepare fluxes for next level:
326 flxEngU(i,j) = flxEngL
327 & + (1. _d 0-fractRunOff)*grdWexcess*enthalpGrdW
328 ENDIF
329 ENDIF
330 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
331
332 ENDIF
333 ENDDO
334 ENDDO
335
336 ENDDO
337 C-- step forward ground Water: end
338 ENDIF
339
340 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
341
342 IF ( land_calc_grT ) THEN
343 C-- Compute ground temperature from enthalpy (if not already done):
344
345 DO k=1,land_nLev
346 DO j=1,sNy
347 DO i=1,sNx
348 C- Ground Heat capacity, layer k:
349 mWater = land_rhoLiqW*land_waterCap
350 & *land_groundW(i,j,k,bi,bj)
351 grd_HeatCp = land_heatCs + land_CpWater*mWater
352 C temperature below freezing:
353 temp_bf = (land_enthalp(i,j,k,bi,bj)+land_Lfreez*mWater)
354 & / grd_HeatCp
355 C temperature above freezing:
356 temp_af = land_enthalp(i,j,k,bi,bj) / grd_HeatCp
357 #ifdef LAND_OLD_VERSION
358 land_enthalp(i,j,k,bi,bj) =
359 & grd_HeatCp*land_groundT(i,j,k,bi,bj)
360 #else
361 land_groundT(i,j,k,bi,bj) =
362 & MIN( temp_bf, MAX(temp_af, 0. _d 0) )
363 #endif
364 ENDDO
365 ENDDO
366 ENDDO
367
368 IF ( land_impl_grT ) THEN
369 DO j=1,sNy
370 DO i=1,sNx
371 IF ( land_hSnow(i,j,bi,bj).GT.0. _d 0 ) THEN
372 land_skinT(i,j,bi,bj) = MIN(land_skinT(i,j,bi,bj), 0. _d 0)
373 ELSE
374 land_skinT(i,j,bi,bj) = land_groundT(i,j,1,bi,bj)
375 ENDIF
376 ENDDO
377 ENDDO
378 ELSE
379 DO j=1,sNy
380 DO i=1,sNx
381 land_skinT(i,j,bi,bj) = land_groundT(i,j,1,bi,bj)
382 ENDDO
383 ENDDO
384 ENDIF
385
386 C-- Compute ground temperature: end
387 ENDIF
388
389 #endif /* ALLOW_LAND */
390
391 RETURN
392 END

  ViewVC Help
Powered by ViewVC 1.1.22