44     character(len=*), 
intent(in) :: component
 
   45     character(len=*), 
intent(in) :: subcomponent
 
   46     integer(I4B), 
intent(in) :: iout
 
   48       write (iout, 
'(1x,a)') 
'Loading input for '//trim(component)//&
 
   49         &
'/'//trim(subcomponent)
 
   56     character(len=*), 
intent(in) :: component
 
   57     character(len=*), 
intent(in) :: subcomponent
 
   58     integer(I4B), 
intent(in) :: iout
 
   60       write (iout, 
'(1x,a)') 
'Loading input complete...' 
   68     character(len=*), 
intent(in) :: component
 
   69     integer(I4B), 
intent(in) :: iout
 
   71       write (iout, 
'(/1x,a,i0,a)') 
'IDP PERIOD ', 
kper, &
 
   72         ' load for component: '//trim(component)
 
   80     integer(I4B), 
intent(in) :: iout
 
   83       write (iout, 
'(1x,a,/)') 
'IDP component dynamic load complete...' 
   90     character(len=*), 
intent(in) :: varname
 
   91     character(len=*), 
intent(in) :: mempath
 
   92     integer(I4B), 
intent(in) :: iout
 
   93     logical(LGP), 
intent(in) :: is_tas
 
   96         write (iout, 
'(3x, a, ": ", a)') &
 
   97           'Time-array-series controlled dynamic variable detected', trim(varname)
 
   99         write (iout, 
'(3x, a, ": ", a)') &
 
  100           'Time-series controlled dynamic variable detected', trim(varname)
 
  108     logical(LGP), 
intent(in) :: p_mem
 
  109     character(len=*), 
intent(in) :: varname
 
  110     character(len=*), 
intent(in) :: mempath
 
  111     integer(I4B), 
intent(in) :: iout
 
  112     character(len=LINELENGTH) :: description
 
  114       description = 
'Logical detected' 
  115       write (iout, 
'(3x, a, ": ", a, " = ", l1)') &
 
  116         trim(description), trim(varname), p_mem
 
  123     integer(I4B), 
intent(in) :: p_mem
 
  124     character(len=*), 
intent(in) :: varname
 
  125     character(len=*), 
intent(in) :: mempath
 
  126     character(len=*), 
intent(in) :: datatype
 
  127     integer(I4B), 
intent(in) :: iout
 
  128     character(len=LINELENGTH) :: description
 
  130       if (datatype == 
'KEYWORD') 
then 
  131         description = 
'Keyword detected' 
  132         write (iout, 
'(3x, a, ": ", a)') trim(description), trim(varname)
 
  134         description = 
'Integer detected' 
  135         write (iout, 
'(3x, a, ": ", a, " = ", i0)') &
 
  136           trim(description), trim(varname), p_mem
 
  144     integer(I4B), 
dimension(:), 
contiguous, 
intent(in) :: p_mem
 
  145     character(len=*), 
intent(in) :: varname
 
  146     character(len=*), 
intent(in) :: mempath
 
  147     integer(I4B), 
intent(in) :: iout
 
  148     integer(I4B) :: min_val, max_val
 
  149     character(len=LINELENGTH) :: description
 
  151       min_val = minval(p_mem)
 
  152       max_val = maxval(p_mem)
 
  153       if (min_val == max_val) 
then 
  154         description = 
'Integer 1D constant array detected' 
  155         write (iout, 
'(3x, a, ": ", a, " = ", i0)') &
 
  156           trim(description), trim(varname), min_val
 
  158         description = 
'Integer 1D array detected' 
  159         write (iout, 
'(3x, a, ": ", a, a, i0, a, i0)') &
 
  160           trim(description), trim(varname), &
 
  161           ' ranges from ', min_val, 
' to ', max_val
 
  169     integer(I4B), 
dimension(:, :), 
contiguous, 
intent(in) :: p_mem
 
  170     character(len=*), 
intent(in) :: varname
 
  171     character(len=*), 
intent(in) :: mempath
 
  172     integer(I4B), 
intent(in) :: iout
 
  173     integer(I4B) :: min_val, max_val
 
  174     character(len=LINELENGTH) :: description
 
  176       min_val = minval(p_mem)
 
  177       max_val = maxval(p_mem)
 
  178       if (min_val == max_val) 
then 
  179         description = 
'Integer 2D constant array detected' 
  180         write (iout, 
'(3x, a, ": ", a, " = ", i0)') &
 
  181           trim(description), trim(varname), min_val
 
  183         description = 
'Integer 2D array detected' 
  184         write (iout, 
'(3x, a, ": ", a, a, i0, a, i0)') &
 
  185           trim(description), trim(varname), &
 
  186           ' ranges from ', min_val, 
' to ', max_val
 
  194     integer(I4B), 
dimension(:, :, :), 
contiguous, 
intent(in) :: p_mem
 
  195     character(len=*), 
intent(in) :: varname
 
  196     character(len=*), 
intent(in) :: mempath
 
  197     integer(I4B), 
intent(in) :: iout
 
  198     integer(I4B) :: min_val, max_val
 
  199     character(len=LINELENGTH) :: description
 
  201       min_val = minval(p_mem)
 
  202       max_val = maxval(p_mem)
 
  203       if (min_val == max_val) 
then 
  204         description = 
'Integer 3D constant array detected' 
  205         write (iout, 
'(3x, a, ": ", a, " = ", i0)') &
 
  206           trim(description), trim(varname), min_val
 
  208         description = 
'Integer 3D array detected' 
  209         write (iout, 
'(3x, a, ": ", a, a, i0, a, i0)') &
 
  210           trim(description), trim(varname), &
 
  211           ' ranges from ', min_val, 
' to ', max_val
 
  219     real(DP), 
intent(in) :: p_mem
 
  220     character(len=*), 
intent(in) :: varname
 
  221     character(len=*), 
intent(in) :: mempath
 
  222     integer(I4B), 
intent(in) :: iout
 
  223     character(len=LINELENGTH) :: description
 
  225       description = 
'Double detected' 
  226       write (iout, 
'(3x, a, ": ", a, " = ", G0)') &
 
  227         trim(description), trim(varname), p_mem
 
  234     real(DP), 
dimension(:), 
contiguous, 
intent(in) :: p_mem
 
  235     character(len=*), 
intent(in) :: varname
 
  236     character(len=*), 
intent(in) :: mempath
 
  237     integer(I4B), 
intent(in) :: iout
 
  238     real(DP) :: min_val, max_val
 
  239     character(len=LINELENGTH) :: description
 
  241       min_val = minval(p_mem)
 
  242       max_val = maxval(p_mem)
 
  243       if (min_val == max_val) 
then 
  244         description = 
'Double precision 1D constant array detected' 
  245         write (iout, 
'(3x, a, ": ", a, " = ", G0)') &
 
  246           trim(description), trim(varname), min_val
 
  248         description = 
'Double precision 1D array detected' 
  249         write (iout, 
'(3x, a, ": ", a, a, G0, a, G0)') &
 
  250           trim(description), trim(varname), &
 
  251           ' ranges from ', min_val, 
' to ', max_val
 
  259     real(DP), 
dimension(:, :), 
contiguous, 
intent(in) :: p_mem
 
  260     character(len=*), 
intent(in) :: varname
 
  261     character(len=*), 
intent(in) :: mempath
 
  262     integer(I4B), 
intent(in) :: iout
 
  263     real(DP) :: min_val, max_val
 
  264     character(len=LINELENGTH) :: description
 
  266       min_val = minval(p_mem)
 
  267       max_val = maxval(p_mem)
 
  268       if (min_val == max_val) 
then 
  269         description = 
'Double precision 2D constant array detected' 
  270         write (iout, 
'(3x, a, ": ", a, " = ", G0)') &
 
  271           trim(description), trim(varname), min_val
 
  273         description = 
'Double precision 2D array detected' 
  274         write (iout, 
'(3x, a, ": ", a, a, G0, a, G0)') &
 
  275           trim(description), trim(varname), &
 
  276           ' ranges from ', min_val, 
' to ', max_val
 
  284     real(DP), 
dimension(:, :, :), 
contiguous, 
intent(in) :: p_mem
 
  285     character(len=*), 
intent(in) :: varname
 
  286     character(len=*), 
intent(in) :: mempath
 
  287     integer(I4B), 
intent(in) :: iout
 
  288     real(DP) :: min_val, max_val
 
  289     character(len=LINELENGTH) :: description
 
  291       min_val = minval(p_mem)
 
  292       max_val = maxval(p_mem)
 
  293       if (min_val == max_val) 
then 
  294         description = 
'Double precision 3D constant array detected' 
  295         write (iout, 
'(3x, a, ": ", a, " = ", G0)') &
 
  296           trim(description), trim(varname), min_val
 
  298         description = 
'Double precision 3D array detected' 
  299         write (iout, 
'(3x, a, ": ", a, a, G0, a, G0)') &
 
  300           trim(description), trim(varname), &
 
  301           ' ranges from ', min_val, 
' to ', max_val
 
  309     character(len=*), 
intent(in) :: p_mem
 
  310     character(len=*), 
intent(in) :: varname
 
  311     character(len=*), 
intent(in) :: mempath
 
  312     integer(I4B), 
intent(in) :: iout
 
  313     character(len=LINELENGTH) :: description
 
  315       description = 
'String detected' 
  316       write (iout, 
'(3x, a, ": ", a, " = ", a)') &
 
  317         trim(description), trim(varname), trim(p_mem)
 
  329     integer(I4B), 
dimension(:), 
contiguous, 
intent(in) :: p_mem
 
  330     character(len=*), 
intent(in) :: varname
 
  331     character(len=*), 
intent(in) :: mempath
 
  332     character(len=*), 
intent(in) :: shapestr
 
  333     integer(I4B), 
intent(in) :: iout
 
  334     integer(I4B), 
dimension(:), 
pointer, 
contiguous :: model_shape
 
  335     integer(I4B), 
dimension(:, :, :), 
pointer, 
contiguous :: int3d
 
  336     integer(I4B), 
dimension(:, :), 
pointer, 
contiguous :: int2d
 
  337     integer(I4B), 
dimension(3) :: dis3d_shape
 
  338     integer(I4B), 
dimension(2) :: dis2d_shape
 
  339     integer(I4B), 
pointer :: distype
 
  340     character(LENMEMPATH) :: input_mempath
 
  341     character(LENCOMPONENTNAME) :: comp, subcomp
 
  342     integer(I4B) :: i, j, k, inunit, export_dim
 
  343     logical(LGP) :: is_layered
 
  348     call mem_setptr(distype, 
'DISENUM', input_mempath)
 
  349     call mem_setptr(model_shape, 
'MODEL_SHAPE', input_mempath)
 
  355     select case (export_dim)
 
  358       dis3d_shape(1) = model_shape(3)
 
  359       dis3d_shape(2) = model_shape(2)
 
  360       dis3d_shape(3) = model_shape(1)
 
  362       allocate (int3d(dis3d_shape(1), dis3d_shape(2), dis3d_shape(3)))
 
  363       int3d = reshape(p_mem, dis3d_shape)
 
  365       do k = 1, dis3d_shape(3)
 
  367         do i = 1, model_shape(2)
 
  368           write (inunit, 
'(*(i0, " "))') (int3d(j, i, k), j=1, &
 
  377       dis2d_shape(1) = model_shape(2)
 
  378       dis2d_shape(2) = model_shape(1)
 
  380       allocate (int2d(dis2d_shape(1), dis2d_shape(2)))
 
  381       int2d = reshape(p_mem, dis2d_shape)
 
  384         do i = 1, dis2d_shape(2)
 
  386           write (inunit, 
'(*(i0, " "))') (int2d(j, i), j=1, dis2d_shape(1))
 
  392         do i = 1, dis2d_shape(2)
 
  393           write (inunit, 
'(*(i0, " "))') (int2d(j, i), j=1, dis2d_shape(1))
 
  402       write (inunit, 
'(*(i0, " "))') p_mem
 
  405       write (
errmsg, 
'(a,i0)') 
'EXPORT unsupported int1d export_dim=', &
 
  416     integer(I4B), 
dimension(:, :), 
contiguous, 
intent(in) :: p_mem
 
  417     character(len=*), 
intent(in) :: varname
 
  418     character(len=*), 
intent(in) :: mempath
 
  419     character(len=*), 
intent(in) :: shapestr
 
  420     integer(I4B), 
intent(in) :: iout
 
  421     integer(I4B), 
dimension(:), 
pointer, 
contiguous :: model_shape
 
  422     integer(I4B), 
pointer :: distype
 
  423     character(LENMEMPATH) :: input_mempath
 
  424     character(LENCOMPONENTNAME) :: comp, subcomp
 
  425     integer(I4B) :: i, j, inunit, export_dim
 
  426     logical(LGP) :: is_layered
 
  431     call mem_setptr(distype, 
'DISENUM', input_mempath)
 
  432     call mem_setptr(model_shape, 
'MODEL_SHAPE', input_mempath)
 
  437     select case (export_dim)
 
  441       do i = 1, 
size(p_mem, dim=2)
 
  442         write (inunit, 
'(*(i0, " "))') (p_mem(j, i), j=1, 
size(p_mem, dim=1))
 
  448         do i = 1, 
size(p_mem, dim=2)
 
  450           write (inunit, 
'(*(i0, " "))') (p_mem(j, i), j=1, 
size(p_mem, dim=1))
 
  456         do i = 1, 
size(p_mem, dim=2)
 
  457           write (inunit, 
'(*(i0, " "))') (p_mem(j, i), j=1, 
size(p_mem, dim=1))
 
  462       write (
errmsg, 
'(a,i0)') 
'EXPORT unsupported int2d export_dim=', &
 
  473     integer(I4B), 
dimension(:, :, :), 
contiguous, 
intent(in) :: p_mem
 
  474     character(len=*), 
intent(in) :: varname
 
  475     character(len=*), 
intent(in) :: mempath
 
  476     character(len=*), 
intent(in) :: shapestr
 
  477     integer(I4B), 
intent(in) :: iout
 
  478     integer(I4B), 
dimension(:), 
pointer, 
contiguous :: model_shape
 
  479     integer(I4B), 
pointer :: distype
 
  480     character(LENMEMPATH) :: input_mempath
 
  481     character(LENCOMPONENTNAME) :: comp, subcomp
 
  482     integer(I4B) :: i, j, k, inunit, export_dim
 
  483     logical(LGP) :: is_layered
 
  488     call mem_setptr(distype, 
'DISENUM', input_mempath)
 
  489     call mem_setptr(model_shape, 
'MODEL_SHAPE', input_mempath)
 
  494     select case (export_dim)
 
  497       do k = 1, 
size(p_mem, dim=3)
 
  499         do i = 1, 
size(p_mem, dim=2)
 
  500           write (inunit, 
'(*(i0, " "))') (p_mem(j, i, k), j=1, 
size(p_mem, dim=1))
 
  505       write (
errmsg, 
'(a,i0)') 
'EXPORT unsupported int3d export_dim=', &
 
  519     real(DP), 
dimension(:), 
contiguous, 
intent(in) :: p_mem
 
  520     character(len=*), 
intent(in) :: varname
 
  521     character(len=*), 
intent(in) :: mempath
 
  522     character(len=*), 
intent(in) :: shapestr
 
  523     integer(I4B), 
intent(in) :: iout
 
  524     integer(I4B), 
dimension(:), 
pointer, 
contiguous :: model_shape
 
  525     real(DP), 
dimension(:, :, :), 
pointer, 
contiguous :: dbl3d
 
  526     real(DP), 
dimension(:, :), 
pointer, 
contiguous :: dbl2d
 
  527     integer(I4B), 
dimension(3) :: dis3d_shape
 
  528     integer(I4B), 
dimension(2) :: dis2d_shape
 
  529     integer(I4B), 
pointer :: distype
 
  530     character(LENMEMPATH) :: input_mempath
 
  531     character(LENCOMPONENTNAME) :: comp, subcomp
 
  532     integer(I4B) :: i, j, k, inunit, export_dim
 
  533     logical(LGP) :: is_layered
 
  538     call mem_setptr(distype, 
'DISENUM', input_mempath)
 
  539     call mem_setptr(model_shape, 
'MODEL_SHAPE', input_mempath)
 
  545     select case (export_dim)
 
  548       dis3d_shape(1) = model_shape(3)
 
  549       dis3d_shape(2) = model_shape(2)
 
  551       dis3d_shape(3) = model_shape(1)
 
  552       allocate (dbl3d(dis3d_shape(1), dis3d_shape(2), dis3d_shape(3)))
 
  553       dbl3d = reshape(p_mem, dis3d_shape)
 
  554       do k = 1, dis3d_shape(3)
 
  557         do i = 1, model_shape(2)
 
  558           write (inunit, 
'(*(G0.10, " "))') (dbl3d(j, i, k), j=1, &
 
  567       dis2d_shape(1) = model_shape(2)
 
  568       dis2d_shape(2) = model_shape(1)
 
  570       allocate (dbl2d(dis2d_shape(1), dis2d_shape(2)))
 
  571       dbl2d = reshape(p_mem, dis2d_shape)
 
  574         do i = 1, dis2d_shape(2)
 
  576           write (inunit, 
'(*(G0.10, " "))') (dbl2d(j, i), j=1, dis2d_shape(1))
 
  582         do i = 1, dis2d_shape(2)
 
  583           write (inunit, 
'(*(G0.10, " "))') (dbl2d(j, i), j=1, dis2d_shape(1))
 
  592       write (inunit, 
'(*(G0.10, " "))') p_mem
 
  595       write (
errmsg, 
'(a,i0)') 
'EXPORT unsupported dbl1d export_dim=', &
 
  606     real(DP), 
dimension(:, :), 
contiguous, 
intent(in) :: p_mem
 
  607     character(len=*), 
intent(in) :: varname
 
  608     character(len=*), 
intent(in) :: mempath
 
  609     character(len=*), 
intent(in) :: shapestr
 
  610     integer(I4B), 
intent(in) :: iout
 
  611     integer(I4B), 
dimension(:), 
pointer, 
contiguous :: model_shape
 
  612     integer(I4B), 
pointer :: distype
 
  613     character(LENMEMPATH) :: input_mempath
 
  614     character(LENCOMPONENTNAME) :: comp, subcomp
 
  615     integer(I4B) :: i, j, inunit, export_dim
 
  616     logical(LGP) :: is_layered
 
  621     call mem_setptr(distype, 
'DISENUM', input_mempath)
 
  622     call mem_setptr(model_shape, 
'MODEL_SHAPE', input_mempath)
 
  627     select case (export_dim)
 
  631       do i = 1, 
size(p_mem, dim=2)
 
  632         write (inunit, 
'(*(G0.10, " "))') (p_mem(j, i), j=1, 
size(p_mem, dim=1))
 
  638         do i = 1, 
size(p_mem, dim=2)
 
  640           write (inunit, 
'(*(G0.10, " "))') (p_mem(j, i), j=1, 
size(p_mem, dim=1))
 
  646         do i = 1, 
size(p_mem, dim=2)
 
  647           write (inunit, 
'(*(G0.10, " "))') (p_mem(j, i), j=1, 
size(p_mem, dim=1))
 
  652       write (
errmsg, 
'(a,i0)') 
'EXPORT unsupported dbl2d export_dim=', &
 
  663     real(DP), 
dimension(:, :, :), 
contiguous, 
intent(in) :: p_mem
 
  664     character(len=*), 
intent(in) :: varname
 
  665     character(len=*), 
intent(in) :: mempath
 
  666     character(len=*), 
intent(in) :: shapestr
 
  667     integer(I4B), 
intent(in) :: iout
 
  668     integer(I4B), 
dimension(:), 
pointer, 
contiguous :: model_shape
 
  669     integer(I4B), 
pointer :: distype
 
  670     character(LENMEMPATH) :: input_mempath
 
  671     character(LENCOMPONENTNAME) :: comp, subcomp
 
  672     integer(I4B) :: i, j, k, inunit, export_dim
 
  673     logical(LGP) :: is_layered
 
  678     call mem_setptr(distype, 
'DISENUM', input_mempath)
 
  679     call mem_setptr(model_shape, 
'MODEL_SHAPE', input_mempath)
 
  684     select case (export_dim)
 
  687       do k = 1, 
size(p_mem, dim=3)
 
  689         do i = 1, 
size(p_mem, dim=2)
 
  690           write (inunit, 
'(*(G0.10, " "))') (p_mem(j, i, k), j=1, &
 
  696       write (
errmsg, 
'(a,i0)') 
'EXPORT unsupported dbl3d export_dim=', &
 
  708     integer(I4B), 
pointer, 
intent(in) :: distype
 
  709     character(len=*), 
intent(in) :: shapestr
 
  710     logical(LGP), 
intent(inout) :: is_layered
 
  711     integer(I4B) :: export_dim
 
  716     select case (distype)
 
  718       if (shapestr == 
'NODES') 
then 
  721       else if (shapestr == 
'NCOL NROW NLAY') 
then 
  728       if (shapestr == 
'NODES') 
then 
  731       else if (shapestr == 
'NCPL NLAY') 
then 
  738       if (shapestr == 
'NODES') 
then 
  740       else if (shapestr == 
'NCOL NROW') 
then 
  766     character(len=*), 
intent(in) :: varname
 
  767     character(len=*), 
intent(in) :: mempath
 
  768     integer(I4B), 
intent(in) :: layer
 
  769     integer(I4B), 
intent(in) :: iout
 
  770     integer(I4B) :: inunit
 
  771     character(len=LENCOMPONENTNAME) :: comp, subcomp
 
  772     character(len=LINELENGTH) :: filename, suffix
 
  783       write (suffix, 
'(a,i0)') trim(suffix)//
'.l', layer
 
  785     suffix = trim(suffix)//
'.txt' 
  788     filename = trim(comp)//
'-'//trim(subcomp)//
'.'//trim(suffix)
 
  792     call openfile(inunit, 0, filename, 
'EXPORT', filstat_opt=
'REPLACE')
 
This module contains simulation constants.
integer(i4b), parameter linelength
maximum length of a standard line
integer(i4b), parameter lencomponentname
maximum length of a component name
@ disu
DISV6 discretization.
@ dis
DIS6 discretization.
@ disv1d
DISV1D6 discretization.
@ dis2d
DIS2D6 discretization.
@ disv
DISU6 discretization.
@ disundef
undefined discretization
integer(i4b), parameter lenvarname
maximum length of a variable name
integer(i4b), parameter lenmempath
maximum length of the memory path
This module contains the Input Data Model Logger Module.
subroutine idm_log_var_str(p_mem, varname, mempath, iout)
Log type specific information str.
integer(i4b) function create_export_file(varname, mempath, layer, iout)
Create export file.
subroutine idm_log_var_int(p_mem, varname, mempath, datatype, iout)
Log type specific information integer.
integer(i4b) function distype_export_dim(distype, shapestr, is_layered)
Set dis type export_dim.
subroutine idm_export_int2d(p_mem, varname, mempath, shapestr, iout)
Create export file int2d.
subroutine, public idm_log_close(component, subcomponent, iout)
@ brief log the closing message
subroutine idm_export_dbl2d(p_mem, varname, mempath, shapestr, iout)
Create export file dbl2d.
subroutine, public idm_log_period_header(component, iout)
@ brief log a dynamic header message
subroutine idm_log_var_dbl3d(p_mem, varname, mempath, iout)
Log type specific information dbl3d.
subroutine idm_export_int3d(p_mem, varname, mempath, shapestr, iout)
Create export file int3d.
subroutine, public idm_log_header(component, subcomponent, iout)
@ brief log a header message
subroutine idm_log_var_dbl2d(p_mem, varname, mempath, iout)
Log type specific information dbl2d.
subroutine idm_log_var_ts(varname, mempath, iout, is_tas)
@ brief log the period closing message
subroutine idm_export_dbl3d(p_mem, varname, mempath, shapestr, iout)
Create export file dbl3d.
subroutine idm_log_var_int1d(p_mem, varname, mempath, iout)
Log type specific information int1d.
subroutine, public idm_log_period_close(iout)
@ brief log the period closing message
subroutine idm_log_var_dbl(p_mem, varname, mempath, iout)
Log type specific information double.
subroutine idm_log_var_dbl1d(p_mem, varname, mempath, iout)
Log type specific information dbl1d.
subroutine idm_log_var_int2d(p_mem, varname, mempath, iout)
Log type specific information int2d.
subroutine idm_log_var_int3d(p_mem, varname, mempath, iout)
Log type specific information int3d.
subroutine idm_log_var_logical(p_mem, varname, mempath, iout)
Log type specific information logical.
subroutine idm_export_dbl1d(p_mem, varname, mempath, shapestr, iout)
Create export file dbl1d.
subroutine idm_export_int1d(p_mem, varname, mempath, shapestr, iout)
Create export file int1d.
This module defines variable data types.
character(len=lenmempath) function create_mem_path(component, subcomponent, context)
returns the path to the memory object
subroutine split_mem_path(mem_path, component, subcomponent)
Split the memory path into component(s)
This module contains simulation methods.
subroutine, public store_error(msg, terminate)
Store an error message.
This module contains simulation variables.
character(len=maxcharlen) errmsg
error message string
character(len=linelength) idm_context
integer(i4b) iparamlog
input (idm) parameter logging to simulation listing file
integer(i4b), pointer, public kstp
current time step number
integer(i4b), pointer, public kper
current stress period number