Skip to content

Commit

Permalink
merge with PRMS 6.0.0, some modules have restored code to more closel…
Browse files Browse the repository at this point in the history
…y match 5.2.1.1
  • Loading branch information
rsregan committed Jun 11, 2024
1 parent 50100fb commit 87261a7
Show file tree
Hide file tree
Showing 24 changed files with 617 additions and 472 deletions.
30 changes: 7 additions & 23 deletions GSFLOW/src/gsflow/gsflow_modflow.f
Original file line number Diff line number Diff line change
Expand Up @@ -444,7 +444,7 @@ SUBROUTINE MFNWT_RUN(AFR, Diversions, Idivert, EXCHANGE,
& MODSIM_MODFLOW
USE PRMS_MODULE, ONLY: Kper_mfo, Kkiter, Timestep, no_snow_flag,
& Init_vars_from_file, Mxsziter, Glacier_flag, AG_flag,
& PRMS_land_iteration_flag,
& PRMS_land_iteration_flag, activeHRU_inactiveCELL_flag,
& Model, GSFLOW_flag, Print_debug, Soilzone_module
use prms_utils, only: error_stop
C1------USE package modules.
Expand Down Expand Up @@ -476,6 +476,7 @@ SUBROUTINE MFNWT_RUN(AFR, Diversions, Idivert, EXCHANGE,
INTEGER, EXTERNAL :: srunoff, intcp, snowcomp, glacr
INTEGER, EXTERNAL :: gsflow_prms2mf, gsflow_mf2prms
EXTERNAL :: MODSIM2SFR, SFR2MODSIM, LAK2MODSIM
EXTERNAL :: gwflow_inactive_cell
INTRINSIC :: MIN
! Local Variables
INTEGER :: retval, KITER, iss, iprt, I !, II, IBDRET
Expand Down Expand Up @@ -672,22 +673,14 @@ SUBROUTINE MFNWT_RUN(AFR, Diversions, Idivert, EXCHANGE,
ENDIF
ENDIF
ENDIF
IF ( PRMS_land_iteration_flag>0 ) THEN
retval = srunoff()
IF ( retval/=0 ) THEN
PRINT 9001, 'srunoff', retval
RETURN
ENDIF
ENDIF
IF ( PRMS_land_iteration_flag>0 ) retval = srunoff()
IF ( AG_flag==ACTIVE ) THEN
retval = soilzone_ag()
ELSE
retval = soilzone()
ENDIF
IF ( retval/=0 ) THEN
PRINT 9001, Soilzone_module, retval
RETURN
ENDIF
IF ( activeHRU_inactiveCELL_flag == ACTIVE )
& CALL gwflow_inactive_cell()
retval = gsflow_prms2mf()
Sziters = Sziters + 1
Maxgziter = KKITER
Expand Down Expand Up @@ -809,21 +802,15 @@ SUBROUTINE MFNWT_RUN(AFR, Diversions, Idivert, EXCHANGE,
ENDIF
IF ( PRMS_land_iteration_flag>0 ) THEN
retval = srunoff()
IF ( retval/=0 ) THEN
PRINT 9001, 'srunoff', retval
RETURN
ENDIF
ENDIF
!IF ( Szcheck==ACTIVE ) retval = gsflow_mf2prms() RGN+RSR 12/14/2022
IF ( AG_flag==ACTIVE ) THEN
retval = soilzone_ag()
ELSE
retval = soilzone()
ENDIF
IF ( retval/=0 ) THEN
PRINT 9001, Soilzone_module, retval
RETURN
ENDIF
IF ( activeHRU_inactiveCELL_flag == ACTIVE )
& CALL gwflow_inactive_cell()
retval = gsflow_prms2mf()
END IF
C
Expand All @@ -840,9 +827,6 @@ SUBROUTINE MFNWT_RUN(AFR, Diversions, Idivert, EXCHANGE,
! kkiter = itreal
!move above and executed when AFR = TRUE
IF(IUNIT(62).GT.0 ) CALL GWF2UPWUPDATE(2,Igrid)
C
9001 FORMAT ('ERROR in ', A, ' module, arg = run.',
& ' Called from MFNWT_RUN.', /, 'Return val =', I2)
C
IF (Model>=10 .AND. iss==0) THEN
IF(IUNIT(44).GT.0) CALL SFR2MODSIM(EXCHANGE, Diversions,
Expand Down
10 changes: 5 additions & 5 deletions GSFLOW/src/gsflow/gsflow_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,10 +8,10 @@ MODULE PRMS_MODULE
& EQULS = '=========================================================================='
character(len=*), parameter :: MODDESC = 'PRMS Computation Order'
character(len=11), parameter :: MODNAME = 'gsflow_prms'
character(len=*), parameter :: GSFLOW_versn = '2.4.0 05/01/2024'
character(len=*), parameter :: PRMS_versn = '2024-05-01'
character(len=*), parameter :: PRMS_VERSION = 'Version 6.0.0 05/01/2024'
character(len=*), parameter :: githash = 'Github Commit Hash 62761520d4284c8e7d0114d7d16c69c508494832 [6276152] branch 5.2.2.2'
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 62761520d4284c8e7d0114d7d16c69c508494832 [6276152] branch master'
character(len=*), parameter :: Version_read_control_file = '2024-03-01'
character(len=*), parameter :: Version_read_parameter_file = '2024-03-01'
character(len=*), parameter :: Version_read_data_file = '2023-06-02'
Expand Down Expand Up @@ -93,7 +93,7 @@ MODULE GSFMODFLOW
! Local Variables
character(len=*), parameter :: MODDESC = 'GSFLOW MODFLOW main'
character(len=14), parameter :: MODNAME = 'gsflow_modflow'
character(len=*), parameter :: Version_gsflow_modflow='2022-10-20'
character(len=*), parameter :: Version_gsflow_modflow='2024-06-01'
character(len=*), parameter :: MODDESC_UZF = 'UZF-NWT Package'
character(len=*), parameter :: MODDESC_SFR = 'SFR-NWT Package'
character(len=*), parameter :: MODDESC_LAK = 'LAK-NWT Package'
Expand Down
21 changes: 10 additions & 11 deletions GSFLOW/src/gsflow/gsflow_prms.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ SUBROUTINE gsflow_prms(Process_mode, AFR, MS_GSF_converge, Nsegshold, Nlakeshold
use PRMS_READ_PARAM_FILE, only: declparam, check_parameters, getparam_int, getparam_real, &
read_parameter_file_dimens, read_parameter_file_params, setup_params
use PRMS_SET_TIME, only: prms_time
use prms_utils, only: error_stop, numchars, print_module, PRMS_open_output_file, read_error, module_error
use prms_utils, only: error_stop, numchars, print_module, PRMS_open_output_file, read_error
USE MF_DLL, ONLY: gsfdecl, MFNWT_RUN, MFNWT_CLEAN, MFNWT_OCBUDGET, MFNWT_INIT
USE GWFSFRMODULE, ONLY: NSS
IMPLICIT NONE
Expand Down Expand Up @@ -334,7 +334,6 @@ SUBROUTINE gsflow_prms(Process_mode, AFR, MS_GSF_converge, Nsegshold, Nlakeshold
ENDIF
IF ( Process_flag/=RUN .AND. PRMS_flag==ACTIVE ) THEN
ierr = basin()
IF ( ierr/=0 ) CALL module_error('basin', Arg, ierr)

IF ( Call_cascade==ACTIVE ) ierr = cascade()

Expand Down Expand Up @@ -474,6 +473,8 @@ SUBROUTINE gsflow_prms(Process_mode, AFR, MS_GSF_converge, Nsegshold, Nlakeshold
ierr = soilzone_ag()
ENDIF

IF ( activeHRU_inactiveCELL_flag == ACTIVE ) CALL gwflow_inactive_cell()

IF ( gwflow_flag == ACTIVE ) THEN
IF ( Model==PRMS ) THEN
ierr = gwflow()
Expand All @@ -500,8 +501,6 @@ SUBROUTINE gsflow_prms(Process_mode, AFR, MS_GSF_converge, Nsegshold, Nlakeshold
IF ( Print_debug>DEBUG_minimum ) ierr = basin_sum()

IF ( Print_debug==DEBUG_WB ) CALL water_balance()
ELSEIF ( activeHRU_inactiveCELL_flag == ACTIVE ) THEN
CALL gwflow_inactive_cell()
ENDIF
ENDIF
ENDIF
Expand Down Expand Up @@ -680,9 +679,9 @@ SUBROUTINE setdims(AFR, Diversions, Idivert, EXCHANGE, DELTAVOL, LAKEVOL, Nsegsh
PRMS4_flag = ACTIVE
IF ( Model_mode(:5)=='PRMS5' .OR. Model_mode(:5)=='prms5' ) PRMS4_flag = OFF
IF ( Model_mode(:5)=='PRMS6' .OR. Model_mode(:5)=='prms6' ) THEN
Model = PRMS6
PRMS4_flag = OFF
PRMS6_flag = OFF
Model = PRMS6
PRMS6_flag = ACTIVE
ENDIF
PRMS_only = ACTIVE
ELSEIF ( Model_mode(:6)=='GSFLOW' .OR. Model_mode(:6)=='gsflow' ) THEN
Expand Down Expand Up @@ -1076,10 +1075,10 @@ SUBROUTINE setdims(AFR, Diversions, Idivert, EXCHANGE, DELTAVOL, LAKEVOL, Nsegsh
IF ( control_integer(Dyn_ag_soil_flag, 'dyn_ag_soil_flag')/=0 ) Dyn_ag_soil_flag = OFF
Dynamic_flag = OFF
Dynamic_soil_flag = OFF
IF ( Dyn_intcp_flag/=0 .OR. Dyn_covden_flag/=0 .OR. &
& Dyn_potet_flag/=OFF .OR. Dyn_covtype_flag/=0 .OR. Dyn_transp_flag/=0 .OR. &
& Dyn_radtrncf_flag/=OFF .OR. Dyn_sro2dprst_perv_flag/=0 .OR. Dyn_sro2dprst_imperv_flag/=OFF .OR. &
& Dyn_fallfrost_flag/=OFF .OR. Dyn_springfrost_flag/=0 .OR. Dyn_snareathresh_flag/=0 .OR. &
IF ( Dyn_intcp_flag/=OFF .OR. Dyn_covden_flag/=OFF .OR. &
& Dyn_potet_flag/=OFF .OR. Dyn_covtype_flag/=OFF .OR. Dyn_transp_flag/=OFF .OR. &
& Dyn_radtrncf_flag/=OFF .OR. Dyn_sro2dprst_perv_flag/=OFF .OR. Dyn_sro2dprst_imperv_flag/=OFF .OR. &
& Dyn_fallfrost_flag/=OFF .OR. Dyn_springfrost_flag/=OFF .OR. Dyn_snareathresh_flag/=OFF .OR. &
& Dyn_transp_on_flag/=OFF ) Dynamic_flag = ACTIVE
IF ( Dyn_imperv_flag/=OFF .OR. Dyn_dprst_flag/=OFF .OR. Dyn_soil_flag/=OFF .OR. &
& Dyn_ag_frac_flag==ACTIVE .OR. Dyn_ag_soil_flag==ACTIVE ) Dynamic_soil_flag = ACTIVE
Expand Down Expand Up @@ -1219,7 +1218,7 @@ INTEGER FUNCTION check_dims(Nsegshold, Nlakeshold)
ENDIF
IF ( Cascadegw_flag==CASCADEGW_SAME ) Ncascdgw = Ncascade
IF ( Ncascade==0 ) Cascade_flag = CASCADE_OFF
IF ( Ncascdgw==0 .OR. gwflow_flag==OFF ) Cascadegw_flag = CASCADEGW_OFF
IF ( (Ncascdgw==0 .OR. gwflow_flag==OFF) .AND. activeHRU_inactiveCELL_flag==OFF ) Cascadegw_flag = CASCADEGW_OFF
IF ( Model==MODFLOW .OR. Model==MODSIM_MODFLOW .OR. Model==MODSIM ) THEN ! only call if PRMS not active
Cascadegw_flag = CASCADEGW_OFF
Cascade_flag = CASCADE_OFF
Expand Down
23 changes: 17 additions & 6 deletions GSFLOW/src/gsflow/gsflow_prms2mf.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ MODULE GSFPRMS2MF
! Module Variables
character(len=*), parameter :: MODDESC = 'GSFLOW PRMS to MODFLOW'
character(len=*), parameter :: MODNAME = 'gsflow_prms2mf'
character(len=*), parameter :: Version_gsflow_prms2mf = '2024-02-10'
character(len=*), parameter :: Version_gsflow_prms2mf = '2024-05-30'
REAL, PARAMETER :: SZ_CHK = 0.00001
DOUBLE PRECISION, PARAMETER :: PCT_CHK = 0.000005D0
INTEGER, SAVE :: NTRAIL_CHK, Nlayp1
Expand Down Expand Up @@ -400,7 +400,7 @@ END FUNCTION prms2mfinit
!***********************************************************************
INTEGER FUNCTION prms2mfrun()
USE PRMS_CONSTANTS, ONLY: NEARZERO, ACTIVE
USE PRMS_MODULE, ONLY: Nhrucell, Gvr_cell_id, Have_lakes, Dprst_flag, Ag_package, Hru_type
USE PRMS_MODULE, ONLY: Nhrucell, Gvr_cell_id, Have_lakes, Dprst_flag, Ag_package, Hru_type, activeHRU_inactiveCELL_flag
USE GSFPRMS2MF
USE GSFMODFLOW, ONLY: Gvr2cell_conv, Acre_inches_to_mfl3_sngl, Gwc_row, Gwc_col, Mft_to_days
USE GLOBAL, ONLY: IBOUND
Expand All @@ -409,7 +409,7 @@ INTEGER FUNCTION prms2mfrun()
USE GWFLAKMODULE, ONLY: RNF, EVAPLK, PRCPLK !, NLAKES
USE PRMS_BASIN, ONLY: Active_hrus, Hru_route_order, Hru_area, Lake_hru_id !, Lake_area
USE PRMS_CLIMATEVARS, ONLY: Hru_ppt
USE PRMS_FLOWVARS, ONLY: Hru_actet
USE PRMS_FLOWVARS, ONLY: Hru_actet, Gw_upslope
USE PRMS_SRUNOFF, ONLY: Hortonian_lakes
USE PRMS_SOILZONE, ONLY: Sm2gw_grav, Lakein_sz, Hrucheck, Gvr_hru_id, Unused_potet, Gvr_hru_pct_adjusted
IMPLICIT NONE
Expand All @@ -419,6 +419,7 @@ INTEGER FUNCTION prms2mfrun()
! Local Variables
INTEGER :: irow, icol, ik, jk, ii, ilake
INTEGER :: j, icell, ihru, is_draining
REAL :: avail_h2o
!***********************************************************************
prms2mfrun = 0

Expand Down Expand Up @@ -464,6 +465,12 @@ INTEGER FUNCTION prms2mfrun()
Cell_drain_rate = 0.0 ! should just be active cells
finf_cell = 0.0
Gw_rejected_grav = Sm2gw_grav ! assume all is rejected to start with
IF ( activeHRU_inactiveCELL_flag == ACTIVE ) THEN
DO j = 1, Active_hrus
ihru = Hru_route_order(j)
IF ( activeHRU_inactiveCell(ihru) == 0 ) Gw_rejected_grav(ihru) = Gw_rejected_grav(ihru) + Gw_upslope(ihru)
ENDDO
ENDIF
is_draining = 0

DO j = 1, Nhrucell
Expand All @@ -487,18 +494,22 @@ INTEGER FUNCTION prms2mfrun()
! If UZF cell is inactive OR if too many waves then dump water back into
! the soilzone
!-----------------------------------------------------------------------
IF ( Sm2gw_grav(j)>0.0 ) THEN
avail_h2o = Sm2gw_grav(j)
IF ( activeHRU_inactiveCELL_flag == ACTIVE ) THEN
IF ( activeHRU_inactiveCell(j) == 0 ) avail_h2o = avail_h2o + Gw_upslope(j)
ENDIF
IF ( avail_h2o>0.0 ) THEN

IF ( IUZFOPT==0 ) THEN !ERIC 20210107: NWAVST is dimensioned (1, 1) if IUZFOPT == 0.
Cell_drain_rate(icell) = Cell_drain_rate(icell) + Sm2gw_grav(j)*Gvr2cell_conv(j)
Cell_drain_rate(icell) = Cell_drain_rate(icell) + avail_h2o*Gvr2cell_conv(j)
Gw_rejected_grav(j) = 0.0
is_draining = 1

ELSEIF ( NWAVST(icol, irow)<NTRAIL_CHK ) THEN
!-----------------------------------------------------------------------
! Convert drainage from inches to MF Length/Time
!-----------------------------------------------------------------------
Cell_drain_rate(icell) = Cell_drain_rate(icell) + Sm2gw_grav(j)*Gvr2cell_conv(j)
Cell_drain_rate(icell) = Cell_drain_rate(icell) + avail_h2o*Gvr2cell_conv(j)
Gw_rejected_grav(j) = 0.0
is_draining = 1
ENDIF
Expand Down
Loading

0 comments on commit 87261a7

Please sign in to comment.