Skip to content

Commit 42baefd

Browse files
authored
Merge pull request #37 from YifanCheng/RBM_res_develop
Fix instability in RBM (This pull request was merged as this is a stable version of RBM-2L)
2 parents a621a5a + c1a667f commit 42baefd

17 files changed

+650
-342
lines changed

src/Begin.f90

Lines changed: 42 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,11 @@ Subroutine BEGIN(param_file,spatial_file)
1313
character (len=200):: param_file,source_file,spatial_file
1414
!
1515
integer:: Julian
16-
integer:: head_name,trib_cell
16+
integer:: head_name,trib_cell
1717
integer:: jul_start,main_stem,nyear1,nyear2,nc,ncell,nseg
1818
integer:: ns_max_test,node,ncol,nrow,nr,cum_sgmnt
1919
!
20-
integer:: nreservoir
20+
integer:: nreservoir,nseg_temp,nseg_cum
2121
!
2222
logical:: first_cell,source
2323
!
@@ -83,6 +83,7 @@ Subroutine BEGIN(param_file,spatial_file)
8383
allocate(res_start_node(nres))
8484
allocate(res_end_node(nres))
8585
allocate(res_capacity_mcm(nres))
86+
allocate(nseg_out(nreach,heat_cells,nseg_out_num))
8687
!
8788
! Start reading the reach date and initialize the reach index, NR
8889
! and the cell index, NCELL
@@ -117,12 +118,13 @@ Subroutine BEGIN(param_file,spatial_file)
117118
! Initialize NSEG, the total number of segments in this reach
118119
!
119120
nseg=0
121+
nseg_cum=0
120122
write(*,*) ' Starting to read reach ',nr
121123
!
122124
! Read the number of cells in this reach, the headwater #,
123125
! the number of the cell where it enters the next higher order stream,
124126
! the headwater number of the next higher order stream it enters, and
125-
! the river mile of the headwaters.
127+
! the river mile of the headwaters.
126128
!
127129
read(90,'(i5,11x,i4,10x,i5,15x,i5,15x,f10.0,i5)') no_cells(nr) &
128130
,head_name,trib_cell,main_stem,rmile0
@@ -139,7 +141,7 @@ Subroutine BEGIN(param_file,spatial_file)
139141
if (trib_cell.gt.0) then
140142
no_tribs(trib_cell) = no_tribs(trib_cell)+1
141143
trib(trib_cell,no_tribs(trib_cell)) = nr
142-
end if
144+
end if
143145
!
144146
! Reading Mohseni parameters for each headwaters (UW_JRY_2011/06/18)
145147
!
@@ -165,7 +167,7 @@ Subroutine BEGIN(param_file,spatial_file)
165167
end if
166168
!
167169
! The headwaters index for each cell in this reach is given
168-
! in the order the cells are read
170+
! in the order the cells are read
169171
!
170172
! Card Type 3. Cell indexing #, Node # Row # Column Lat Long RM
171173
!
@@ -175,14 +177,14 @@ Subroutine BEGIN(param_file,spatial_file)
175177
if (reservoir) then
176178
read(90,'(5x,i5,5x,i5,8x,i5,6x,a8,6x,a10,7x,f10.0,f5.0,i6)') &
177179
node,nrow,ncol,lat,long,rmile1,ndelta(ncell),res_num(ncell)
178-
write(*,*) node,nrow,ncol,lat,long,rmile1,ndelta(ncell),res_num(ncell)
180+
!write(*,*) node,nrow,ncol,lat,long,rmile1,ndelta(ncell),res_num(ncell)
179181
if(res_num(ncell) .gt. 0) then
180182
res_pres(ncell) = .TRUE.
181183
end if
182184
else
183185
read(90,'(5x,i5,5x,i5,8x,i5,6x,a8,6x,a10,7x,f10.0,f5.0)') &
184186
node,nrow,ncol,lat,long,rmile1,ndelta(ncell)
185-
write(*,*) node,nrow,ncol,lat,long,rmile1,ndelta(ncell)
187+
!write(*,*) node,nrow,ncol,lat,long,rmile1,ndelta(ncell)
186188
end if
187189
!
188190
! Set the number of segments of the default, if not specified
@@ -197,9 +199,16 @@ Subroutine BEGIN(param_file,spatial_file)
197199
! Added variable ndelta (UW_JRY_2011/03/15)
198200
!
199201
dx(ncell)=miles_to_ft*(rmile0-rmile1)/ndelta(ncell)
200-
rmile0=rmile1
201-
nndlta=0
202-
200 continue
202+
rmile0=rmile1
203+
!
204+
! Here we define the output segments
205+
!
206+
do nseg_temp=1,nseg_out_num
207+
nseg_out(nr,ncell,nseg_temp)=nseg_cum+ndelta(ncell)*nseg_temp/(nseg_out_num)
208+
end do
209+
nseg_cum = nseg_cum+ndelta(ncell)
210+
nndlta=0
211+
200 continue
203212
nndlta=nndlta+1
204213
nseg=nseg+1
205214
segment_cell(nr,nseg)=ncell
@@ -208,20 +217,25 @@ Subroutine BEGIN(param_file,spatial_file)
208217
!
209218
! Write Segment List for mapping to temperature output (UW_JRY_2008/11/19)
210219
!
211-
open(22,file=TRIM(spatial_file),status='unknown') ! (changed by WUR_WF_MvV_2011/01/05)
212-
write(22,'(4i6,1x,a8,1x,a10,f5.0)') nr,ncell,nrow,ncol,lat,long,nndlta
220+
do nseg_temp=1,nseg_out_num
221+
if (nseg_out(nr,ncell,nseg_temp).eq.nseg) then
222+
open(22,file=TRIM(spatial_file),status='unknown') ! (changed by WUR_WF_MvV_2011/01/05)
223+
write(22,'(4i6,1x,a8,1x,a10,i5)') nr,ncell,nrow,ncol,lat,long,nseg_temp
224+
end if
225+
end do
213226
!
214227
!
215228
!
216229
! Added variable ndelta (UW_JRY_2011/03/15)
217230
!
218231
if(nndlta.lt.ndelta(ncell)) go to 200
219-
no_celm(nr)=nseg
232+
no_celm(nr)=nseg
220233
segment_cell(nr,nseg)=ncell
221-
x_dist(nr,nseg)=miles_to_ft*rmile1
234+
x_dist(nr,nseg)=miles_to_ft*rmile1
235+
write(*,*) 'number of segment in reach', nr, nseg
222236
!
223237
! End of cell and segment loop
224-
!
238+
!
225239
end do
226240
!
227241
! If this is a reach that is tributary to another, set the confluence cell to the previous
@@ -233,26 +247,26 @@ Subroutine BEGIN(param_file,spatial_file)
233247
conflnce(trib_cell,no_tribs(trib_cell)) = ncell
234248
end if
235249

236-
if(ns_max_test.lt.nseg) ns_max_test=nseg
237-
!
250+
if(ns_max_test.lt.nseg) ns_max_test=nseg
251+
!
238252
! End of reach loop
239-
!
253+
!
240254
end do
241255
if(ns_max_test.gt.ns_max) then
242256
write(*,*) 'RBM is terminating because'
243257
write(*,*) 'NS_MAX exceeded. Change NS_MAX in Block_Network to: ',ns_max_test
244258
stop
245-
end if
246-
!
247-
nwpd=1
248-
xwpd=nwpd
249-
dt_comp=86400./xwpd
259+
end if
260+
!
261+
nwpd=1
262+
xwpd=nwpd
263+
dt_comp=86400./xwpd
264+
!
265+
! ******************************************************
266+
! Return to RMAIN
267+
! ******************************************************
250268
!
251-
! ******************************************************
252-
! Return to RMAIN
253-
! ******************************************************
254-
!
255-
900 continue
269+
900 continue
256270
!
257271
!
258272
end subroutine BEGIN

src/Block_Energy.f90

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,11 +32,14 @@ module Block_Energy
3232
! Some important constants
3333
!
3434
real :: lvp,rb,rho
35+
real :: deriv_2nd,error_EE
36+
real :: deriv_conv,deriv_evap,deriv_ws
37+
real :: temp_equil,time_equil
3538
real,parameter :: evap_coeff=1.5e-9 !Lake Hefner coefficient, 1/meters
3639
real,parameter :: pf=0.640,pi=3.14159
3740
real,parameter :: rfac=304.8 !rho/Cp kg/meter**3/Kilocalories/kg/Deg K
3841
real,parameter :: sec_day = 86400 !number of seconds in a day
3942
real,parameter :: a_z=0.408, b_z=0.392 !Leopold parameter for depth
40-
real,parameter :: a_w=4.346, b_w=0.520 !Leopold parameter for width
43+
real,parameter :: a_w=4.346, b_w=0.520 !Leopold parameter for width
4144
!
4245
end module Block_Energy

src/Block_Hydro.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,8 +2,8 @@
22
! Module for hydraulic characteristics and water quality constituents of the basin
33
!
44
module Block_Hydro
5-
integer, dimension(2000):: no_dt,nstrt_elm
6-
real, dimension(2000) :: dt_part,x_part
5+
integer, dimension(2500):: no_dt,nstrt_elm
6+
real, dimension(2500) :: dt_part,x_part
77
!
88
real, dimension(:), allocatable :: depth
99
real, dimension(:), allocatable :: width

src/Block_Network.f90

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,18 +7,29 @@ Module Block_Network
77
!
88
integer, dimension(:,:), allocatable::conflnce,reach_cell,segment_cell,trib
99
!
10+
integer, dimension(:,:,:), allocatable::nseg_out
1011
!
1112
! Integer variables
1213
!
1314
integer:: flow_cells,heat_cells
1415
integer:: ndays,nreach,ntrb,nwpd
15-
integer,parameter::ns_max=200
16+
integer,parameter::ns_max=3000
17+
integer,parameter::nseg_out_num=2
1618
integer:: start_year,start_month,start_day
1719
integer:: end_year,end_month,end_day
20+
integer:: numsub !number of subdaily timestep
21+
integer:: nsub
1822
!
1923
! Real variables
2024
!
2125
real :: delta_n,n_default=2
2226
real :: dt_comp
27+
real :: dt_res
2328
real, dimension(:), allocatable :: ndelta
29+
!
30+
! Logical variables
31+
!
32+
33+
34+
2435
end module Block_Network

src/Block_Reservoir.f90

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,9 @@ module Block_Reservoir
1212
logical, dimension(:), allocatable :: res_trib_calc !
1313
logical, dimension(:), allocatable :: res_stratif_start !
1414
logical, dimension(:), allocatable :: res_turnover !
15+
logical :: exceed_error_bound
16+
logical :: adjust_timestep
17+
logical :: recalculate_volume
1518
!
1619
!
1720
real, parameter :: depth_e_frac=0.4, depth_h_frac=0.6
@@ -23,6 +26,13 @@ module Block_Reservoir
2326
real :: flow_epi_hyp_x, outflow_x
2427
real :: res_vol_delta_x, vol_change_hyp_x, vol_change_epi_x
2528
real :: res_storage_pre, res_storage_post
29+
!
30+
! Error estimation
31+
!
32+
real :: m11,m12,m21,m22
33+
real :: const1,const2
34+
real :: error_e,error_h
35+
real, parameter :: error_threshold = 0.1
2636
real, dimension(:), allocatable :: K_z
2737
real, dimension(:), allocatable :: depth_e, depth_h
2838
real, dimension(:), allocatable :: density_epil, density_hypo
@@ -54,6 +64,7 @@ module Block_Reservoir
5464
real, dimension(:), allocatable :: qsurf_tot
5565
real, dimension(:), allocatable :: res_capacity_mcm
5666
real, dimension(:), allocatable :: volume_h_min
67+
real, dimension(:), allocatable :: volume_e_min
5768
real, dimension(:,:), allocatable :: res_storage
5869
!
5970
!

0 commit comments

Comments
 (0)