Skip to content

Commit

Permalink
resolved some bugs and merged with PRMS6.0.0, main bugs in stream_tem…
Browse files Browse the repository at this point in the history
…p.f90 and prms_summary.f90
  • Loading branch information
rsregan committed Jan 16, 2025
1 parent 56914aa commit 4876e8e
Show file tree
Hide file tree
Showing 15 changed files with 308 additions and 160 deletions.
4 changes: 2 additions & 2 deletions GSFLOW/src/gsflow/gsflow_module.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ 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 12/11/2024'
character(len=*), parameter :: GSFLOW_versn = '2.4.0 12/20/2024'
character(len=*), parameter :: PRMS_versn = '2024-12-20'
character(len=*), parameter :: PRMS_VERSION = 'Version 6.0.0 12/20/2024'
character(len=*), parameter :: githash = 'Github Commit Hash a4cffeceecab925507a192e0f4822c89f8f37065'
Expand All @@ -32,7 +32,7 @@ MODULE PRMS_MODULE
INTEGER, SAVE :: Precip_combined_flag, Temp_combined_flag, Muskingum_flag
INTEGER, SAVE :: Inputerror_flag, Timestep
INTEGER, SAVE :: Humidity_cbh_flag, Windspeed_cbh_flag, Albedo_cbh_flag, Cloud_cover_cbh_flag
INTEGER, SAVE :: PRMS4_flag, PRMS6_flag
INTEGER, SAVE :: PRMS4_flag, bias_adjust_flag
INTEGER, SAVE :: PRMS_flag, GSFLOW_flag, PRMS_only, Gsf_unt
INTEGER, SAVE :: Kper_mfo, Kkstp_mfo, Have_lakes, Grid_flag, Ag_package, MODSIM_flag, AG_flag, gwflow_flag
INTEGER, SAVE :: Canopy_iter, irrigated_area_cbh_flag, AET_cbh_flag, PET_cbh_flag
Expand Down
25 changes: 12 additions & 13 deletions GSFLOW/src/gsflow/gsflow_prms.f90
Original file line number Diff line number Diff line change
Expand Up @@ -51,7 +51,7 @@ SUBROUTINE gsflow_prms(Process_mode, AFR, MS_GSF_converge, Nsegshold, Nlakeshold
INTEGER, EXTERNAL :: stream_temp, glacr, dynamic_soil_param_read, strmflow_character
INTEGER, EXTERNAL :: soilzone_ag
EXTERNAL :: precip_map, temp_map, segment_to_hru, gwflow_inactive_cell
EXTERNAL :: water_balance, prms_summary, convert_params, input_error
EXTERNAL :: water_balance, prms_summary, convert_params
EXTERNAL :: gsflow_prms2modsim, gsflow_modsim2prms
INTEGER, EXTERNAL :: gsflow_prms2mf, gsflow_mf2prms, gsflow_budget, gsflow_sum
! Local Variables
Expand Down Expand Up @@ -375,7 +375,7 @@ SUBROUTINE gsflow_prms(Process_mode, AFR, MS_GSF_converge, Nsegshold, Nlakeshold
IF ( Model==FROST ) THEN
IF ( Process_flag==DECL ) CALL read_parameter_file_params()
ierr = frost_date()
IF ( Inputerror_flag == 1 ) CALL input_error()
IF ( Inputerror_flag == 1 .OR. Parameter_check_flag==2 ) CALL input_error()
RETURN
ENDIF

Expand All @@ -391,7 +391,7 @@ SUBROUTINE gsflow_prms(Process_mode, AFR, MS_GSF_converge, Nsegshold, Nlakeshold

IF ( Model==CLIMATE ) THEN
IF ( Process_flag==DECL ) CALL read_parameter_file_params()
IF ( Inputerror_flag == 1 ) CALL input_error()
IF ( Inputerror_flag == 1 .OR. Parameter_check_flag==2 ) CALL input_error()
CALL summary_output()
RETURN
ENDIF
Expand All @@ -412,7 +412,7 @@ SUBROUTINE gsflow_prms(Process_mode, AFR, MS_GSF_converge, Nsegshold, Nlakeshold

IF ( Model==TRANSPIRE ) THEN
IF ( Process_flag==DECL ) CALL read_parameter_file_params()
IF ( Inputerror_flag == 1 ) CALL input_error()
IF ( Inputerror_flag == 1 .OR. Parameter_check_flag==2 ) CALL input_error()
CALL summary_output()
RETURN
ENDIF
Expand All @@ -438,13 +438,13 @@ SUBROUTINE gsflow_prms(Process_mode, AFR, MS_GSF_converge, Nsegshold, Nlakeshold
IF ( Model==WRITE_CLIMATE ) THEN
ierr = write_climate_hru()
IF ( Process_flag==DECL ) CALL read_parameter_file_params()
IF ( Inputerror_flag == 1 ) CALL input_error()
IF ( Inputerror_flag == 1 .OR. Parameter_check_flag==2 ) CALL input_error()
RETURN
ENDIF

IF ( Model==POTET ) THEN
IF ( Process_flag==DECL ) CALL read_parameter_file_params()
IF ( Inputerror_flag == 1 ) CALL input_error()
IF ( Inputerror_flag == 1 .OR. Parameter_check_flag==2 ) CALL input_error()
CALL summary_output()
RETURN
ENDIF
Expand Down Expand Up @@ -595,10 +595,10 @@ SUBROUTINE gsflow_prms(Process_mode, AFR, MS_GSF_converge, Nsegshold, Nlakeshold
IF ( Model==CONVERT ) CALL convert_params()
ELSEIF ( Process_flag==INIT ) THEN
CALL check_parameters()
IF ( Parameter_check_flag==2 ) STOP
IF ( Inputerror_flag==1 ) CALL input_error()
IF ( Inputerror_flag==1 .OR. Parameter_check_flag==2 ) CALL input_error()
IF ( Model==CONVERT ) THEN
CALL convert_params()
PRINT *, 'File PRMS_4.params or PRMS_5.params contain the converted parameters'
STOP
ENDIF
IF ( Print_debug>DEBUG_minimum ) &
Expand Down Expand Up @@ -664,7 +664,6 @@ SUBROUTINE setdims(AFR, Diversions, Idivert, EXCHANGE, DELTAVOL, LAKEVOL, Nsegsh
IF ( control_string(Model_mode, 'model_mode')/=0 ) CALL read_error(5, 'model_mode')
IF ( Model_mode(:4)==' ' ) Model_mode = 'GSFLOW5'
PRMS4_flag = OFF
PRMS6_flag = OFF
PRMS_flag = ACTIVE
GSFLOW_flag = OFF
PRMS_only = OFF
Expand All @@ -674,10 +673,6 @@ SUBROUTINE setdims(AFR, Diversions, Idivert, EXCHANGE, DELTAVOL, LAKEVOL, Nsegsh
Model = PRMS
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' .OR. Model_mode(:5)=='GSFLOW6' ) THEN
PRMS4_flag = OFF
PRMS6_flag = ACTIVE
ENDIF
PRMS_only = ACTIVE
ELSEIF ( Model_mode(:6)=='GSFLOW' .OR. Model_mode(:6)=='gsflow' ) THEN
Model = GSFLOW
Expand Down Expand Up @@ -950,6 +945,7 @@ SUBROUTINE setdims(AFR, Diversions, Idivert, EXCHANGE, DELTAVOL, LAKEVOL, Nsegsh
IF ( control_integer(Windspeed_cbh_flag, 'windspeed_cbh_flag')/=0 ) Windspeed_cbh_flag = OFF
IF ( control_integer(Albedo_cbh_flag, 'albedo_cbh_flag')/=0 ) Albedo_cbh_flag = OFF
IF ( control_integer(Cloud_cover_cbh_flag, 'cloud_cover_cbh_flag')/=0 ) Cloud_cover_cbh_flag = OFF
IF ( control_integer(bias_adjust_flag, 'bias_adjust_flag')/=0 ) bias_adjust_flag = OFF
IF ( Et_flag==potet_pm_module .OR. Et_flag==potet_pt_module .OR. &
& (Stream_temp_flag==ACTIVE .AND. Strmtemp_humidity_flag==OFF) ) Humidity_cbh_flag = ACTIVE
IF ( Et_flag==potet_pm_module ) Windspeed_cbh_flag = ACTIVE
Expand Down Expand Up @@ -1035,6 +1031,7 @@ SUBROUTINE setdims(AFR, Diversions, Idivert, EXCHANGE, DELTAVOL, LAKEVOL, Nsegsh

! 0 = off, 1 = on, 2 = lauren version, 3 = CSV for POIs
IF ( control_integer(CsvON_OFF, 'csvON_OFF')/=0 ) CsvON_OFF = OFF

! map results dimensions
IF ( control_integer(MapOutON_OFF, 'mapOutON_OFF')/=0 ) MapOutON_OFF = OFF
idim = 0
Expand Down Expand Up @@ -1515,6 +1512,7 @@ END SUBROUTINE check_module_names
SUBROUTINE input_error()
!***********************************************************************
USE PRMS_CONSTANTS, ONLY: ERROR_param
USE PRMS_MODULE, ONLY: Parameter_check_flag
IMPLICIT NONE
!***********************************************************************
PRINT '(//,A,//,A,/,A,/,A)', '**Fix input errors in your Parameter File to continue**', &
Expand All @@ -1526,6 +1524,7 @@ SUBROUTINE input_error()
'parameter_check_flag to 0. After calibration set the', &
'parameter_check_flag to 1 to verify that those calibration', &
'parameters have valid and compatible values.'
IF ( Parameter_check_flag==2 ) STOP
ERROR STOP ERROR_param

END SUBROUTINE input_error
Expand Down
6 changes: 3 additions & 3 deletions GSFLOW/src/prms/climate_hru.f90
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ INTEGER FUNCTION climate_hru()
& Climate_precip_flag, Climate_temp_flag, Climate_potet_flag, Climate_swrad_flag, &
& Start_year, Start_month, Start_day, Humidity_cbh_flag, Windspeed_cbh_flag, &
& Albedo_cbh_flag, Cloud_cover_cbh_flag, Nowmonth, &
& Nowyear, Nowday, forcing_check_flag, Print_debug, Ncbh, PRMS6_flag, &
& Nowyear, Nowday, forcing_check_flag, Print_debug, Ncbh, bias_adjust_flag, &
& irrigated_area_cbh_flag, AET_cbh_flag, PET_cbh_flag
USE PRMS_CLIMATE_HRU
USE PRMS_BASIN, ONLY: Active_hrus, Hru_route_order, Hru_area, Basin_area_inv, Ag_Frac
Expand Down Expand Up @@ -420,7 +420,7 @@ INTEGER FUNCTION climate_hru()
! Declared Parameters
IF ( Climate_temp_flag==ACTIVE ) THEN
ALLOCATE ( Tmax_cbh_adj(Nhru,MONTHS_PER_YEAR) )
IF ( PRMS6_flag==ACTIVE ) THEN
IF ( bias_adjust_flag==ACTIVE ) THEN
ALLOCATE ( Tmax_cbh_adj_offset(Nhru,MONTHS_PER_YEAR) )
IF ( declparam(MODNAME, 'tmax_cbh_adj_offset', 'nhru,nmonths', 'real', &
& '0.0', '0.0', '50.0', &
Expand Down Expand Up @@ -512,7 +512,7 @@ INTEGER FUNCTION climate_hru()
IF ( Climate_temp_flag==ACTIVE ) THEN
IF ( getparam_real(MODNAME, 'tmin_cbh_adj', Nhru*MONTHS_PER_YEAR, Tmin_cbh_adj)/=0 ) &
CALL read_error(2, 'tmin_cbh_adj')
IF ( PRMS6_flag==ACTIVE ) THEN
IF ( bias_adjust_flag==ACTIVE ) THEN
IF ( getparam_real(MODNAME, 'tmax_cbh_adj_offset', Nhru*MONTHS_PER_YEAR, Tmax_cbh_adj_offset)/=0 ) &
CALL read_error(2, 'tmax_cbh_adj_offset')
Tmax_cbh_adj = Tmin_cbh_adj + Tmax_cbh_adj_offset
Expand Down
16 changes: 8 additions & 8 deletions GSFLOW/src/prms/climateflow.f90
Original file line number Diff line number Diff line change
Expand Up @@ -162,7 +162,7 @@ INTEGER FUNCTION climateflow_decl()
& ddsolrad_module, ccsolrad_module, CANOPY
USE PRMS_MODULE, ONLY: Nhru, Nssr, Nsegment, Nevap, Nlake, Ntemp, Nrain, Nsol, Ngw, Inputerror_flag, &
& Init_vars_from_file, Temp_flag, Precip_flag, Glacier_flag, &
& Strmflow_module, Temp_module, Stream_order_flag, PRMS6_flag, &
& Strmflow_module, Temp_module, Stream_order_flag, bias_adjust_flag, &
& Precip_module, Solrad_module, Transp_module, Et_module, PRMS4_flag, &
& Soilzone_module, Srunoff_module, Call_cascade, Et_flag, Dprst_flag, Solrad_flag, Humidity_cbh_flag, &
& AG_flag, PRMS_land_iteration_flag, GSFLOW_flag, snow_flag, gwflow_flag, Nhrucell, activeHRU_inactiveCELL_flag
Expand Down Expand Up @@ -739,7 +739,7 @@ INTEGER FUNCTION climateflow_decl()
IF ( Temp_flag==temp_1sta_module .OR. Temp_flag==temp_laps_module .OR. Temp_flag==temp_dist2_module .OR. &
& Temp_flag==ide_dist_module .OR. Temp_flag==xyz_dist_module .OR. Temp_flag==temp_sta_module ) THEN
ALLOCATE ( Tmax_aspect_adjust(Nhru,MONTHS_PER_YEAR) )
IF ( PRMS6_flag==ACTIVE ) THEN
IF ( bias_adjust_flag==ACTIVE ) THEN
ALLOCATE ( Tmax_adj_offset(Nhru,MONTHS_PER_YEAR) )
IF ( declparam(Temp_module, 'tmax_adj_offset', 'nhru,nmonths', 'real', &
& '0.0', '0.0', '50.0', &
Expand Down Expand Up @@ -1018,7 +1018,7 @@ INTEGER FUNCTION climateflow_decl()
& 'inches', Ag_soil_moist)
ALLOCATE ( Ag_soil_rechr(Nhru), It0_ag_soil_rechr(Nhru) )
CALL declvar_real(Soilzone_module, 'ag_soil_rechr', 'nhru', Nhru, &
& 'Water storage for upper portion in the capillary reservoir of the irrigated area for each HRU that // &
& 'Water storage for upper portion in the capillary reservoir of the irrigated area for each HRU that' // &
& ' is available for both evaporation and transpiration', &
& 'inches', Ag_soil_rechr)
ALLOCATE ( Ag_soil_moist_max(Nhru) )
Expand Down Expand Up @@ -1069,7 +1069,7 @@ INTEGER FUNCTION climateflow_init()
& Temp_module, Stream_order_flag, Glacier_flag, &
& Precip_module, Solrad_module, Et_module, PRMS4_flag, &
& Soilzone_module, Srunoff_module, Et_flag, Dprst_flag, Solrad_flag, &
& Parameter_check_flag, Inputerror_flag, Humidity_cbh_flag, PRMS6_flag, &
& Parameter_check_flag, Inputerror_flag, Humidity_cbh_flag, bias_adjust_flag, &
& GSFLOW_flag, Hru_type, AG_flag, gwflow_flag
USE PRMS_CLIMATEVARS
USE PRMS_FLOWVARS
Expand Down Expand Up @@ -1100,7 +1100,7 @@ INTEGER FUNCTION climateflow_init()
& Temp_flag==ide_dist_module .OR. Temp_flag==xyz_dist_module .OR. Temp_flag==temp_sta_module ) THEN
IF ( getparam_real(Temp_module, 'tmin_adj', Nhru*MONTHS_PER_YEAR, Tmin_aspect_adjust)/=0 ) &
CALL read_error(2, 'tmin_adj')
IF ( PRMS6_flag==ACTIVE ) THEN
IF ( bias_adjust_flag==ACTIVE ) THEN
IF ( getparam_real(Temp_module, 'tmax_adj_offset', Nhru*MONTHS_PER_YEAR, Tmax_adj_offset)/=0 ) &
CALL read_error(2, 'tmax_adj_offset')
Tmax_aspect_adjust = Tmin_aspect_adjust + Tmax_adj_offset
Expand Down Expand Up @@ -1637,7 +1637,7 @@ SUBROUTINE precip_form(Precip, Hru_ppt, Hru_rain, Hru_snow, Tmaxf, &
& Tminf, Tavgf, Pptmix, Newsnow, Prmx, Tmax_allrain_f, Rain_adj, &
& Snow_adj, Adjmix_rain, Hru_area, Sum_obs, Tmax_allsnow_f, Ihru)
USE PRMS_CONSTANTS, ONLY: ACTIVE, OFF !, DEBUG_minimum
USE PRMS_MODULE, ONLY: forcing_check_flag, PRMS6_flag !, Print_debug
USE PRMS_MODULE, ONLY: forcing_check_flag, bias_adjust_flag !, Print_debug
USE PRMS_CLIMATEVARS, ONLY: Basin_ppt, Basin_rain, Basin_snow
use prms_utils, only: print_date
IMPLICIT NONE
Expand Down Expand Up @@ -1666,11 +1666,11 @@ SUBROUTINE precip_form(Precip, Hru_ppt, Hru_rain, Hru_snow, Tmaxf, &
!******If minimum temperature is above base temperature for snow or
!******maximum temperature is above all_rain temperature then
!******precipitation is all rain
ELSEIF ( PRMS6_flag==ACTIVE .AND. .not.(Tavgf<Tmax_allrain_f) ) THEN
ELSEIF ( bias_adjust_flag==ACTIVE .AND. .not.(Tavgf<Tmax_allrain_f) ) THEN
Hru_ppt = Precip*Rain_adj
Hru_rain = Hru_ppt
Prmx = 1.0
ELSEIF ( PRMS6_flag==OFF .AND. (Tminf>Tmax_allsnow_f .OR. Tmaxf>=Tmax_allrain_f) ) THEN
ELSEIF ( bias_adjust_flag==OFF .AND. (Tminf>Tmax_allsnow_f .OR. Tmaxf>=Tmax_allrain_f) ) THEN
Hru_ppt = Precip*Rain_adj
Hru_rain = Hru_ppt
Prmx = 1.0
Expand Down
6 changes: 5 additions & 1 deletion GSFLOW/src/prms/muskingum.f90
Original file line number Diff line number Diff line change
Expand Up @@ -238,7 +238,11 @@ INTEGER FUNCTION muskingum_run()
! current inflow to the segment is the time weighted average of the outflow
! of the upstream segments plus the lateral HRU inflow plus any gains.
currin = Seg_lateral_inflow(iorder) !note, this routes to inlet
IF ( Obsin_segment(iorder)>0 ) Seg_upstream_inflow(iorder) = Streamflow_cfs(Obsin_segment(iorder))
IF ( Obsin_segment(iorder)>0 ) THEN
IF ( .not.(Streamflow_cfs(Obsin_segment(iorder))<0.0)) &
CALL error_stop('negative replacement streamflow in muskingum', ERROR_streamflow)
Seg_upstream_inflow(iorder) = Streamflow_cfs(Obsin_segment(iorder))
ENDIF
currin = currin + Seg_upstream_inflow(iorder)
Seg_inflow(iorder) = Seg_inflow(iorder) + currin
Inflow_ts(iorder) = Inflow_ts(iorder) + currin
Expand Down
7 changes: 5 additions & 2 deletions GSFLOW/src/prms/muskingum_lake.f90
Original file line number Diff line number Diff line change
Expand Up @@ -991,8 +991,11 @@ INTEGER FUNCTION muskingum_lake_run()
! current inflow to the segment is the time weighted average of the outflow
! of the upstream segments plus the lateral HRU inflow plus any gains.
currin = Seg_lateral_inflow(iorder) !note, this routes to inlet

IF ( Obsin_segment(iorder)>0 ) Seg_upstream_inflow(iorder) = Streamflow_cfs(Obsin_segment(iorder))
IF ( Obsin_segment(iorder)>0 ) THEN
IF ( .not.(Streamflow_cfs(Obsin_segment(iorder))<0.0)) &
CALL error_stop('negative replacement streamflow in muskingum', ERROR_streamflow)
Seg_upstream_inflow(iorder) = Streamflow_cfs(Obsin_segment(iorder))
ENDIF
currin = currin + Seg_upstream_inflow(iorder)
Seg_inflow(iorder) = Seg_inflow(iorder) + currin
Inflow_ts(iorder) = Inflow_ts(iorder) + currin
Expand Down
2 changes: 1 addition & 1 deletion GSFLOW/src/prms/precip_1sta_laps.f90
Original file line number Diff line number Diff line change
Expand Up @@ -126,7 +126,7 @@ INTEGER FUNCTION precip_1sta_laps()
& '1.0', '0.2', '10.0', &
& 'Monthly rain adjustment factor for each HRU', &
& 'Monthly (January to December) multiplicative factor to adjust measured rain on each HRU'// &
& ' to account for differences in elevationand other factors', &
& ' to account for differences in elevation and other factors', &
& 'decimal fraction')/=0 ) CALL read_error(1, 'rain_adj')

IF ( declparam(MODNAME, 'snow_adj', 'nhru,nmonths', 'real', &
Expand Down
2 changes: 0 additions & 2 deletions GSFLOW/src/prms/prms_constants.f90
Original file line number Diff line number Diff line change
Expand Up @@ -134,9 +134,7 @@ MODULE PRMS_CONSTANTS
! model_mode
integer, parameter :: GSFLOW = 0
integer, parameter :: PRMS = 1
integer, parameter :: PRMS6 = 6
integer, parameter :: MODFLOW = 2

integer, parameter :: MODSIM_PRMS = 3
integer, parameter :: MODSIM_GSFLOW = 10
integer, parameter :: MODSIM_MODFLOW = 11
Expand Down
Loading

0 comments on commit 4876e8e

Please sign in to comment.