18   character(len=LENFTYPE) :: 
ftype = 
'RIV' 
   19   character(len=LENPACKAGENAME) :: 
text = 
'             RIV' 
   22     real(dp), 
dimension(:), 
pointer, 
contiguous :: stage => null() 
 
   23     real(dp), 
dimension(:), 
pointer, 
contiguous :: cond => null() 
 
   24     real(dp), 
dimension(:), 
pointer, 
contiguous :: rbot => null() 
 
   49   subroutine riv_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, &
 
   52     class(
bndtype), 
pointer :: packobj
 
   53     integer(I4B), 
intent(in) :: id
 
   54     integer(I4B), 
intent(in) :: ibcnum
 
   55     integer(I4B), 
intent(in) :: inunit
 
   56     integer(I4B), 
intent(in) :: iout
 
   57     character(len=*), 
intent(in) :: namemodel
 
   58     character(len=*), 
intent(in) :: pakname
 
   59     character(len=*), 
intent(in) :: mempath
 
   61     type(
rivtype), 
pointer :: rivobj
 
   68     call packobj%set_names(ibcnum, namemodel, pakname, 
ftype, mempath)
 
   72     call rivobj%allocate_scalars()
 
   75     call packobj%pack_initialize()
 
   77     packobj%inunit = inunit
 
   80     packobj%ibcnum = ibcnum
 
   93     call this%BndExtType%bnd_da()
 
  109     class(
rivtype), 
intent(inout) :: this
 
  114     call this%BndExtType%source_options()
 
  117     call mem_set_value(this%imover, 
'MOVER', this%input_mempath, found%mover)
 
  120     call this%log_riv_options(found)
 
  129     class(
rivtype), 
intent(inout) :: this
 
  133     write (this%iout, 
'(/1x,a)') 
'PROCESSING '//trim(adjustl(this%text)) &
 
  136     if (found%mover) 
then 
  137       write (this%iout, 
'(4x,A)') 
'MOVER OPTION ENABLED' 
  141     write (this%iout, 
'(1x,a)') &
 
  142       'END OF '//trim(adjustl(this%text))//
' OPTIONS' 
  152     integer(I4B), 
dimension(:), 
pointer, 
contiguous, 
optional :: nodelist
 
  153     real(DP), 
dimension(:, :), 
pointer, 
contiguous, 
optional :: auxvar
 
  156     call this%BndExtType%allocate_arrays(nodelist, auxvar)
 
  159     call mem_setptr(this%stage, 
'STAGE', this%input_mempath)
 
  160     call mem_setptr(this%cond, 
'COND', this%input_mempath)
 
  161     call mem_setptr(this%rbot, 
'RBOT', this%input_mempath)
 
  164     call mem_checkin(this%stage, 
'STAGE', this%memoryPath, &
 
  165                      'STAGE', this%input_mempath)
 
  166     call mem_checkin(this%cond, 
'COND', this%memoryPath, &
 
  167                      'COND', this%input_mempath)
 
  168     call mem_checkin(this%rbot, 
'RBOT', this%memoryPath, &
 
  169                      'RBOT', this%input_mempath)
 
  178     class(
rivtype), 
intent(inout) :: this
 
  180     if (this%iper /= 
kper) 
return 
  183     call this%BndExtType%bnd_rp()
 
  186     if (this%ivsc == 1) 
then 
  187       call this%riv_store_user_cond()
 
  191     if (this%iprpak /= 0) 
then 
  192       call this%write_list()
 
  203     class(
rivtype), 
intent(inout) :: this
 
  205     character(len=LINELENGTH) :: errmsg
 
  212     character(len=*), 
parameter :: fmtriverr = &
 
  213       "('RIV BOUNDARY (',i0,') RIVER BOTTOM (',f10.4,') IS LESS & 
  214       &THAN CELL BOTTOM (',f10.4,')')" 
  215     character(len=*), 
parameter :: fmtriverr2 = &
 
  216       "('RIV BOUNDARY (',i0,') RIVER STAGE (',f10.4,') IS LESS & 
  217       &THAN RIVER BOTTOM (',f10.4,')')" 
  218     character(len=*), 
parameter :: fmtriverr3 = &
 
  219       "('RIV BOUNDARY (',i0,') RIVER STAGE (',f10.4,') IS LESS & 
  220       &THAN CELL BOTTOM (',f10.4,')')" 
  221     character(len=*), 
parameter :: fmtcondmulterr = &
 
  222       "('RIV BOUNDARY (',i0,') CONDUCTANCE MULTIPLIER (',g10.3,') IS & 
  224     character(len=*), 
parameter :: fmtconderr = &
 
  225       "('RIV BOUNDARY (',i0,') CONDUCTANCE (',g10.3,') IS LESS THAN & 
  229     do i = 1, this%nbound
 
  230       node = this%nodelist(i)
 
  231       bt = this%dis%bot(node)
 
  232       stage = this%stage(i)
 
  235       if (rbot < bt .and. this%icelltype(node) /= 0) 
then 
  236         write (errmsg, fmt=fmtriverr) i, rbot, bt
 
  239       if (stage < rbot) 
then 
  240         write (errmsg, fmt=fmtriverr2) i, stage, rbot
 
  243       if (stage < bt .and. this%icelltype(node) /= 0) 
then 
  244         write (errmsg, fmt=fmtriverr3) i, stage, bt
 
  247       if (this%iauxmultcol > 0) 
then 
  248         if (this%auxvar(this%iauxmultcol, i) < dzero) 
then 
  249           write (errmsg, fmt=fmtcondmulterr) &
 
  250             i, this%auxvar(this%iauxmultcol, i)
 
  254       if (this%cond(i) < dzero) 
then 
  255         write (errmsg, fmt=fmtconderr) i, this%cond(i)
 
  274     integer(I4B) :: i, node
 
  275     real(DP) :: hriv, criv, rbot
 
  278     if (this%nbound .eq. 0) 
return 
  281     do i = 1, this%nbound
 
  282       node = this%nodelist(i)
 
  283       if (this%ibound(node) <= 0) 
then 
  289       criv = this%cond_mult(i)
 
  291       if (this%xnew(node) <= rbot) 
then 
  292         this%rhs(i) = -criv * (hriv - rbot)
 
  295         this%rhs(i) = -criv * hriv
 
  303   subroutine riv_fc(this, rhs, ia, idxglo, matrix_sln)
 
  306     real(DP), 
dimension(:), 
intent(inout) :: rhs
 
  307     integer(I4B), 
dimension(:), 
intent(in) :: ia
 
  308     integer(I4B), 
dimension(:), 
intent(in) :: idxglo
 
  311     integer(I4B) :: i, n, ipos
 
  312     real(DP) :: cond, stage, qriv 
 
  315     if (this%imover == 1) 
then 
  316       call this%pakmvrobj%fc()
 
  320     do i = 1, this%nbound
 
  322       rhs(n) = rhs(n) + this%rhs(i)
 
  324       call matrix_sln%add_value_pos(idxglo(ipos), this%hcof(i))
 
  328       stage = this%stage(i)
 
  329       if (this%imover == 1 .and. this%xnew(n) > stage) 
then 
  330         cond = this%cond_mult(i)
 
  331         qriv = cond * (this%xnew(n) - stage)
 
  332         call this%pakmvrobj%accumulate_qformvr(i, qriv)
 
  342     class(
rivtype), 
intent(inout) :: this
 
  345     this%listlabel = trim(this%filtyp)//
' NO.' 
  346     if (this%dis%ndim == 3) 
then 
  347       write (this%listlabel, 
'(a, a7)') trim(this%listlabel), 
'LAYER' 
  348       write (this%listlabel, 
'(a, a7)') trim(this%listlabel), 
'ROW' 
  349       write (this%listlabel, 
'(a, a7)') trim(this%listlabel), 
'COL' 
  350     elseif (this%dis%ndim == 2) 
then 
  351       write (this%listlabel, 
'(a, a7)') trim(this%listlabel), 
'LAYER' 
  352       write (this%listlabel, 
'(a, a7)') trim(this%listlabel), 
'CELL2D' 
  354       write (this%listlabel, 
'(a, a7)') trim(this%listlabel), 
'NODE' 
  356     write (this%listlabel, 
'(a, a16)') trim(this%listlabel), 
'STAGE' 
  357     write (this%listlabel, 
'(a, a16)') trim(this%listlabel), 
'CONDUCTANCE' 
  358     write (this%listlabel, 
'(a, a16)') trim(this%listlabel), 
'BOTTOM EL.' 
  359     if (this%inamedbound == 1) 
then 
  360       write (this%listlabel, 
'(a, a16)') trim(this%listlabel), 
'BOUNDARY NAME' 
  389     call this%obs%StoreObsType(
'riv', .true., indx)
 
  394     call this%obs%StoreObsType(
'to-mvr', .true., indx)
 
  402     class(
rivtype), 
intent(inout) :: this
 
  407     do n = 1, this%nbound
 
  408       this%condinput(n) = this%cond_mult(n)
 
  418     class(
rivtype), 
intent(inout) :: this
 
  419     integer(I4B), 
intent(in) :: row
 
  423     if (this%iauxmultcol > 0) 
then 
  424       cond = this%cond(row) * this%auxvar(this%iauxmultcol, row)
 
  426       cond = this%cond(row)
 
  436     class(
rivtype), 
intent(inout) :: this
 
  437     integer(I4B), 
intent(in) :: col
 
  438     integer(I4B), 
intent(in) :: row
 
  444       bndval = this%stage(row)
 
  446       bndval = this%cond_mult(row)
 
  448       bndval = this%rbot(row)
 
  450       errmsg = 
'Programming error. RIV bound value requested column '&
 
  451                &
'outside range of ncolbnd (3).' 
This module contains the extended boundary package.
This module contains the base boundary package.
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
integer(i4b), parameter lenpackagename
maximum length of the package name
integer(i4b), parameter lenftype
maximum length of a package type (DIS, WEL, OC, etc.)
real(dp), parameter dzero
real constant zero
This module defines variable data types.
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
This module contains the derived type ObsType.
subroutine, public defaultobsidprocessor(obsrv, dis, inunitobs, iout)
@ brief Process IDstring provided for each observation
subroutine riv_store_user_cond(this)
Store user-specified conductance value.
logical function riv_obs_supported(this)
Return true because RIV package supports observations.
real(dp) function cond_mult(this, row)
Apply multiplier to conductance if auxmultcol option is in use.
subroutine riv_allocate_arrays(this, nodelist, auxvar)
Allocate package arrays.
subroutine log_riv_options(this, found)
Log options specific to RivType.
subroutine riv_df_obs(this)
Store observation type supported by RIV package.
character(len=lenftype) ftype
subroutine define_listlabel(this)
Define the list heading that is written to iout when PRINT_INPUT option is used.
subroutine riv_options(this)
Set options specific to RivType.
character(len=lenpackagename) text
subroutine, public riv_create(packobj, id, ibcnum, inunit, iout, namemodel, pakname, mempath)
Create a New Riv Package and point packobj to the new package.
subroutine riv_cf(this)
Formulate the HCOF and RHS terms.
real(dp) function riv_bound_value(this, col, row)
Return requested boundary value.
subroutine riv_ck(this)
Check river boundary condition data.
subroutine riv_da(this)
Deallocate memory.
subroutine riv_fc(this, rhs, ia, idxglo, matrix_sln)
Copy rhs and hcof into solution rhs and amat.
subroutine riv_rp(this)
Read and prepare.
This module contains simulation methods.
subroutine, public store_error(msg, terminate)
Store an error message.
integer(i4b) function, public count_errors()
Return number of errors.
subroutine, public store_error_filename(filename, terminate)
Store the erroring file name.
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
This module contains simulation variables.
character(len=maxcharlen) errmsg
error message string
integer(i4b), pointer, public kper
current stress period number
This class is used to store a single deferred-length character string. It was designed to work in an ...