Skip to content

Commit

Permalink
set cascade_flag, cascadegw_flag, and subbasin_flag defaults back to 1
Browse files Browse the repository at this point in the history
fixed a couple mixed precision calculatations and made gwflow_inactive_cell.f90 more like gwflow.f90
  • Loading branch information
rsregan committed Jul 1, 2024
1 parent b5bdbd9 commit 9617ec3
Show file tree
Hide file tree
Showing 8 changed files with 74 additions and 66 deletions.
2 changes: 1 addition & 1 deletion GSFLOW/src/gsflow/gsflow_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ MODULE PRMS_MODULE
character(len=*), parameter :: GSFLOW_versn = '2.4.0 06/01/2024'
character(len=*), parameter :: PRMS_versn = '2024-06-01'
character(len=*), parameter :: PRMS_VERSION = 'Version 6.0.0 06/01/2024'
character(len=*), parameter :: githash = 'Github Commit Hash 87261a7bfb1fe745bfa4ec46d6c333cb9a40a4c8 [87261a7] master branch'
character(len=*), parameter :: githash = 'Github Commit Hash b5bdbd9 master branch'
character(len=*), parameter :: Version_read_control_file = '2024-03-01'
character(len=*), parameter :: Version_read_parameter_file = '2024-06-21'
character(len=*), parameter :: Version_read_data_file = '2023-06-02'
Expand Down
4 changes: 2 additions & 2 deletions GSFLOW/src/gsflow/gsflow_prms.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1119,7 +1119,7 @@ SUBROUTINE setdims(AFR, Diversions, Idivert, EXCHANGE, DELTAVOL, LAKEVOL, Nsegsh

! cascade
! if cascade_flag = 2 (CASCADE_HRU_SEGMENT), use hru_segment parameter for cascades, ncascade=ncascdgw=nhru (typical polygon HRUs)
IF ( control_integer(Cascade_flag, 'cascade_flag')/=0 ) Cascade_flag = OFF
IF ( control_integer(Cascade_flag, 'cascade_flag')/=0 ) Cascade_flag = ACTIVE
! if cascadegw_flag = 2 (CASCADEGW_SAME), use same cascades as HRUs
IF ( control_integer(Cascadegw_flag, 'cascadegw_flag')/=0 ) Cascadegw_flag = OFF

Expand Down Expand Up @@ -1223,7 +1223,7 @@ INTEGER FUNCTION check_dims(Nsegshold, Nlakeshold)
Cascadegw_flag = CASCADEGW_OFF
Cascade_flag = CASCADE_OFF
ENDIF
IF ( Cascade_flag>CASCADE_OFF .OR. Cascadegw_flag>CASCADEGW_OFF .AND. Model/=CONVERT ) THEN
IF ( (Cascade_flag>CASCADE_OFF .OR. Cascadegw_flag>CASCADEGW_OFF) .AND. Model/=CONVERT ) THEN
Call_cascade = ACTIVE
ELSE
Call_cascade = OFF
Expand Down
85 changes: 47 additions & 38 deletions GSFLOW/src/gsflow/gwflow_inactive_cell.f90
Original file line number Diff line number Diff line change
@@ -1,29 +1,37 @@
!***********************************************************************
! Sums inflow to and outflow from PRMS ground-water reservoirs for inactive MF cells
! outflow can be routed to downslope ground-water reservoirs and stream
! segments. No PRMS water use or lakes or minimum area or sink or swales
! Sums inflow to and outflow from PRMS ground-water reservoirs for inactive MF cells; outflow
! can be routed to downslope ground-water reservoirs and stream
! segments. Lakes are not allowed.
!
! Can be used for depression storage
!***********************************************************************
! Modified 7/1997 J. Vaccaro to set a minimum value for groundwater flow
! by reading in a minimum ground-water storage value for each groundwater
! reservoir, if this value is set=0, then standard PRMS routine module.
! A minimum may represent an injection well, intrabasin transfer,
! contribution from larger regional gw system, or past residual storage
! modified 10/1/2008 rsregan to include Vaccaro code
!***********************************************************************
MODULE PRMS_GWFLOW_INACTIVE_CELL
IMPLICIT NONE
! Local Variables
! Local Variables
character(len=*), parameter :: MODDESC = 'Groundwater'
character(len=*), parameter :: MODNAME = 'gwflow_inactive_cell'
character(len=*), parameter :: Version_gwflow = '2024-05-30'
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Gwstor_minarea(:), Gwin_dprst(:)
DOUBLE PRECISION, SAVE :: Basin_gw_upslope
INTEGER, SAVE :: Gwminarea_flag
DOUBLE PRECISION, SAVE :: Basin_dnflow
! Declared Variables
! Declared Variables
DOUBLE PRECISION, SAVE :: Basin_gwstor, Basin_gwflow, Basin_gwsink
DOUBLE PRECISION, SAVE :: Basin_gwin
DOUBLE PRECISION, SAVE :: Basin_gwstor_minarea_wb
REAL, SAVE, ALLOCATABLE :: Gwres_flow(:), Gwres_sink(:)
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Gwres_in(:)
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Hru_gw_cascadeflow(:)
REAL, SAVE, ALLOCATABLE :: Hru_gw_cascadeflow(:)
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Gw_in_soil(:), Gw_in_ssr(:), Hru_lateral_flow(:)
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Gwstor_minarea_wb(:), Hru_streamflow_out(:)
! Declared Parameters
! Declared Parameters
REAL, SAVE, ALLOCATABLE :: Gwflow_coef(:), Gwsink_coef(:)
REAL, SAVE, ALLOCATABLE :: Gwstor_init(:), Gwstor_min(:)
END MODULE PRMS_GWFLOW_INACTIVE_CELL
Expand All @@ -35,9 +43,9 @@ SUBROUTINE gwflow_inactive_cell ()
USE PRMS_CONSTANTS, ONLY: RUN, DECL, INIT
USE PRMS_MODULE, ONLY: Process_flag
IMPLICIT NONE
! Functions
! Functions
EXTERNAL :: gwflow_inactivecell_run, gwflow_inactivecell_decl, gwflow_inactivecell_init
!***********************************************************************
!***********************************************************************
IF ( Process_flag==RUN ) THEN
CALL gwflow_inactivecell_run()
ELSEIF ( Process_flag==DECL ) THEN
Expand All @@ -61,13 +69,13 @@ SUBROUTINE gwflow_inactivecell_decl()
USE PRMS_GWFLOW_INACTIVE_CELL
use prms_utils, only: print_module, read_error
IMPLICIT NONE
!***********************************************************************
!***********************************************************************
CALL print_module(MODDESC, MODNAME, Version_gwflow)

! cascading variables and parameters
! cascading variables and parameters
IF ( Cascadegw_flag>CASCADEGW_OFF ) THEN
ALLOCATE ( Hru_gw_cascadeflow(Ngw) )
CALL declvar_dble(MODNAME, 'hru_gw_cascadeflow', 'ngw', Ngw, &
CALL declvar_real(MODNAME, 'hru_gw_cascadeflow', 'ngw', Ngw, &
& 'Cascading groundwater flow from each GWR', &
& 'inches', Hru_gw_cascadeflow)
ENDIF
Expand Down Expand Up @@ -187,9 +195,9 @@ SUBROUTINE gwflow_inactivecell_init()
use prms_utils, only: read_error
IMPLICIT NONE
INTRINSIC :: DBLE
! Local Variables
! Local Variables
INTEGER :: i, j
!***********************************************************************
!***********************************************************************
IF ( getparam_real(MODNAME, 'gwflow_coef', Ngw, Gwflow_coef)/=0 ) CALL read_error(2, 'gwflow_coef')
IF ( getparam_real(MODNAME, 'gwsink_coef', Ngw, Gwsink_coef)/=0 ) CALL read_error(2, 'gwsink_coef')
IF ( getparam_real(MODNAME, 'gwstor_min', Ngw, Gwstor_min)/=0 ) CALL read_error(2, 'gwstor_min')
Expand Down Expand Up @@ -225,7 +233,7 @@ SUBROUTINE gwflow_inactivecell_init()
IF ( Print_debug>DEBUG_less ) PRINT *, 'WARNING, GWR:', i, &
& ' is treated as a swale, flow sent to basin_cfs and hru_segment if > 0'
ELSE
! maybe gwr_swale_flag = 3 abs(hru_segment) so hru_segment could be changed from 0 to allow HRU swales
! maybe gwr_swale_flag = 3 abs(hru_segment) so hru_segment could be changed from 0 to allow HRU swales
PRINT *, 'ERROR, invalid gwr_swale_flag value, specified as:', gwr_swale_flag
Inputerror_flag = 1
ENDIF
Expand All @@ -251,7 +259,8 @@ SUBROUTINE gwflow_inactivecell_init()
END SUBROUTINE gwflow_inactivecell_init

!***********************************************************************
! gwflow_inactivecell_run - Computes groundwater flow to streamflow
! gwflow_inactivecell_run - Computes groundwater flow to streamflow and to
! groundwater sink
!***********************************************************************
SUBROUTINE gwflow_inactivecell_run()
USE PRMS_CONSTANTS, ONLY: ACTIVE, SWALE, DEBUG_less, CASCADEGW_OFF, ERROR_water_use
Expand All @@ -260,7 +269,7 @@ SUBROUTINE gwflow_inactivecell_run()
USE PRMS_GWFLOW_INACTIVE_CELL
USE PRMS_BASIN, ONLY: Active_gwrs, Gwr_route_order, &
& Basin_area_inv, Hru_area, Gwr_type, Hru_area_dble, Hru_storage
USE PRMS_FLOWVARS, ONLY: Ssr_to_gw, Sroff, Ssres_flow, Gwres_stor, Gw_upslope !, Soil_to_gw
USE PRMS_FLOWVARS, ONLY: Soil_to_gw, Ssr_to_gw, Sroff, Ssres_flow, Gwres_stor, Gw_upslope
USE PRMS_CASCADE, ONLY: Ncascade_gwr
USE PRMS_SET_TIME, ONLY: Cfs_conv
USE PRMS_SRUNOFF, ONLY: Dprst_seep_hru
Expand All @@ -269,17 +278,17 @@ SUBROUTINE gwflow_inactivecell_run()
USE GSFPRMS2MF, ONLY: activeHru_inactiveCell
use prms_utils, only: print_date
IMPLICIT NONE
! Functions
! Functions
EXTERNAL :: rungw_inactive_cell_cascade
INTRINSIC :: DBLE, DABS, SNGL, MIN
! Local Variables
! Local Variables
INTEGER :: i, j
DOUBLE PRECISION :: dnflow
REAL :: dnflow
DOUBLE PRECISION :: gwin, gwstor, gwsink, gwflow, gwstor_last, gwarea
!***********************************************************************
!***********************************************************************
IF ( Cascadegw_flag>CASCADEGW_OFF ) THEN
Gw_upslope = 0.0D0
Hru_gw_cascadeflow = 0.0D0
Hru_gw_cascadeflow = 0.0
Basin_dnflow = 0.0D0
Basin_gw_upslope = 0.0D0
ENDIF
Expand All @@ -295,7 +304,7 @@ SUBROUTINE gwflow_inactivecell_run()
gwarea = Hru_area_dble(i)
gwstor = Gwres_stor(i)*gwarea ! acre-inches
! soil_to_gw is for whole HRU, not just perv
! Gw_in_soil(i) = DBLE( Soil_to_gw(i)*Hru_area(i) ) ! soil_to_gw added to sm2gw_grav
Gw_in_soil(i) = DBLE( Soil_to_gw(i)*Hru_area(i) )
Gw_in_ssr(i) = DBLE( Ssr_to_gw(i)*Hru_area(i) )
gwin = Gw_in_soil(i) + Gw_in_ssr(i)
IF ( Cascadegw_flag>CASCADEGW_OFF ) THEN
Expand All @@ -318,7 +327,7 @@ SUBROUTINE gwflow_inactivecell_run()
IF ( gwstor<0.0D0 ) THEN
IF ( Print_debug>DEBUG_less ) PRINT *, 'Warning, groundwater reservoir for HRU:', i, &
& ' is < 0.0 with gwstor_min active', gwstor
!ERROR STOP ERROR_var
! ERROR STOP ERROR_var
ENDIF
gwstor_last = gwstor
gwstor = Gwstor_minarea(i)
Expand Down Expand Up @@ -353,18 +362,18 @@ SUBROUTINE gwflow_inactivecell_run()
gwstor = 0.0D0
ELSE

! Compute groundwater discharge
! Compute groundwater discharge
gwflow = gwstor*DBLE( Gwflow_coef(i) )

! Reduce storage by outflow
! Reduce storage by outflow
gwstor = gwstor - gwflow

IF ( Gwsink_coef(i)>0.0 ) THEN
gwsink = MIN( gwstor*DBLE( Gwsink_coef(i) ), gwstor ) ! if gwsink_coef > 1, could have had negative gwstor
gwstor = gwstor - gwsink
ENDIF
! if gwr_swale_flag = 1 swale GWR flow goes to sink, 2 included in stream network and cascades
! maybe gwr_swale_flag = 3 abs(hru_segment) so hru_segment could be changed from 0 to allow HRU swales
! if gwr_swale_flag = 1 swale GWR flow goes to sink, 2 included in stream network and cascades
! maybe gwr_swale_flag = 3 abs(hru_segment) so hru_segment could be changed from 0 to allow HRU swales
IF ( Gwr_swale_flag==ACTIVE ) THEN
IF ( Gwr_type(i)==SWALE ) THEN
gwsink = gwsink + gwflow
Expand Down Expand Up @@ -396,7 +405,7 @@ SUBROUTINE gwflow_inactivecell_run()
ELSE
! a gw cascade could go to active HRU/cell, so add to potential draing to MODFLOW
! gw cascades to segments are already accounted for
IF ( Gw_upslope(i) > 0.0 ) Sm2gw_grav(i) = Sm2gw_grav(i) + Gw_upslope(i)
IF ( Gw_upslope(i) > 0.0D0 ) Sm2gw_grav(i) = Sm2gw_grav(i) + SNGL( Gw_upslope(i) )
ENDIF
ENDDO

Expand All @@ -419,32 +428,32 @@ SUBROUTINE rungw_inactive_cell_cascade(Igwr, Ncascade_gwr, Gwres_flow, Dnflow)
! Cfs_conv converts acre-inches per timestep to cfs
USE PRMS_SET_TIME, ONLY: Cfs_conv
IMPLICIT NONE
! Functions
! Functions
INTRINSIC :: IABS, DBLE
! Arguments
! Arguments
INTEGER, INTENT(IN) :: Igwr, Ncascade_gwr
REAL, INTENT(INOUT) :: Gwres_flow
DOUBLE PRECISION, INTENT(OUT) :: Dnflow
! Local variables
REAL, INTENT(OUT) :: Dnflow
! Local variables
INTEGER :: j, k
!***********************************************************************
Dnflow = 0.0D0
Dnflow = 0.0
DO k = 1, Ncascade_gwr
j = Gwr_down(k, Igwr)
! Gwres_flow is in inches
! if gwr_down(k, Igwr) > 0, cascade contributes to a downslope GWR
! if gwr_down(k, Igwr) > 0, cascade contributes to a downslope GWR
IF ( j>0 ) THEN
Gw_upslope(j) = Gw_upslope(j) + DBLE( Gwres_flow*Cascade_gwr_area(k, Igwr) )
Dnflow = Dnflow + DBLE( Gwres_flow*Gwr_down_frac(k, Igwr) )
! if gwr_down(k, Igwr) < 0, cascade contributes to a stream
Dnflow = Dnflow + Gwres_flow*Gwr_down_frac(k, Igwr)
! if gwr_down(k, Igwr) < 0, cascade contributes to a stream
ELSEIF ( j<0 ) THEN
j = IABS( j )
Strm_seg_in(j) = Strm_seg_in(j) + DBLE( Gwres_flow*Cascade_gwr_area(k, Igwr) )*Cfs_conv
ENDIF
ENDDO

! gwres_flow reduced by cascading flow to HRUs
Gwres_flow = Gwres_flow - SNGL( Dnflow )
Gwres_flow = Gwres_flow - Dnflow
IF ( Gwres_flow<0.0 ) Gwres_flow = 0.0

END SUBROUTINE rungw_inactive_cell_cascade
1 change: 0 additions & 1 deletion GSFLOW/src/prms/cascade.f90
Original file line number Diff line number Diff line change
Expand Up @@ -220,7 +220,6 @@ INTEGER FUNCTION cascinit()

IF ( Cascade_flag>CASCADE_OFF ) CALL init_cascade(cascinit)

iret = 0
IF ( Cascadegw_flag>CASCADEGW_OFF ) THEN
ALLOCATE ( Gwr_down(Ndown,Ngw), Gwr_down_frac(Ndown,Ngw), Cascade_gwr_area(Ndown,Ngw) )
! ALLOCATE ( Gwr_down_fracwt(Ndown,Ngw) )
Expand Down
14 changes: 7 additions & 7 deletions GSFLOW/src/prms/climateflow.f90
Original file line number Diff line number Diff line change
Expand Up @@ -1370,17 +1370,17 @@ INTEGER FUNCTION climateflow_init()
PRINT 9006, i, Soil_moist_max(i)
Inputerror_flag = 1
ELSE
Soil_moist_max(i) = 0.0001
Soil_moist_max(i) = 0.00001
IF ( Print_debug>DEBUG_less ) PRINT 9008, i
bad_soil_moist_max = bad_soil_moist_max + 1
ENDIF
ENDIF
IF ( Soil_rechr_max(i)<0.0001 ) THEN
IF ( Soil_rechr_max(i)<0.00001 ) THEN
IF ( Parameter_check_flag>0 ) THEN
PRINT 9007, i, Soil_rechr_max(i)
Inputerror_flag = 1
ELSE
Soil_rechr_max(i) = 0.0001
Soil_rechr_max(i) = 0.00001
IF ( Print_debug>DEBUG_less ) PRINT 9009, i
ENDIF
ENDIF
Expand Down Expand Up @@ -1527,10 +1527,10 @@ INTEGER FUNCTION climateflow_init()
9023 FORMAT (/, 'ERROR, HRU: ', I0, ' ag_soil_rechr_init > ag_soil_rechr_max', 2F15.9)
9024 FORMAT (/, 'ERROR, HRU: ', I0, ' ag_soil_moist_init > ag_soil_moist_max', 2F15.9)
9025 FORMAT (/, 'ERROR, HRU: ', I0, ' ag_soil_rechr > ag_soil_moist based on init and max values', 2F15.9)
9006 FORMAT (/, 'ERROR, HRU: ', I0, ' soil_moist_max < 0.0001', F15.9)
9007 FORMAT (/, 'ERROR, HRU: ', I0, ' soil_rechr_max < 0.0001', F15.9)
9008 FORMAT (/, 'WARNING, HRU: ', I0, ' soil_moist_max < 0.0001, set to 0.0001')
9009 FORMAT (/, 'WARNING, HRU: ', I0, ' soil_rechr_max < 0.0001, set to 0.0001')
9006 FORMAT (/, 'ERROR, HRU: ', I0, ' soil_moist_max < 0.00001', F15.9)
9007 FORMAT (/, 'ERROR, HRU: ', I0, ' soil_rechr_max < 0.00001', F15.9)
9008 FORMAT (/, 'WARNING, HRU: ', I0, ' soil_moist_max < 0.00001, set to 0.00001')
9009 FORMAT (/, 'WARNING, HRU: ', I0, ' soil_rechr_max < 0.00001, set to 0.00001')
9012 FORMAT (/, 'WARNING, HRU: ', I0, ' soil_rechr_max > soil_moist_max,', 2F15.9, /, 9X, &
& 'soil_rechr_max set to soil_moist_max')
9013 FORMAT (/, 'WARNING, HRU: ', I0, ' soil_rechr_init > soil_rechr_max,', 2F15.9, /, 9X, &
Expand Down
22 changes: 11 additions & 11 deletions GSFLOW/src/prms/gwflow.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,8 +16,8 @@ MODULE PRMS_GWFLOW
IMPLICIT NONE
! Local Variables
character(len=*), parameter :: MODDESC = 'Groundwater'
character(len=6), parameter :: MODNAME = 'gwflow'
character(len=*), parameter :: Version_gwflow = '2024-01-22'
character(len=*), parameter :: MODNAME = 'gwflow'
character(len=*), parameter :: Version_gwflow = '2024-05-30'
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Gwstor_minarea(:), Gwin_dprst(:)
DOUBLE PRECISION, SAVE :: Basin_gw_upslope
INTEGER, SAVE :: Gwminarea_flag
Expand All @@ -29,7 +29,7 @@ MODULE PRMS_GWFLOW
DOUBLE PRECISION, SAVE :: Basin_gwstor_minarea_wb
REAL, SAVE, ALLOCATABLE :: Gwres_flow(:), Gwres_sink(:)
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Gwres_in(:)
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Hru_gw_cascadeflow(:)
REAL, SAVE, ALLOCATABLE :: Hru_gw_cascadeflow(:)
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Gw_in_soil(:), Gw_in_ssr(:), Hru_lateral_flow(:)
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Gwstor_minarea_wb(:), Hru_streamflow_out(:), Lakein_gwflow(:)
DOUBLE PRECISION, SAVE, ALLOCATABLE :: Lake_seepage(:), Gw_seep_lakein(:), Lake_seepage_gwr(:)
Expand Down Expand Up @@ -88,7 +88,7 @@ INTEGER FUNCTION gwflowdecl()
! cascading variables and parameters
IF ( Cascadegw_flag>CASCADEGW_OFF ) THEN
ALLOCATE ( Hru_gw_cascadeflow(Ngw) )
CALL declvar_dble(MODNAME, 'hru_gw_cascadeflow', 'ngw', Ngw, &
CALL declvar_real(MODNAME, 'hru_gw_cascadeflow', 'ngw', Ngw, &
& 'Cascading groundwater flow from each GWR', &
& 'inches', Hru_gw_cascadeflow)

Expand Down Expand Up @@ -384,14 +384,14 @@ INTEGER FUNCTION gwflowrun()
INTRINSIC :: DBLE, DABS, SNGL, MIN
! Local Variables
INTEGER :: i, j, jj, jjj
DOUBLE PRECISION :: dnflow
REAL :: dnflow
DOUBLE PRECISION :: gwin, gwstor, gwsink, gwflow, gwstor_last, seepage, gwarea, inch2acre_feet
!***********************************************************************
gwflowrun = 0

IF ( Cascadegw_flag>CASCADEGW_OFF ) THEN
Gw_upslope = 0.0D0
Hru_gw_cascadeflow = 0.0D0
Hru_gw_cascadeflow = 0.0
Basin_dnflow = 0.0D0
Basin_gw_upslope = 0.0D0
IF ( Nlake>0 ) Lakein_gwflow = 0.0D0
Expand Down Expand Up @@ -546,7 +546,7 @@ INTEGER FUNCTION gwflowrun()
IF ( Ncascade_gwr(i)>0 ) THEN
CALL rungw_cascade(i, Ncascade_gwr(i), Gwres_flow(i), dnflow)
Hru_gw_cascadeflow(i) = dnflow
Basin_dnflow = Basin_dnflow + dnflow*gwarea
Basin_dnflow = Basin_dnflow + DBLE( dnflow*Hru_area(i) )
ELSEIF ( Gwr_type(i)==LAKE ) THEN
Lakein_gwflow(Lake_hru_id(i)) = Lakein_gwflow(Lake_hru_id(i)) + Gwres_flow(i)
ENDIF
Expand Down Expand Up @@ -586,18 +586,18 @@ SUBROUTINE rungw_cascade(Igwr, Ncascade_gwr, Gwres_flow, Dnflow)
! Arguments
INTEGER, INTENT(IN) :: Igwr, Ncascade_gwr
REAL, INTENT(INOUT) :: Gwres_flow
DOUBLE PRECISION, INTENT(OUT) :: Dnflow
REAL, INTENT(OUT) :: Dnflow
! Local variables
INTEGER :: j, k
!***********************************************************************
Dnflow = 0.0D0
Dnflow = 0.0
DO k = 1, Ncascade_gwr
j = Gwr_down(k, Igwr)
! Gwres_flow is in inches
! if gwr_down(k, Igwr) > 0, cascade contributes to a downslope GWR
IF ( j>0 ) THEN
Gw_upslope(j) = Gw_upslope(j) + DBLE( Gwres_flow*Cascade_gwr_area(k, Igwr) )
Dnflow = Dnflow + DBLE( Gwres_flow*Gwr_down_frac(k, Igwr) )
Dnflow = Dnflow + Gwres_flow*Gwr_down_frac(k, Igwr)
! if gwr_down(k, Igwr) < 0, cascade contributes to a stream
ELSEIF ( j<0 ) THEN
j = IABS( j )
Expand All @@ -606,7 +606,7 @@ SUBROUTINE rungw_cascade(Igwr, Ncascade_gwr, Gwres_flow, Dnflow)
ENDDO

! gwres_flow reduced by cascading flow to HRUs
Gwres_flow = Gwres_flow - SNGL( Dnflow )
Gwres_flow = Gwres_flow - Dnflow
IF ( Gwres_flow<0.0 ) Gwres_flow = 0.0

END SUBROUTINE rungw_cascade
Expand Down
Loading

0 comments on commit 9617ec3

Please sign in to comment.