@@ -56,7 +56,8 @@ module module_levelpool
56
56
subroutine levelpool_init (this , water_elevation , &
57
57
lake_area , weir_elevation , weir_coeffecient , &
58
58
weir_length , dam_length , orifice_elevation , orifice_coefficient , &
59
- orifice_area , max_depth , lake_number )
59
+ orifice_area , max_depth , lake_number , lake_opt )
60
+
60
61
implicit none
61
62
class(levelpool), intent (inout ) :: this ! object being initialized
62
63
real , intent (inout ) :: water_elevation ! meters AMSL
@@ -69,7 +70,9 @@ subroutine levelpool_init(this, water_elevation, &
69
70
real , intent (in ) :: orifice_coefficient ! orifice coefficient
70
71
real , intent (in ) :: orifice_area ! orifice area (meters^2 )
71
72
real , intent (in ) :: max_depth ! max depth of reservoir before overtop (meters)
72
- integer (kind= int64), intent (in ) :: lake_number ! lake number
73
+ integer (kind= int64), intent (in ) :: lake_number ! lake number
74
+ integer , intent (in ) :: lake_opt ! bypass lake physics (2 to use pass- through)
75
+
73
76
character (len= 15 ) :: lake_number_string
74
77
75
78
#ifdef RESERVOIR_D
@@ -114,7 +117,7 @@ subroutine levelpool_init(this, water_elevation, &
114
117
call this%properties%init( lake_area, &
115
118
weir_elevation, weir_coeffecient, weir_length, dam_length, &
116
119
orifice_elevation, orifice_coefficient, &
117
- orifice_area, max_depth, lake_number )
120
+ orifice_area, max_depth, lake_number, lake_opt )
118
121
end if
119
122
this%pointer_allocation_guard = .true.
120
123
@@ -169,6 +172,7 @@ subroutine run_levelpool_reservoir(this, previous_timestep_inflow, inflow, &
169
172
this%state%water_elevation = water_elevation
170
173
171
174
call LEVELPOOL_PHYSICS(this%properties%lake_number, &
175
+ this%properties%lake_opt, &
172
176
previous_timestep_inflow, &
173
177
this%input%inflow, &
174
178
this%output%outflow, &
@@ -217,7 +221,7 @@ end subroutine run_levelpool_reservoir
217
221
! SUBROUTINE LEVELPOOL
218
222
! ------------------------------------------------
219
223
220
- subroutine LEVELPOOL_PHYSICS (ln ,qi0 ,qi1 ,qo1 ,ql ,dt ,H ,ar ,we ,maxh ,wc ,wl ,dl ,oe ,oc ,oa )
224
+ subroutine LEVELPOOL_PHYSICS (ln ,lake_opt , qi0 ,qi1 ,qo1 ,ql ,dt ,H ,ar ,we ,maxh ,wc ,wl ,dl ,oe ,oc ,oa )
221
225
222
226
!! ---------------------------- argument variables
223
227
!! All elevations should be relative to a common base (often belev(k))
@@ -238,9 +242,8 @@ subroutine LEVELPOOL_PHYSICS(ln,qi0,qi1,qo1,ql,dt,H,ar,we,maxh,wc,wl,dl,oe,oc,oa
238
242
real , intent (IN ) :: oa ! orifice area (m^2 )
239
243
real , intent (IN ) :: maxh ! max depth of reservoir before overtop (m)
240
244
integer (kind= int64), intent (IN ) :: ln ! lake number
245
+ integer , intent (in ) :: lake_opt ! reservoir physics options (1 : levelpool, 2 : passthrough)
241
246
242
- !!DJG Add lake option switch here...move up to namelist in future versions...
243
- integer :: LAKE_OPT ! Lake model option (move to namelist later)
244
247
real :: Htmp ! Temporary assign of incoming lake el. (m)
245
248
246
249
!! ---------------------------- local variables
@@ -254,22 +257,20 @@ subroutine LEVELPOOL_PHYSICS(ln,qi0,qi1,qo1,ql,dt,H,ar,we,maxh,wc,wl,dl,oe,oc,oa
254
257
!! ---------------------------- subroutine body: from chow, mad mays. pg. 252
255
258
!! -- determine from inflow hydrograph
256
259
257
-
258
- !!DJG Set hardwire for LAKE_OPT...move specification of this to namelist in
259
- !future versions...
260
- LAKE_OPT = 2
261
260
Htmp = H !temporary set of incoming lake water elevation...
262
261
!hdiff_vol = 0.0
263
262
!qdiff_vol = 0.0
264
263
265
264
!!DJG IF - block for lake model option 1 - outflow= inflow, 2 - Chow et al level
266
265
!pool, .....
267
- if (LAKE_OPT == 1 ) then ! If - block for simple pass through scheme....
268
-
266
+ if (LAKE_OPT == 2 ) then ! If - block for simple pass through scheme....
267
+ #ifdef RESERVOIR_D
268
+ write (6 ,* ) " LEVELPOOL LAKE_OPT=2, using reservoir passthrough"
269
+ #endif
269
270
qo1 = qi1 ! Set outflow equal to inflow at current time
270
271
H = Htmp ! Set new lake water elevation to incoming lake el.
271
272
272
- else if (LAKE_OPT == 2 ) then ! If - block for Chow et al level pool scheme
273
+ else if (LAKE_OPT == 1 ) then ! If - block for Chow et al level pool scheme
273
274
274
275
It = qi0
275
276
Itdt_3 = qi0 + ((qi1 + ql - qi0) * 0.33 )
0 commit comments