Skip to content

Commit d126988

Browse files
committed
Update to 2012Rev664
1 parent fcf4df1 commit d126988

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

99 files changed

+2147
-447
lines changed

VERSIONS

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,3 @@
11
VERSION_MAJOR 2012
2-
VERSION_MINOR 637
2+
VERSION_MINOR 664
33
VERSION_PATCH

src/addh.f

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,10 +6,11 @@ subroutine addh
66
!! name |units |definition
77
!! ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~ ~
88
!! hhvaroute(:,:,:)|varies |routing storage array for hourly time step
9-
!! ievent |none |rainfall/runoff code
9+
! ievent |none |rainfall/runoff code
1010
!! |0 daily rainfall/curve number technique
1111
!! |1 sub-daily rainfall/Green&Ampt/hourly
1212
!! | routing
13+
!! |3 sub-daily rainfall/Green&Ampt/hourly routing
1314
!! ihout |none |outflow hydrograph storage location number
1415
!! inum1 |none |hydrograph storage location number of
1516
!! |first dataset to be added

src/allocate_parms.f

Lines changed: 97 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -55,11 +55,9 @@ subroutine allocate_parms
5555

5656
!! initialize variables
5757
mvaro = 33
58-
mhruo = 78
58+
mhruo = 79
5959
mrcho = 62
60-
! msubo = 18
61-
! changed for jennifer b
62-
msubo = 22
60+
msubo = 24
6361
mstdo = 113
6462
motot = 600 !! (50 years limit)
6563

@@ -414,6 +412,7 @@ subroutine allocate_parms
414412
allocate (sub_lat(msub))
415413
allocate (sub_latq(msub))
416414
allocate (sub_tileq(msub))
415+
allocate (sub_vaptile(msub))
417416
allocate (sub_latno3(msub))
418417
allocate (sub_minp(msub))
419418
allocate (sub_minpa(msub))
@@ -1335,6 +1334,8 @@ subroutine allocate_parms
13351334
allocate (wtab_mx(mhru))
13361335
allocate (wet_chla(mhru))
13371336
allocate (wet_fr(mhru))
1337+
allocate (iwetgw(mhru))
1338+
allocate (iwetile(mhru))
13381339
allocate (wet_k(mhru))
13391340
allocate (wet_mxsa(mhru))
13401341
allocate (wet_mxvol(mhru))
@@ -1415,9 +1416,9 @@ subroutine allocate_parms
14151416
allocate (hrupsty(mpst,4,mhru))
14161417
allocate (icols(mhruo))
14171418
allocate (ipdvas(mhruo))
1418-
allocate (hrumono(73,mhru))
1419-
allocate (hruyro(73,mhru))
1420-
allocate (hruaao(73,mhru))
1419+
allocate (hrumono(74,mhru))
1420+
allocate (hruyro(74,mhru))
1421+
allocate (hruaao(74,mhru))
14211422
allocate (wtrmon(40,mhru))
14221423
allocate (wtryr(40,mhru))
14231424
allocate (wtraa(40,mhru))
@@ -1658,26 +1659,63 @@ subroutine allocate_parms
16581659
allocate (psp_store(mlyr,mhru))
16591660
allocate (ssp_store(mlyr,mhru))
16601661
allocate (sol_cal(mlyr,mhru))
1661-
allocate (sol_ph(mlyr,mhru))
1662+
allocate (sol_ph(mlyr,mhru))
16621663
allocate (harv_min(mhru))
16631664
allocate (fstap(mfdb))
16641665
allocate (min_res(mhru))
16651666
allocate (so_res(20,mhru))
16661667
allocate (so_res_flag(20,mhru))
1667-
allocate (ro_bmp_flag (20,mhru))
1668-
allocate (ro_bmp_sed(20,mhru))
1669-
allocate (ro_bmp_pp(20,mhru))
1668+
allocate (ro_bmp_flag(20,mhru))
1669+
allocate (ro_bmp_flo(20,mhru))
1670+
allocate (ro_bmp_sed(20,mhru))
1671+
allocate (ro_bmp_pp(20,mhru))
16701672
allocate (ro_bmp_sp(20,mhru))
16711673
allocate (ro_bmp_pn(20,mhru))
16721674
allocate (ro_bmp_sn(20,mhru))
16731675
allocate (ro_bmp_bac(20,mhru))
1676+
1677+
allocate (ro_bmp_flos(20,mhru))
1678+
allocate (ro_bmp_seds(20,mhru))
1679+
allocate (ro_bmp_pps(20,mhru))
1680+
allocate (ro_bmp_sps(20,mhru))
1681+
allocate (ro_bmp_pns(20,mhru))
1682+
allocate (ro_bmp_sns(20,mhru))
1683+
allocate (ro_bmp_bacs(20,mhru))
1684+
1685+
allocate (ro_bmp_flot(20,mhru))
1686+
allocate (ro_bmp_sedt(20,mhru))
1687+
allocate (ro_bmp_ppt(20,mhru))
1688+
allocate (ro_bmp_spt(20,mhru))
1689+
allocate (ro_bmp_pnt(20,mhru))
1690+
allocate (ro_bmp_snt(20,mhru))
1691+
allocate (ro_bmp_bact(20,mhru))
1692+
16741693
allocate (bmp_flag(mhru))
1694+
1695+
allocate (bmp_flo(mhru))
16751696
allocate (bmp_sed(mhru))
16761697
allocate (bmp_pp(mhru))
16771698
allocate (bmp_sp(mhru))
16781699
allocate (bmp_pn(mhru))
16791700
allocate (bmp_sn(mhru))
16801701
allocate (bmp_bac(mhru))
1702+
1703+
allocate (bmp_flos(mhru))
1704+
allocate (bmp_seds(mhru))
1705+
allocate (bmp_pps(mhru))
1706+
allocate (bmp_sps(mhru))
1707+
allocate (bmp_pns(mhru))
1708+
allocate (bmp_sns(mhru))
1709+
allocate (bmp_bacs(mhru))
1710+
1711+
allocate (bmp_flot(mhru))
1712+
allocate (bmp_sedt(mhru))
1713+
allocate (bmp_ppt(mhru))
1714+
allocate (bmp_spt(mhru))
1715+
allocate (bmp_pnt(mhru))
1716+
allocate (bmp_snt(mhru))
1717+
allocate (bmp_bact(mhru))
1718+
16811719
!retention irrigation
16821720
allocate(ri_sed(msub,10),ri_fr(msub,10),ri_dim(msub,10),
16831721
& ri_im(msub,10),ri_iy(msub,10),ri_sa(msub,10),ri_vol(msub,10),
@@ -1698,8 +1736,55 @@ subroutine allocate_parms
16981736
& wtp_sdc2(mhyd),wtp_sdc3(mhyd),wtp_pdia(mhyd),wtp_plen(mhyd),
16991737
& wtp_pmann(mhyd),wtp_ploss(mhyd),wtp_k(mhyd),
17001738
& wtp_dp(mhyd),wtp_sedi(mhyd),wtp_sede(mhyd),wtp_qi(mhyd))
1701-
17021739

1740+
!! LID simulations
1741+
!! Common variable
1742+
!! van Genuchten equation's coefficients
1743+
allocate(lid_vgcl,lid_vgcm,lid_qsurf_total,
1744+
& lid_farea_sum)
1745+
allocate(lid_cuminf_last(mhru,4),lid_sw_last(mhru,4),
1746+
& interval_last(mhru,4),lid_f_last(mhru,4),lid_cumr_last(mhru,4),
1747+
& lid_str_last(mhru,4),lid_farea(mhru,4),lid_qsurf(mhru,4),
1748+
& lid_sw_add(mhru,4),lid_cumqperc_last(mhru,4),
1749+
& lid_cumirr_last(mhru,4),lid_excum_last(mhru,4)) !! nbs
1750+
1751+
!! Green Roof
1752+
allocate(gr_onoff(msub,mudb),gr_imo(msub,mudb),gr_iyr(msub,mudb),
1753+
& gr_farea(msub,mudb),gr_solop(msub,mudb),gr_etcoef(msub,mudb),
1754+
& gr_fc(msub,mudb),gr_wp(msub,mudb),gr_ksat(msub,mudb),
1755+
& gr_por(msub,mudb),gr_hydeff(msub,mudb),gr_soldpt(msub,mudb),
1756+
& gr_dummy1(msub,mudb),gr_dummy2(msub,mudb),gr_dummy3(msub,mudb),
1757+
& gr_dummy4(msub,mudb),gr_dummy5(msub,mudb))
1758+
1759+
!! Rain Garden
1760+
allocate(rg_onoff(msub,mudb),rg_imo(msub,mudb),rg_iyr(msub,mudb),
1761+
& rg_farea(msub,mudb),rg_solop(msub,mudb),rg_etcoef(msub,mudb),
1762+
& rg_fc(msub,mudb),rg_wp(msub,mudb),rg_ksat(msub,mudb),
1763+
& rg_por(msub,mudb),rg_hydeff(msub,mudb),rg_soldpt(msub,mudb),
1764+
& rg_dimop(msub,mudb),rg_sarea(msub,mudb),rg_vol(msub,mudb),
1765+
& rg_sth(msub,mudb),rg_sdia(msub,mudb),rg_bdia(msub,mudb),
1766+
& rg_sts(msub,mudb),rg_orifice(msub,mudb),rg_oheight(msub,mudb),
1767+
& rg_odia(msub,mudb),rg_dummy1(msub,mudb),rg_dummy2(msub,mudb),
1768+
& rg_dummy3(msub,mudb),rg_dummy4(msub,mudb),rg_dummy5(msub,mudb))
1769+
1770+
!! CiStern
1771+
allocate(cs_onoff(msub,mudb),cs_imo(msub,mudb),cs_iyr(msub,mudb),
1772+
& cs_grcon(msub,mudb),cs_farea(msub,mudb),cs_vol(msub,mudb),
1773+
& cs_rdepth(msub,mudb),cs_dummy1(msub,mudb),cs_dummy2(msub,mudb),
1774+
& cs_dummy3(msub,mudb),cs_dummy4(msub,mudb),cs_dummy5(msub,mudb))
1775+
1776+
!! Poropus paVement
1777+
allocate(pv_onoff(msub,mudb),pv_imo(msub,mudb),pv_iyr(msub,mudb),
1778+
& pv_grvdep(msub,mudb),pv_grvpor(msub,mudb),pv_farea(msub,mudb),
1779+
& pv_solop(msub,mudb),pv_drcoef(msub,mudb),pv_fc(msub,mudb),
1780+
& pv_wp(msub,mudb),pv_ksat(msub,mudb),pv_por(msub,mudb),
1781+
& pv_hydeff(msub,mudb),pv_soldpt(msub,mudb),pv_dummy1(msub,mudb),
1782+
& pv_dummy2(msub,mudb),pv_dummy3(msub,mudb),pv_dummy4(msub,mudb),
1783+
& pv_dummy5(msub,mudb))
1784+
1785+
!! LID general
1786+
allocate(lid_onoff(msub,mudb))
1787+
17031788
!! By Zhang for C/N cycling
17041789
!! ============================
17051790
!allocate(sol_PH(mlyr,mhru))

src/alph.f

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -12,10 +12,11 @@ subroutine alph(iwave)
1212
!! |used for a given process
1313
!! idt |minutes |length of time step used to report
1414
!! |precipitation data for sub-daily modeling
15-
!! ievent |none |rainfall/runoff code
16-
!! |0 daily rainfall/curve number technique
17-
!! |1 sub-daily rainfall/Green&Ampt/hourly
18-
!! | routing
15+
!! ievent |none |rainfall/runoff code
16+
!! |0 daily rainfall/curve number technique
17+
!! |1 sub-daily rainfall/Green&Ampt/hourly
18+
!! | routing
19+
!! |3 sub-daily rainfall/Green&Ampt/hourly routing
1920
!! ihru |none |HRU number
2021
!! iwave |none |flag to differentiate calculation of HRU and
2122
!! |subbasin sediment calculation

src/anfert.f

Lines changed: 24 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -217,7 +217,11 @@ subroutine anfert
217217
if (fminn(ifrt) > 0.0001) then
218218
dwfert = targn / fminn(ifrt)
219219
else
220-
dwfert = 0.
220+
!! Naresh (npai@stone-env.com) commented this line on 4/12/2016
221+
!! for cases where fmin(ifrt) = 0 (e.g. for elemental P fertilizer)
222+
!! setting this to targn, further edits made around line 317
223+
!! dwfert = 0.
224+
dwfert = targn
221225
endif
222226

223227
!! add bacteria to surface layer
@@ -313,18 +317,33 @@ subroutine anfert
313317

314318
!! check for P stress
315319
tfp = 0.
316-
if (strsp(j) <= 0.75) then
317-
tfp = fminn(ifrt) / 7.
320+
!! Naresh (npai@stone-env.com) edited on 4/12/2016
321+
!! to handle fertilizers which have fminn(ifrt) = 0 (e.g. elemental P)
322+
!! if (strsp(j) <= 0.75) then
323+
!! tfp = fminn(ifrt) / 7.
324+
!! else
325+
!! tfp = fminp(ifrt)
326+
!! end if
327+
328+
if (strsp(j) <= 0.75 .and. fminn(ifrt) > 0.0001) then
329+
tfp = fminn(ifrt) / 7. !! all other fertilizers
330+
autop = autop + dwfert *(tfp + forgp(ifrt))
331+
else if (strsp(j) <= 0.75 .and. fminn(ifrt) == 0) then
332+
tfp = 1/7. !! elemental P cases
333+
autop = autop + dwfert *(tfp + forgp(ifrt))
318334
else
319-
tfp = fminp(ifrt)
335+
tfp = 0 !! no P stress, plant doesn't need any P
336+
autop=0
320337
end if
321338
sol_solp(ly,j) = sol_solp(ly,j) + xx * dwfert * tfp
322339
end do
323340
324341
325342
!! summary calculations
326343
auton = auton + dwfert * (fminn(ifrt) + forgn(ifrt))
327-
autop = autop + dwfert * (tfp + forgp(ifrt))
344+
!! Naresh ([email protected]) commented this code on 4/12/2016
345+
!! and moved it above to handle elemental P auto-fertilization
346+
!! autop = autop + dwfert *(tfp + forgp(ifrt))
328347
tauton(j) = tauton(j) + auton
329348
tautop(j) = tautop(j) + autop
330349
if (curyr > nyskip) then

src/apex_day.f

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ subroutine apex_day
1313
!! |0 daily rainfall/curve number technique
1414
!! |1 sub-daily rainfall/Green&Ampt/hourly
1515
!! | routing
16+
!! |3 sub-daily rainfall/Green&Ampt/hourly routing
1617
!! inum1 |none |reach number
1718
!! ifirstr(:) |none |measured data search code
1819
!! |0 first day of measured data located in file

src/ascrv.f

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -57,6 +57,5 @@ subroutine ascrv(x1,x2,x3,x4,x5,x6)
5757
x6 = (xx - Log(x4/x2 - x4)) / (x4 - x3)
5858
x5 = xx + (x3 * x6)
5959

60-
6160
return
6261
end

src/biozone.f

Lines changed: 6 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -132,9 +132,9 @@ subroutine biozone()
132132
real*8 rnit, rdenit, rbio, rmort, rrsp, rslg, rbod, rfcoli
133133
real*8 nh3_begin, nh3_end, nh3_inflw_ste, no3_begin, no3_end
134134
real*8 no3_inflow_ste, bio_steintobz,bio_outbz,bza,qi,nperc
135-
real*8 nh3_init, no3_init, hvol, solpconc, solpsorb, qlyr,qsrf
136-
real*8 n1,n2,n3,n4,n5,n6,n7,n8,p1,p2,p3,p4
137-
real*8 solp_init,solp_begin,solp_end,svolp,totalp,ctmp,plch
135+
real*8 hvol, solpconc, solpsorb, qlyr,qsrf
136+
real*8 n2,n3,n5,n6,n7,n8,p2,p3,p4
137+
real*8 solp_begin,solp_end,svolp,totalp,ctmp,plch
138138

139139
j = ihru
140140
nly = sol_nly(j)
@@ -160,10 +160,6 @@ subroutine biozone()
160160

161161
xx = qin / hru_ha(j) / 1000.
162162

163-
nh3_init = sol_nh3(bz_lyr,j)
164-
no3_init = sol_no3(bz_lyr,j)
165-
solp_init = sol_solp(bz_lyr,j)
166-
167163
!! Failing system: STE saturates upper soil layers
168164
if (isep_opt(j)==2) then
169165

@@ -323,22 +319,19 @@ subroutine biozone()
323319

324320
!! print out time seriese results. header is in "readfile.f"
325321
if(curyr>nyskip) then
326-
n1=nh3_init
327322
n2=nh3_begin
328323
n3=nh3_end
329-
n4=no3_init
330324
n5=no3_begin
331325
n6=no3_end !*bza/hvol*1000
332326
n7=rnit
333327
n8=rdenit
334-
p1=solp_init
335328
p2=solp_begin
336329
p3=solp_end
337330
p4 = solpconc
338331

339-
write(173,1000) ihru,iyr,iida,precipday,qout,sol_ul(bz_lyr,j),
340-
& sol_st(bz_lyr,j),sol_fc(bz_lyr,j),n1,n2,n3,n4,n5,n6,
341-
& n7,n8,p1,p2,p3,p4
332+
write(173,1000) ihru,iyr,iida,precipday,bz_perc(j),sol_ul(bz_lyr,j),
333+
& sol_st(bz_lyr,j),sol_fc(bz_lyr,j),n2,n3,n5,n6,
334+
& n7,n8,p2,p3,p4
342335
endif
343336

344337
!! output.std variables added 03/01/2011 jga

src/bmp_ri_pond.f

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ subroutine ri_pond(kk,riflw,rised)
4040
real :: qin,qout,qpnd,sweir,hpnd,qet
4141
real :: qweir, qseep,qpipe,qpndi,decayexp,splw,qpump
4242
real :: sedconc,sedpndi, sedpnde,ksed,td,sedpump
43-
real, dimension(3,0:nstep), intent(in out) :: riflw,rised
43+
real, dimension(4,0:nstep), intent(in out) :: riflw,rised
4444
real, dimension(0:nstep) :: inflw,insed,outflw,outsed
4545

4646
sb = inum1
@@ -122,6 +122,7 @@ subroutine ri_pond(kk,riflw,rised)
122122
riflw(1,ii) = qin / (sub_ha *10000. - tsa) * 1000. !mm
123123
riflw(2,ii) = outflw(ii) / (sub_ha *10000. - tsa) * 1000.
124124
riflw(3,ii) = qpump / (sub_ha *10000. - tsa) * 1000.
125+
riflw(4,ii) = qseep / (sub_ha *10000. - tsa) * 1000.
125126
rised(3,:) = sedpump
126127
rised(2,:) = outsed(:)
127128
End do

src/bmp_sand_filter.f

Lines changed: 9 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -38,16 +38,16 @@ subroutine sand_filter(kk,flw,sed)
3838
& wetfsh,whd,sub_ha,dt,qcms,effct,effl,effg,effbr,vpipe,phead,hpnd,
3939
& tmpw,qloss,fsat,qpipe,mu,pipeflow,splw,hweir,tst,kb,qintns,qq,
4040
& qfiltr,sloss,spndconc,sedpnd,qpndi,qpnde,sedrmeff,sed_removed,
41-
& sedconc,qevap,hrd
41+
& sedconc,qevap,hrd,qrchg
4242
real*8, dimension(:) :: qpnd(0:nstep),qsw(0:nstep),qin(0:nstep),
4343
& qout(0:nstep),fc(0:nstep),f(0:nstep)
44-
real, dimension(3,0:nstep), intent(inout) :: flw, sed
44+
real, dimension(4,0:nstep), intent(inout) :: flw, sed
4545

4646
sb = inum1
4747
sub_ha = da_ha * sub_fr(sb)
4848
dt = real(idt) / 60. !time interval in hours
4949
qin = 0.; qout = 0.;qevap=0
50-
flw(2,:) = 0.; sed(2,:) = 0.;f=0
50+
flw(2,:) = 0.; sed(2,:) = 0.;f=0; qrchg = 0
5151
qpnd = 0.; qsw = 0.; qpndi = 0.; qpnde = 0.; fc = 0.;qfiltr = 0.
5252
kb = 1.38e-16 !Boltzmann constant, g-cm^2/s^2-K
5353

@@ -85,6 +85,10 @@ subroutine sand_filter(kk,flw,sed)
8585
qin(ii) = flw(1,ii) * 10. * (sub_ha - tsa / 10000.) +
8686
& precipdt(ii) * tsa / 1000. !m^3
8787
qout(ii) = qout(ii-1)
88+
if(qin(ii)>0.5) then
89+
qin(ii)=qin(ii)
90+
endif
91+
8892

8993
If (qin(ii)<0.001.and.qpnd(ii-1)<0.001)then
9094

@@ -246,13 +250,15 @@ subroutine sand_filter(kk,flw,sed)
246250
if (sf_ptp(sb,kk)==0) then
247251
bmp_recharge(sb) = bmp_recharge(sb)
248252
& + qout(ii) / (sub_ha*10000.- tsa) *1000.
253+
qrchg = qout(ii)
249254
qout(ii) = 0. !effluent from the filter unit (through-flow+overflow), normalized to subbasin area
250255
end if
251256

252257
! store the flow output
253258
flw(1,ii) = qin(ii) / (sub_ha *10000. - tsa) * 1000. !mm
254259
flw(2,ii) = qout(ii) / (sub_ha*10000.- tsa) *1000. !mm
255260
flw(3,ii) = qloss / (sub_ha *10000. - tsa) * 1000. !mm
261+
flw(4,ii) = qrchg / (sub_ha *10000. - tsa) * 1000. !mm
256262

257263
! write(*,'(2i3,20f7.3)') iida, ii, qin(ii),qout(ii),qpnd(ii),
258264
! & qsw(ii),qloss

0 commit comments

Comments
 (0)