/[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.1 - (show annotations) (download)
Thu Jun 12 17:54:22 2003 UTC (20 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint51e_post, checkpoint51k_post, checkpoint52l_pre, checkpoint52e_pre, hrcube4, checkpoint52j_post, checkpoint51o_pre, checkpoint52e_post, checkpoint51n_pre, checkpoint51l_post, checkpoint51q_post, checkpoint51j_post, hrcube_1, checkpoint50h_post, branch-netcdf, checkpoint52d_pre, checkpoint51r_post, checkpoint52k_post, checkpoint52b_pre, checkpoint51a_post, checkpoint51c_post, checkpoint51f_pre, checkpoint51, checkpoint51o_post, checkpoint51p_post, checkpoint52a_pre, checkpoint51i_post, checkpoint52, checkpoint51f_post, checkpoint52d_post, checkpoint51b_post, checkpoint51b_pre, checkpoint52a_post, checkpoint52b_post, checkpoint52f_post, branchpoint-genmake2, checkpoint52c_post, checkpoint51h_pre, checkpoint51l_pre, checkpoint51g_post, ecco_c52_e35, hrcube5, checkpoint51d_post, checkpoint52i_post, checkpoint52j_pre, checkpoint51t_post, checkpoint51n_post, checkpoint51i_pre, checkpoint52i_pre, checkpoint51u_post, checkpoint52h_pre, checkpoint52f_pre, hrcube_2, hrcube_3, checkpoint51m_post, checkpoint51s_post
Branch point for: branch-nonh, branch-genmake2, tg2-branch, checkpoint51n_branch, netcdf-sm0
A simple land model implemented for AIM (_v23) atmospheric physics

1 C $Header: $
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 #include "PARAMS.h"
31 c #include "GRID.h"
32 c #include "DYNVARS.h"
33
34 C !INPUT/OUTPUT PARAMETERS:
35 C == Routine arguments ==
36 C land_frc :: land fraction [0-1]
37 C bi,bj :: Tile index
38 C myTime :: Current time of simulation ( s )
39 C myIter :: Current iteration number in simulation
40 C myThid :: Number of this instance of the routine
41 _RS land_frc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
42 INTEGER bi, bj, myIter, myThid
43 _RL myTime
44 CEOP
45
46 #ifdef ALLOW_LAND
47 C == Local variables ==
48 C i,j,k :: loop counters
49 C kp1 :: k+1
50 C grd_HeatCp :: Heat capacity of the ground
51 C fieldCapac :: field capacity (of water) [m]
52 C ground_dTdt :: ground temperature tendency
53 C ground_dWdt :: soil moisture tendency
54 C flxkup :: downward flux, upper interface (k-1,k)
55 C flxdwn :: downward flux, lower interface (k,k+1)
56 C fractRunOff :: fraction of water in excess which leaves as runoff
57 C grdWexcess :: ground water in excess [m/s]
58 _RL grd_HeatCp, fieldCapac, ground_dTdt, ground_dWdt
59 _RL fractRunOff, grdWexcess, groundWnp1
60 _RL flxkup(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61 _RL flxkdw(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
62 INTEGER i,j,k,kp1
63
64 IF (land_calc_grT) THEN
65 C-- Step forward ground temperature:
66
67 DO k=1,land_nLev
68 kp1 = MIN(k+1,land_nLev)
69
70 IF (k.EQ.1) THEN
71 DO j=1,sNy
72 DO i=1,sNx
73 flxkup(i,j) = land_HeatFlx(i,j,bi,bj)
74 ENDDO
75 ENDDO
76 ELSE
77 DO j=1,sNy
78 DO i=1,sNx
79 flxkup(i,j) = flxkdw(i,j)
80 ENDDO
81 ENDDO
82 ENDIF
83
84 DO j=1,sNy
85 DO i=1,sNx
86 IF ( land_frc(i,j,bi,bj).GT.0. ) THEN
87 C- Thermal conductivity flux, lower interface (k,k+1):
88 flxkdw(i,j) = land_grdLambda*
89 & ( land_groundT(i,j,k,bi,bj)
90 & -land_groundT(i,j,kp1,bi,bj) )
91 & *land_rec_dzC(kp1)
92
93 C- Ground Heat capacity, layer k:
94 grd_HeatCp = land_heatCs
95 & + land_heatCw*land_groundW(i,j,k,bi,bj)
96 & *land_waterCap
97
98 C- Net temperature tendency
99 ground_dTdt = (flxkup(i,j)-flxkdw(i,j))
100 & / (grd_HeatCp*land_dzF(k))
101
102 C- Step forward ground temperature, level k :
103 land_groundT(i,j,k,bi,bj) = land_groundT(i,j,k,bi,bj)
104 & + land_deltaT*ground_dTdt
105
106 ENDIF
107 ENDDO
108 ENDDO
109
110 ENDDO
111 C-- step forward ground temperature: end
112 ENDIF
113
114 IF (land_calc_grW) THEN
115 C-- Step forward ground Water:
116
117 DO k=1,land_nLev
118 IF (k.EQ.land_nLev) THEN
119 kp1 = k
120 fractRunOff = 1. _d 0
121 ELSE
122 kp1 = k+1
123 fractRunOff = land_fractRunOff
124 ENDIF
125 fieldCapac = land_waterCap*land_dzF(k)
126
127 IF (k.EQ.1) THEN
128 DO j=1,sNy
129 DO i=1,sNx
130 flxkup(i,j) = land_Pr_m_Ev(i,j,bi,bj)
131 land_runOff(i,j,bi,bj) = 0. _d 0
132 ENDDO
133 ENDDO
134 ELSE
135 DO j=1,sNy
136 DO i=1,sNx
137 flxkup(i,j) = flxkdw(i,j)
138 ENDDO
139 ENDDO
140 ENDIF
141
142 DO j=1,sNy
143 DO i=1,sNx
144 IF ( land_frc(i,j,bi,bj).GT.0. ) THEN
145 C- Diffusion flux of soil moisture, lower interface (k,k+1):
146 flxkdw(i,j) = fieldCapac*
147 & ( land_groundW(i,j,k,bi,bj)
148 & -land_groundW(i,j,kp1,bi,bj) )
149 & / land_wTauDiff
150
151 C- Net soil moisture tendency
152 ground_dWdt = (flxkup(i,j)-flxkdw(i,j)) / fieldCapac
153
154 C- Step forward soil moisture, level k :
155 groundWnp1 = land_groundW(i,j,k,bi,bj)
156 & + land_deltaT*ground_dWdt
157 land_groundW(i,j,k,bi,bj) = MIN(1. _d 0, groundWnp1)
158
159 C- Run off: fraction 1-fractRunOff enters level below
160 grdWexcess = ( groundWnp1 - MIN(1. _d 0, groundWnp1) )
161 & *fieldCapac/land_deltaT
162 flxkdw(i,j) = flxkdw(i,j)
163 & + (1. _d 0-fractRunOff)*grdWexcess
164 land_runOff(i,j,bi,bj) = land_runOff(i,j,bi,bj)
165 & + fractRunOff*grdWexcess
166 ENDIF
167 ENDDO
168 ENDDO
169
170 ENDDO
171 C-- step forward ground Water: end
172 ENDIF
173
174 #endif /* ALLOW_LAND */
175
176 RETURN
177 END

  ViewVC Help
Powered by ViewVC 1.1.22