MODFLOW 6  version 6.7.0.dev1
USGS Modular Hydrologic Model
FlowModelInterface.f90
Go to the documentation of this file.
2 
3  use kindmodule, only: dp, i4b, lgp
7  use simvariablesmodule, only: errmsg
9  use basedismodule, only: disbasetype
10  use listmodule, only: listtype
16 
17  implicit none
18  private
19  public :: flowmodelinterfacetype
20 
22 
23  character(len=LENPACKAGENAME) :: text = '' !< text string for package
24  logical, pointer :: flows_from_file => null() !< if .false., then flows come from GWF through GWF-Model exg
25  type(listtype), pointer :: gwfbndlist => null() !< list of gwf stress packages
26  integer(I4B), pointer :: iflowsupdated => null() !< flows were updated for this time step
27  integer(I4B), dimension(:), pointer, contiguous :: ibound => null() !< pointer to this model ibound
28  real(dp), dimension(:), pointer, contiguous :: gwfflowja => null() !< pointer to the GWF flowja array
29  real(dp), dimension(:, :), pointer, contiguous :: gwfspdis => null() !< pointer to npf specific discharge array
30  real(dp), dimension(:), pointer, contiguous :: gwfhead => null() !< pointer to the GWF head array
31  real(dp), dimension(:), pointer, contiguous :: gwfsat => null() !< pointer to the GWF saturation array
32  integer(I4B), dimension(:), pointer, contiguous :: ibdgwfsat0 => null() !< mark cells with saturation = 0 to exclude from dispersion
33  integer(I4B), pointer :: idryinactive => null() !< mark cells with an additional flag to exclude from deactivation (gwe will simulate conduction through dry cells)
34  real(dp), dimension(:), pointer, contiguous :: gwfstrgss => null() !< pointer to flow model QSTOSS
35  real(dp), dimension(:), pointer, contiguous :: gwfstrgsy => null() !< pointer to flow model QSTOSY
36  integer(I4B), pointer :: igwfstrgss => null() !< indicates if gwfstrgss is available
37  integer(I4B), pointer :: igwfstrgsy => null() !< indicates if gwfstrgsy is available
38  integer(I4B), pointer :: iubud => null() !< unit number GWF budget file
39  integer(I4B), pointer :: iuhds => null() !< unit number GWF head file
40  integer(I4B), pointer :: iumvr => null() !< unit number GWF mover budget file
41  integer(I4B), pointer :: iugrb => null() !< unit number binary grid file
42  integer(I4B), pointer :: nflowpack => null() !< number of GWF flow packages
43  integer(I4B), dimension(:), pointer, contiguous :: igwfmvrterm => null() !< flag to indicate that gwf package is a mover term
44  type(budgetfilereadertype) :: bfr !< budget file reader
45  type(headfilereadertype) :: hfr !< head file reader
46  type(gridfilereadertype) :: gfr !< grid file reader
47  type(packagebudgettype), dimension(:), allocatable :: gwfpackages !< used to get flows between a package and gwf
48  type(budgetobjecttype), pointer :: mvrbudobj => null() !< pointer to the mover budget object
49  character(len=16), dimension(:), allocatable :: flowpacknamearray !< array of boundary package names (e.g. LAK-1, SFR-3, etc.)
50  character(len=LENVARNAME) :: depvartype = ''
51 
52  contains
53 
54  procedure :: advance_bfr
55  procedure :: advance_hfr
56  procedure :: allocate_arrays
57  procedure :: allocate_gwfpackages
58  procedure :: allocate_scalars
60  procedure :: finalize_bfr
61  procedure :: finalize_hfr
62  procedure :: fmi_ar
63  procedure :: fmi_da
64  procedure :: fmi_df
65  procedure :: get_package_index
66  procedure :: initialize_bfr
69  procedure :: initialize_hfr
70  procedure :: read_options
71  procedure :: read_packagedata
72 
73  end type flowmodelinterfacetype
74 
75 contains
76 
77  !> @brief Define the flow model interface
78  !<
79  subroutine fmi_df(this, dis, idryinactive)
80  ! -- modules
81  use simmodule, only: store_error
82  ! -- dummy
83  class(flowmodelinterfacetype) :: this
84  class(disbasetype), pointer, intent(in) :: dis
85  integer(I4B), intent(in) :: idryinactive
86  ! -- formats
87  character(len=*), parameter :: fmtfmi = &
88  "(1x,/1x,'FMI -- FLOW MODEL INTERFACE, VERSION 2, 8/17/2023', &
89  &' INPUT READ FROM UNIT ', i0, //)"
90  character(len=*), parameter :: fmtfmi0 = &
91  "(1x,/1x,'FMI -- FLOW MODEL INTERFACE,'&
92  &' VERSION 2, 8/17/2023')"
93  !
94  ! --print a message identifying the FMI package.
95  if (this%iout > 0) then
96  if (this%inunit /= 0) then
97  write (this%iout, fmtfmi) this%inunit
98  else
99  write (this%iout, fmtfmi0)
100  if (this%flows_from_file) then
101  write (this%iout, '(a)') ' FLOWS ARE ASSUMED TO BE ZERO.'
102  else
103  write (this%iout, '(a)') ' FLOWS PROVIDED BY A GWF MODEL IN THIS &
104  &SIMULATION'
105  end if
106  end if
107  end if
108  !
109  ! -- Store pointers
110  this%dis => dis
111  !
112  ! -- Read fmi options
113  if (this%inunit /= 0) then
114  call this%read_options()
115  end if
116  !
117  ! -- Read packagedata options
118  if (this%inunit /= 0 .and. this%flows_from_file) then
119  call this%read_packagedata()
120  call this%initialize_gwfterms_from_bfr()
121  end if
122  !
123  ! -- If GWF-Model exchange is active, setup flow terms
124  if (.not. this%flows_from_file) then
125  call this%initialize_gwfterms_from_gwfbndlist()
126  end if
127  !
128  ! -- Set flag that stops dry flows from being deactivated in a GWE
129  ! transport model since conduction will still be simulated.
130  ! 0: GWE (skip deactivation step); 1: GWT (default: use existing code)
131  this%idryinactive = idryinactive
132  end subroutine fmi_df
133 
134  !> @brief Allocate the package
135  !<
136  subroutine fmi_ar(this, ibound)
137  ! -- modules
138  use simmodule, only: store_error
139  ! -- dummy
140  class(flowmodelinterfacetype) :: this
141  integer(I4B), dimension(:), pointer, contiguous :: ibound
142  !
143  ! -- store pointers to arguments that were passed in
144  this%ibound => ibound
145  !
146  ! -- Allocate arrays
147  call this%allocate_arrays(this%dis%nodes)
148  end subroutine fmi_ar
149 
150  !> @brief Deallocate variables
151  !<
152  subroutine fmi_da(this)
153  ! -- modules
155  ! -- dummy
156  class(flowmodelinterfacetype) :: this
157  ! -- todo: finalize hfr and bfr either here or in a finalize routine
158  !
159  ! -- deallocate any memory stored with gwfpackages
160  call this%deallocate_gwfpackages()
161  !
162  ! -- deallocate fmi arrays
163  deallocate (this%gwfpackages)
164  deallocate (this%flowpacknamearray)
165  call mem_deallocate(this%igwfmvrterm)
166  call mem_deallocate(this%ibdgwfsat0)
167  !
168  if (this%flows_from_file) then
169  call mem_deallocate(this%gwfstrgss)
170  call mem_deallocate(this%gwfstrgsy)
171  end if
172  !
173  ! -- special treatment, these could be from mem_checkin
174  call mem_deallocate(this%gwfhead, 'GWFHEAD', this%memoryPath)
175  call mem_deallocate(this%gwfsat, 'GWFSAT', this%memoryPath)
176  call mem_deallocate(this%gwfspdis, 'GWFSPDIS', this%memoryPath)
177  call mem_deallocate(this%gwfflowja, 'GWFFLOWJA', this%memoryPath)
178  !
179  ! -- deallocate scalars
180  call mem_deallocate(this%flows_from_file)
181  call mem_deallocate(this%iflowsupdated)
182  call mem_deallocate(this%igwfstrgss)
183  call mem_deallocate(this%igwfstrgsy)
184  call mem_deallocate(this%iubud)
185  call mem_deallocate(this%iuhds)
186  call mem_deallocate(this%iumvr)
187  call mem_deallocate(this%iugrb)
188  call mem_deallocate(this%nflowpack)
189  call mem_deallocate(this%idryinactive)
190  !
191  ! -- deallocate parent
192  call this%NumericalPackageType%da()
193  end subroutine fmi_da
194 
195  !> @brief Allocate scalars
196  !<
197  subroutine allocate_scalars(this)
198  ! -- modules
200  ! -- dummy
201  class(flowmodelinterfacetype) :: this
202  ! -- local
203  !
204  ! -- allocate scalars in NumericalPackageType
205  call this%NumericalPackageType%allocate_scalars()
206  !
207  ! -- Allocate
208  call mem_allocate(this%flows_from_file, 'FLOWS_FROM_FILE', this%memoryPath)
209  call mem_allocate(this%iflowsupdated, 'IFLOWSUPDATED', this%memoryPath)
210  call mem_allocate(this%igwfstrgss, 'IGWFSTRGSS', this%memoryPath)
211  call mem_allocate(this%igwfstrgsy, 'IGWFSTRGSY', this%memoryPath)
212  call mem_allocate(this%iubud, 'IUBUD', this%memoryPath)
213  call mem_allocate(this%iuhds, 'IUHDS', this%memoryPath)
214  call mem_allocate(this%iumvr, 'IUMVR', this%memoryPath)
215  call mem_allocate(this%iugrb, 'IUGRB', this%memoryPath)
216  call mem_allocate(this%nflowpack, 'NFLOWPACK', this%memoryPath)
217  call mem_allocate(this%idryinactive, "IDRYINACTIVE", this%memoryPath)
218  !
219  ! !
220  ! -- Initialize
221  this%flows_from_file = .true.
222  this%iflowsupdated = 1
223  this%igwfstrgss = 0
224  this%igwfstrgsy = 0
225  this%iubud = 0
226  this%iuhds = 0
227  this%iumvr = 0
228  this%iugrb = 0
229  this%nflowpack = 0
230  this%idryinactive = 1
231  end subroutine allocate_scalars
232 
233  !> @brief Allocate arrays
234  !<
235  subroutine allocate_arrays(this, nodes)
237  !modules
238  use constantsmodule, only: dzero
239  ! -- dummy
240  class(flowmodelinterfacetype) :: this
241  integer(I4B), intent(in) :: nodes
242  ! -- local
243  integer(I4B) :: n
244  !
245  ! -- Allocate ibdgwfsat0, which is an indicator array marking cells with
246  ! saturation greater than 0.0 with a value of 1
247  call mem_allocate(this%ibdgwfsat0, nodes, 'IBDGWFSAT0', this%memoryPath)
248  do n = 1, nodes
249  this%ibdgwfsat0(n) = 1
250  end do
251  !
252  ! -- Allocate differently depending on whether or not flows are
253  ! being read from a file.
254  if (this%flows_from_file) then
255  call mem_allocate(this%gwfflowja, this%dis%con%nja, &
256  'GWFFLOWJA', this%memoryPath)
257  call mem_allocate(this%gwfsat, nodes, 'GWFSAT', this%memoryPath)
258  call mem_allocate(this%gwfhead, nodes, 'GWFHEAD', this%memoryPath)
259  call mem_allocate(this%gwfspdis, 3, nodes, 'GWFSPDIS', this%memoryPath)
260  do n = 1, nodes
261  this%gwfsat(n) = done
262  this%gwfhead(n) = dzero
263  this%gwfspdis(:, n) = dzero
264  end do
265  do n = 1, size(this%gwfflowja)
266  this%gwfflowja(n) = dzero
267  end do
268  !
269  ! -- allocate and initialize storage arrays
270  if (this%igwfstrgss == 0) then
271  call mem_allocate(this%gwfstrgss, 1, 'GWFSTRGSS', this%memoryPath)
272  else
273  call mem_allocate(this%gwfstrgss, nodes, 'GWFSTRGSS', this%memoryPath)
274  end if
275  if (this%igwfstrgsy == 0) then
276  call mem_allocate(this%gwfstrgsy, 1, 'GWFSTRGSY', this%memoryPath)
277  else
278  call mem_allocate(this%gwfstrgsy, nodes, 'GWFSTRGSY', this%memoryPath)
279  end if
280  do n = 1, size(this%gwfstrgss)
281  this%gwfstrgss(n) = dzero
282  end do
283  do n = 1, size(this%gwfstrgsy)
284  this%gwfstrgsy(n) = dzero
285  end do
286  !
287  ! -- If there is no fmi package, then there are no flows at all or a
288  ! connected GWF model, so allocate gwfpackages to zero
289  if (this%inunit == 0) call this%allocate_gwfpackages(this%nflowpack)
290  end if
291  end subroutine allocate_arrays
292 
293  !> @brief Read options from input file
294  !<
295  subroutine read_options(this)
296  ! -- modules
297  use constantsmodule, only: linelength, dem6
300  ! -- dummy
301  class(flowmodelinterfacetype) :: this
302  ! -- local
303  character(len=LINELENGTH) :: keyword
304  integer(I4B) :: ierr
305  logical :: isfound, endOfBlock
306  !
307  ! -- get options block
308  call this%parser%GetBlock('OPTIONS', isfound, ierr, blockrequired=.false., &
309  supportopenclose=.true.)
310  !
311  ! -- parse options block if detected
312  if (isfound) then
313  write (this%iout, '(1x,a)') 'PROCESSING FMI OPTIONS'
314  do
315  call this%parser%GetNextLine(endofblock)
316  if (endofblock) exit
317  call this%parser%GetStringCaps(keyword)
318  select case (keyword)
319  case ('SAVE_FLOWS')
320  this%ipakcb = -1
321  case default
322  write (errmsg, '(a,3(1x,a))') &
323  'UNKNOWN', trim(adjustl(this%text)), 'OPTION:', trim(keyword)
324  call store_error(errmsg)
325  call this%parser%StoreErrorUnit()
326  end select
327  end do
328  write (this%iout, '(1x,a)') 'END OF FMI OPTIONS'
329  end if
330  end subroutine read_options
331 
332  !> @brief Read packagedata block from input file
333  !<
334  subroutine read_packagedata(this)
335  ! -- modules
336  use openspecmodule, only: access, form
340  use dismodule, only: distype
341  use disvmodule, only: disvtype
342  use disumodule, only: disutype
343  use dis2dmodule, only: dis2dtype
344  use disv2dmodule, only: disv2dtype
345  use disv1dmodule, only: disv1dtype
346  ! -- dummy
347  class(flowmodelinterfacetype) :: this
348  ! -- local
349  character(len=LINELENGTH) :: keyword, fname
350  integer(I4B) :: ierr
351  integer(I4B) :: inunit
352  integer(I4B) :: iapt
353  integer(I4B) :: nodes
354  logical :: isfound, endOfBlock
355  logical :: blockrequired
356  logical :: exist
357  integer(I4B), allocatable :: idomain1d(:), idomain2d(:, :), idomain3d(:, :, :)
358  ! -- formats
359  character(len=*), parameter :: fmtdiserr = &
360  "('Models do not have the same discretization&
361  & ',a,'.&
362  & GWF model has ', i0, ' user nodes and ', i0, ' reduced nodes.&
363  & This model has ', i0, ' user nodes and ', i0, ' reduced nodes.&
364  & Ensure discretization packages, including IDOMAIN, are identical.')"
365  character(len=*), parameter :: fmtidomerr = &
366  "('Models do not have the same discretization&
367  & ',a,'.&
368  & Models have different IDOMAIN arrays.&
369  & Ensure discretization packages, including IDOMAIN, are identical.')"
370  !
371  ! -- initialize
372  iapt = 0
373  blockrequired = .true.
374  !
375  ! -- get packagedata block
376  call this%parser%GetBlock('PACKAGEDATA', isfound, ierr, &
377  blockrequired=blockrequired, &
378  supportopenclose=.true.)
379  !
380  ! -- parse packagedata block if detected
381  if (isfound) then
382  write (this%iout, '(1x,a)') 'PROCESSING FMI PACKAGEDATA'
383  do
384  call this%parser%GetNextLine(endofblock)
385  if (endofblock) exit
386  call this%parser%GetStringCaps(keyword)
387  select case (keyword)
388  case ('GWFBUDGET')
389  call this%parser%GetStringCaps(keyword)
390  if (keyword /= 'FILEIN') then
391  call store_error('GWFBUDGET KEYWORD MUST BE FOLLOWED BY '// &
392  '"FILEIN" then by filename.')
393  call this%parser%StoreErrorUnit()
394  end if
395  call this%parser%GetString(fname)
396  inunit = getunit()
397  inquire (file=trim(fname), exist=exist)
398  if (.not. exist) then
399  call store_error('Could not find file '//trim(fname))
400  call this%parser%StoreErrorUnit()
401  end if
402  call openfile(inunit, this%iout, fname, 'DATA(BINARY)', form, &
403  access, 'UNKNOWN')
404  this%iubud = inunit
405  call this%initialize_bfr()
406  case ('GWFHEAD')
407  call this%parser%GetStringCaps(keyword)
408  if (keyword /= 'FILEIN') then
409  call store_error('GWFHEAD KEYWORD MUST BE FOLLOWED BY '// &
410  '"FILEIN" then by filename.')
411  call this%parser%StoreErrorUnit()
412  end if
413  call this%parser%GetString(fname)
414  inquire (file=trim(fname), exist=exist)
415  if (.not. exist) then
416  call store_error('Could not find file '//trim(fname))
417  call this%parser%StoreErrorUnit()
418  end if
419  inunit = getunit()
420  call openfile(inunit, this%iout, fname, 'DATA(BINARY)', form, &
421  access, 'UNKNOWN')
422  this%iuhds = inunit
423  call this%initialize_hfr()
424  case ('GWFMOVER')
425  call this%parser%GetStringCaps(keyword)
426  if (keyword /= 'FILEIN') then
427  call store_error('GWFMOVER KEYWORD MUST BE FOLLOWED BY '// &
428  '"FILEIN" then by filename.')
429  call this%parser%StoreErrorUnit()
430  end if
431  call this%parser%GetString(fname)
432  inunit = getunit()
433  call openfile(inunit, this%iout, fname, 'DATA(BINARY)', form, &
434  access, 'UNKNOWN')
435  this%iumvr = inunit
436  call budgetobject_cr_bfr(this%mvrbudobj, 'MVT', this%iumvr, &
437  this%iout)
438  call this%mvrbudobj%fill_from_bfr(this%dis, this%iout)
439  case ('GWFGRID')
440  call this%parser%GetStringCaps(keyword)
441  if (keyword /= 'FILEIN') then
442  call store_error('GWFGRID KEYWORD MUST BE FOLLOWED BY '// &
443  '"FILEIN" then by filename.')
444  call this%parser%StoreErrorUnit()
445  end if
446  call this%parser%GetString(fname)
447  inunit = getunit()
448  call openfile(inunit, this%iout, fname, 'DATA(BINARY)', &
449  form, access, 'UNKNOWN')
450  this%iugrb = inunit
451  call this%gfr%initialize(this%iugrb)
452 
453  ! check grid equivalence
454  select case (this%gfr%grid_type)
455  case ('DIS')
456  select type (dis => this%dis)
457  type is (distype)
458  nodes = this%gfr%read_int("NCELLS")
459  if (nodes /= this%dis%nodes) then
460  write (errmsg, fmtdiserr) trim(this%text)
461  call store_error(errmsg, terminate=.true.)
462  end if
463  idomain1d = this%gfr%read_int_1d("IDOMAIN")
464  idomain3d = reshape(idomain1d, [ &
465  this%gfr%read_int("NCOL"), &
466  this%gfr%read_int("NROW"), &
467  this%gfr%read_int("NLAY") &
468  ])
469  if (.not. all(dis%idomain == idomain3d)) then
470  write (errmsg, fmtidomerr) trim(this%text)
471  call store_error(errmsg, terminate=.true.)
472  end if
473  end select
474  case ('DISV')
475  select type (dis => this%dis)
476  type is (disvtype)
477  nodes = this%gfr%read_int("NCELLS")
478  if (nodes /= this%dis%nodes) then
479  write (errmsg, fmtdiserr) trim(this%text)
480  call store_error(errmsg, terminate=.true.)
481  end if
482  idomain1d = this%gfr%read_int_1d("IDOMAIN")
483  idomain2d = reshape(idomain1d, [ &
484  this%gfr%read_int("NCPL"), &
485  this%gfr%read_int("NLAY") &
486  ])
487  if (.not. all(dis%idomain == idomain2d)) then
488  write (errmsg, fmtidomerr) trim(this%text)
489  call store_error(errmsg, terminate=.true.)
490  end if
491  end select
492  case ('DISU')
493  select type (dis => this%dis)
494  type is (disutype)
495  nodes = this%gfr%read_int("NODES")
496  if (nodes /= this%dis%nodes) then
497  write (errmsg, fmtdiserr) trim(this%text)
498  call store_error(errmsg, terminate=.true.)
499  end if
500  idomain1d = this%gfr%read_int_1d("IDOMAIN")
501  if (.not. all(dis%idomain == idomain1d)) then
502  write (errmsg, fmtidomerr) trim(this%text)
503  call store_error(errmsg, terminate=.true.)
504  end if
505  end select
506  case ('DIS2D')
507  select type (dis => this%dis)
508  type is (dis2dtype)
509  nodes = this%gfr%read_int("NCELLS")
510  if (nodes /= this%dis%nodes) then
511  write (errmsg, fmtdiserr) trim(this%text)
512  call store_error(errmsg, terminate=.true.)
513  end if
514  idomain1d = this%gfr%read_int_1d("IDOMAIN")
515  idomain2d = reshape(idomain1d, [ &
516  this%gfr%read_int("NCOL"), &
517  this%gfr%read_int("NROW") &
518  ])
519  if (.not. all(dis%idomain == idomain2d)) then
520  write (errmsg, fmtidomerr) trim(this%text)
521  call store_error(errmsg, terminate=.true.)
522  end if
523  end select
524  case ('DISV2D')
525  select type (dis => this%dis)
526  type is (disv2dtype)
527  nodes = this%gfr%read_int("NODES")
528  if (nodes /= this%dis%nodes) then
529  write (errmsg, fmtdiserr) trim(this%text)
530  call store_error(errmsg, terminate=.true.)
531  end if
532  idomain1d = this%gfr%read_int_1d("IDOMAIN")
533  if (.not. all(dis%idomain == idomain1d)) then
534  write (errmsg, fmtidomerr) trim(this%text)
535  call store_error(errmsg, terminate=.true.)
536  end if
537  end select
538  case ('DISV1D')
539  select type (dis => this%dis)
540  type is (disv1dtype)
541  nodes = this%gfr%read_int("NCELLS")
542  if (nodes /= this%dis%nodes) then
543  write (errmsg, fmtdiserr) trim(this%text)
544  call store_error(errmsg, terminate=.true.)
545  end if
546  idomain1d = this%gfr%read_int_1d("IDOMAIN")
547  if (.not. all(dis%idomain == idomain1d)) then
548  write (errmsg, fmtidomerr) trim(this%text)
549  call store_error(errmsg, terminate=.true.)
550  end if
551  end select
552  end select
553 
554  if (allocated(idomain3d)) deallocate (idomain3d)
555  if (allocated(idomain2d)) deallocate (idomain2d)
556  if (allocated(idomain1d)) deallocate (idomain1d)
557 
558  call this%gfr%finalize()
559  case default
560  write (errmsg, '(a,3(1x,a))') &
561  'UNKNOWN', trim(adjustl(this%text)), 'PACKAGEDATA:', trim(keyword)
562  call store_error(errmsg)
563  end select
564  end do
565  write (this%iout, '(1x,a)') 'END OF FMI PACKAGEDATA'
566  end if
567  end subroutine read_packagedata
568 
569  !> @brief Initialize the budget file reader
570  subroutine initialize_bfr(this)
571  class(flowmodelinterfacetype) :: this
572  integer(I4B) :: ncrbud
573  call this%bfr%initialize(this%iubud, this%iout, ncrbud)
574  ! todo: need to run through the budget terms
575  ! and do some checking
576  end subroutine initialize_bfr
577 
578  !> @brief Advance the budget file reader
579  !!
580  !! Advance the budget file reader by reading the next chunk
581  !! of information for the current time step and stress period.
582  !<
583  subroutine advance_bfr(this)
584  ! -- modules
585  use tdismodule, only: kstp, kper
586  ! -- dummy
587  class(flowmodelinterfacetype) :: this
588  ! -- local
589  logical :: success
590  integer(I4B) :: n
591  integer(I4B) :: ipos
592  integer(I4B) :: nu, nr
593  integer(I4B) :: ip, i
594  logical :: readnext
595  ! -- format
596  character(len=*), parameter :: fmtkstpkper = &
597  "(1x,/1x,'FMI READING BUDGET TERMS &
598  &FOR KSTP ', i0, ' KPER ', i0)"
599  character(len=*), parameter :: fmtbudkstpkper = &
600  "(1x,/1x, 'FMI SETTING BUDGET TERMS &
601  &FOR KSTP ', i0, ' AND KPER ', &
602  &i0, ' TO BUDGET FILE TERMS FROM &
603  &KSTP ', i0, ' AND KPER ', i0)"
604  !
605  ! -- If the latest record read from the budget file is from a stress
606  ! -- period with only one time step, reuse that record (do not read a
607  ! -- new record) if the running model is still in that same stress period,
608  ! -- or if that record is the last one in the budget file.
609  readnext = .true.
610  if (kstp * kper > 1) then
611  if (this%bfr%kstp == 1) then
612  if (this%bfr%kpernext == kper + 1) then
613  readnext = .false.
614  else if (this%bfr%endoffile) then
615  readnext = .false.
616  end if
617  else if (this%bfr%endoffile) then
618  write (errmsg, '(4x,a)') 'REACHED END OF GWF BUDGET &
619  &FILE BEFORE READING SUFFICIENT BUDGET INFORMATION FOR THIS &
620  &GWT SIMULATION.'
621  call store_error(errmsg)
622  call store_error_unit(this%iubud)
623  end if
624  end if
625  !
626  ! -- Read the next record
627  if (readnext) then
628  !
629  ! -- Write the current time step and stress period
630  write (this%iout, fmtkstpkper) kstp, kper
631  !
632  ! -- loop through the budget terms for this stress period
633  ! i is the counter for gwf flow packages
634  ip = 1
635  do n = 1, this%bfr%nbudterms
636  call this%bfr%read_record(success, this%iout)
637  if (.not. success) then
638  write (errmsg, '(4x,a)') 'GWF BUDGET READ NOT SUCCESSFUL'
639  call store_error(errmsg)
640  call store_error_unit(this%iubud)
641  end if
642  !
643  ! -- Ensure kper is same between model and budget file
644  if (kper /= this%bfr%kper) then
645  write (errmsg, '(4x,a)') 'PERIOD NUMBER IN BUDGET FILE &
646  &DOES NOT MATCH PERIOD NUMBER IN TRANSPORT MODEL. IF THERE &
647  &IS MORE THAN ONE TIME STEP IN THE BUDGET FILE FOR A GIVEN &
648  &STRESS PERIOD, BUDGET FILE TIME STEPS MUST MATCH GWT MODEL &
649  &TIME STEPS ONE-FOR-ONE IN THAT STRESS PERIOD.'
650  call store_error(errmsg)
651  call store_error_unit(this%iubud)
652  end if
653  !
654  ! -- if budget file kstp > 1, then kstp must match
655  if (this%bfr%kstp > 1 .and. (kstp /= this%bfr%kstp)) then
656  write (errmsg, '(4x,a)') 'TIME STEP NUMBER IN BUDGET FILE &
657  &DOES NOT MATCH TIME STEP NUMBER IN TRANSPORT MODEL. IF THERE &
658  &IS MORE THAN ONE TIME STEP IN THE BUDGET FILE FOR A GIVEN STRESS &
659  &PERIOD, BUDGET FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
660  &ONE-FOR-ONE IN THAT STRESS PERIOD.'
661  call store_error(errmsg)
662  call store_error_unit(this%iubud)
663  end if
664  !
665  ! -- parse based on the type of data, and compress all user node
666  ! numbers into reduced node numbers
667  select case (trim(adjustl(this%bfr%budtxt)))
668  case ('FLOW-JA-FACE')
669  !
670  ! -- bfr%flowja contains only reduced connections so there is
671  ! a one-to-one match with this%gwfflowja
672  do ipos = 1, size(this%bfr%flowja)
673  this%gwfflowja(ipos) = this%bfr%flowja(ipos)
674  end do
675  case ('DATA-SPDIS')
676  do i = 1, this%bfr%nlist
677  nu = this%bfr%nodesrc(i)
678  nr = this%dis%get_nodenumber(nu, 0)
679  if (nr <= 0) cycle
680  this%gwfspdis(1, nr) = this%bfr%auxvar(1, i)
681  this%gwfspdis(2, nr) = this%bfr%auxvar(2, i)
682  this%gwfspdis(3, nr) = this%bfr%auxvar(3, i)
683  end do
684  case ('DATA-SAT')
685  do i = 1, this%bfr%nlist
686  nu = this%bfr%nodesrc(i)
687  nr = this%dis%get_nodenumber(nu, 0)
688  if (nr <= 0) cycle
689  this%gwfsat(nr) = this%bfr%auxvar(1, i)
690  end do
691  case ('STO-SS')
692  do nu = 1, this%dis%nodesuser
693  nr = this%dis%get_nodenumber(nu, 0)
694  if (nr <= 0) cycle
695  this%gwfstrgss(nr) = this%bfr%flow(nu)
696  end do
697  case ('STO-SY')
698  do nu = 1, this%dis%nodesuser
699  nr = this%dis%get_nodenumber(nu, 0)
700  if (nr <= 0) cycle
701  this%gwfstrgsy(nr) = this%bfr%flow(nu)
702  end do
703  case default
704  call this%gwfpackages(ip)%copy_values( &
705  this%bfr%nlist, &
706  this%bfr%nodesrc, &
707  this%bfr%flow, &
708  this%bfr%auxvar)
709  do i = 1, this%gwfpackages(ip)%nbound
710  nu = this%gwfpackages(ip)%nodelist(i)
711  nr = this%dis%get_nodenumber(nu, 0)
712  this%gwfpackages(ip)%nodelist(i) = nr
713  end do
714  ip = ip + 1
715  end select
716  end do
717  else
718  !
719  ! -- write message to indicate that flows are being reused
720  write (this%iout, fmtbudkstpkper) kstp, kper, this%bfr%kstp, this%bfr%kper
721  !
722  ! -- set the flag to indicate that flows were not updated
723  this%iflowsupdated = 0
724  end if
725  end subroutine advance_bfr
726 
727  !> @brief Finalize the budget file reader
728  subroutine finalize_bfr(this)
729  class(flowmodelinterfacetype) :: this
730  call this%bfr%finalize()
731  end subroutine finalize_bfr
732 
733  !> @brief Initialize the head file reader
734  subroutine initialize_hfr(this)
735  class(flowmodelinterfacetype) :: this
736  call this%hfr%initialize(this%iuhds, this%iout)
737  ! todo: need to run through the head terms
738  ! and do some checking
739  end subroutine initialize_hfr
740 
741  !> @brief Advance the head file reader
742  subroutine advance_hfr(this)
743  ! modules
744  use tdismodule, only: kstp, kper
745  class(flowmodelinterfacetype) :: this
746  integer(I4B) :: nu, nr, i, ilay
747  integer(I4B) :: ncpl
748  real(DP) :: val
749  logical :: readnext
750  logical :: success
751  character(len=*), parameter :: fmtkstpkper = &
752  "(1x,/1x,'FMI READING HEAD FOR &
753  &KSTP ', i0, ' KPER ', i0)"
754  character(len=*), parameter :: fmthdskstpkper = &
755  "(1x,/1x, 'FMI SETTING HEAD FOR KSTP ', i0, ' AND KPER ', &
756  &i0, ' TO BINARY FILE HEADS FROM KSTP ', i0, ' AND KPER ', i0)"
757  !
758  ! -- If the latest record read from the head file is from a stress
759  ! -- period with only one time step, reuse that record (do not read a
760  ! -- new record) if the running model is still in that same stress period,
761  ! -- or if that record is the last one in the head file.
762  readnext = .true.
763  if (kstp * kper > 1) then
764  if (this%hfr%kstp == 1) then
765  if (this%hfr%kpernext == kper + 1) then
766  readnext = .false.
767  else if (this%hfr%endoffile) then
768  readnext = .false.
769  end if
770  else if (this%hfr%endoffile) then
771  write (errmsg, '(4x,a)') 'REACHED END OF GWF HEAD &
772  &FILE BEFORE READING SUFFICIENT HEAD INFORMATION FOR THIS &
773  &GWT SIMULATION.'
774  call store_error(errmsg)
775  call store_error_unit(this%iuhds)
776  end if
777  end if
778  !
779  ! -- Read the next record
780  if (readnext) then
781  !
782  ! -- write to list file that heads are being read
783  write (this%iout, fmtkstpkper) kstp, kper
784  !
785  ! -- loop through the layered heads for this time step
786  do ilay = 1, this%hfr%nlay
787  !
788  ! -- read next head chunk
789  call this%hfr%read_record(success, this%iout)
790  if (.not. success) then
791  write (errmsg, '(4x,a)') 'GWF HEAD READ NOT SUCCESSFUL'
792  call store_error(errmsg)
793  call store_error_unit(this%iuhds)
794  end if
795  !
796  ! -- Ensure kper is same between model and head file
797  if (kper /= this%hfr%kper) then
798  write (errmsg, '(4x,a)') 'PERIOD NUMBER IN HEAD FILE &
799  &DOES NOT MATCH PERIOD NUMBER IN TRANSPORT MODEL. IF THERE &
800  &IS MORE THAN ONE TIME STEP IN THE HEAD FILE FOR A GIVEN STRESS &
801  &PERIOD, HEAD FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
802  &ONE-FOR-ONE IN THAT STRESS PERIOD.'
803  call store_error(errmsg)
804  call store_error_unit(this%iuhds)
805  end if
806  !
807  ! -- if head file kstp > 1, then kstp must match
808  if (this%hfr%kstp > 1 .and. (kstp /= this%hfr%kstp)) then
809  write (errmsg, '(4x,a)') 'TIME STEP NUMBER IN HEAD FILE &
810  &DOES NOT MATCH TIME STEP NUMBER IN TRANSPORT MODEL. IF THERE &
811  &IS MORE THAN ONE TIME STEP IN THE HEAD FILE FOR A GIVEN STRESS &
812  &PERIOD, HEAD FILE TIME STEPS MUST MATCH GWT MODEL TIME STEPS &
813  &ONE-FOR-ONE IN THAT STRESS PERIOD.'
814  call store_error(errmsg)
815  call store_error_unit(this%iuhds)
816  end if
817  !
818  ! -- fill the head array for this layer and
819  ! compress into reduced form
820  ncpl = size(this%hfr%head)
821  do i = 1, ncpl
822  nu = (ilay - 1) * ncpl + i
823  nr = this%dis%get_nodenumber(nu, 0)
824  val = this%hfr%head(i)
825  if (nr > 0) this%gwfhead(nr) = val
826  end do
827  end do
828  else
829  write (this%iout, fmthdskstpkper) kstp, kper, this%hfr%kstp, this%hfr%kper
830  end if
831  end subroutine advance_hfr
832 
833  !> @brief Finalize the head file reader
834  subroutine finalize_hfr(this)
835  class(flowmodelinterfacetype) :: this
836  close (this%iuhds)
837  end subroutine finalize_hfr
838 
839  !> @brief Initialize gwf terms from budget file
840  !!
841  !! initialize terms and figure out how many
842  !! different terms and packages are contained within the file
843  !<
845  ! -- modules
848  ! -- dummy
849  class(flowmodelinterfacetype) :: this
850  ! -- local
851  integer(I4B) :: nflowpack
852  integer(I4B) :: i, ip
853  integer(I4B) :: naux
854  logical :: found_flowja
855  logical :: found_dataspdis
856  logical :: found_datasat
857  logical :: found_stoss
858  logical :: found_stosy
859  integer(I4B), dimension(:), allocatable :: imap
860  !
861  ! -- Calculate the number of gwf flow packages
862  allocate (imap(this%bfr%nbudterms))
863  imap(:) = 0
864  nflowpack = 0
865  found_flowja = .false.
866  found_dataspdis = .false.
867  found_datasat = .false.
868  found_stoss = .false.
869  found_stosy = .false.
870  do i = 1, this%bfr%nbudterms
871  select case (trim(adjustl(this%bfr%budtxtarray(i))))
872  case ('FLOW-JA-FACE')
873  found_flowja = .true.
874  case ('DATA-SPDIS')
875  found_dataspdis = .true.
876  case ('DATA-SAT')
877  found_datasat = .true.
878  case ('STO-SS')
879  found_stoss = .true.
880  this%igwfstrgss = 1
881  case ('STO-SY')
882  found_stosy = .true.
883  this%igwfstrgsy = 1
884  case default
885  nflowpack = nflowpack + 1
886  imap(i) = 1
887  end select
888  end do
889  !
890  ! -- allocate gwfpackage arrays
891  call this%allocate_gwfpackages(nflowpack)
892  !
893  ! -- Copy the package name and aux names from budget file reader
894  ! to the gwfpackages derived-type variable
895  ip = 1
896  do i = 1, this%bfr%nbudterms
897  if (imap(i) == 0) cycle
898  call this%gwfpackages(ip)%set_name(this%bfr%dstpackagenamearray(i), &
899  this%bfr%budtxtarray(i))
900  naux = this%bfr%nauxarray(i)
901  call this%gwfpackages(ip)%set_auxname(naux, this%bfr%auxtxtarray(1:naux, i))
902  ip = ip + 1
903  end do
904  !
905  ! -- Copy just the package names for the boundary packages into
906  ! the flowpacknamearray
907  ip = 1
908  do i = 1, size(imap)
909  if (imap(i) == 1) then
910  this%flowpacknamearray(ip) = this%bfr%dstpackagenamearray(i)
911  ip = ip + 1
912  end if
913  end do
914  !
915  ! -- Error if specific discharge, saturation or flowja not found
916  if (.not. found_dataspdis) then
917  write (errmsg, '(4x,a)') 'SPECIFIC DISCHARGE NOT FOUND IN &
918  &BUDGET FILE. SAVE_SPECIFIC_DISCHARGE AND &
919  &SAVE_FLOWS MUST BE ACTIVATED IN THE NPF PACKAGE.'
920  call store_error(errmsg)
921  end if
922  if (.not. found_datasat) then
923  write (errmsg, '(4x,a)') 'SATURATION NOT FOUND IN &
924  &BUDGET FILE. SAVE_SATURATION AND &
925  &SAVE_FLOWS MUST BE ACTIVATED IN THE NPF PACKAGE.'
926  call store_error(errmsg)
927  end if
928  if (.not. found_flowja) then
929  write (errmsg, '(4x,a)') 'FLOWJA NOT FOUND IN &
930  &BUDGET FILE. SAVE_FLOWS MUST &
931  &BE ACTIVATED IN THE NPF PACKAGE.'
932  call store_error(errmsg)
933  end if
934  if (count_errors() > 0) then
935  call this%parser%StoreErrorUnit()
936  end if
937  end subroutine initialize_gwfterms_from_bfr
938 
939  !> @brief Initialize gwf terms from a GWF exchange
941  ! -- modules
942  use bndmodule, only: bndtype, getbndfromlist
943  ! -- dummy
944  class(flowmodelinterfacetype) :: this
945  ! -- local
946  integer(I4B) :: ngwfpack
947  integer(I4B) :: ngwfterms
948  integer(I4B) :: ip
949  integer(I4B) :: imover
950  integer(I4B) :: ntomvr
951  integer(I4B) :: iterm
952  character(len=LENPACKAGENAME) :: budtxt
953  class(bndtype), pointer :: packobj => null()
954  !
955  ! -- determine size of gwf terms
956  ngwfpack = this%gwfbndlist%Count()
957  !
958  ! -- Count number of to-mvr terms, but do not include advanced packages
959  ! as those mover terms are not losses from the cell, but rather flows
960  ! within the advanced package
961  ntomvr = 0
962  do ip = 1, ngwfpack
963  packobj => getbndfromlist(this%gwfbndlist, ip)
964  imover = packobj%imover
965  if (packobj%isadvpak /= 0) imover = 0
966  if (imover /= 0) then
967  ntomvr = ntomvr + 1
968  end if
969  end do
970  !
971  ! -- Allocate arrays in fmi of size ngwfterms, which is the number of
972  ! packages plus the number of packages with mover terms.
973  ngwfterms = ngwfpack + ntomvr
974  call this%allocate_gwfpackages(ngwfterms)
975  !
976  ! -- Assign values in the fmi package
977  iterm = 1
978  do ip = 1, ngwfpack
979  !
980  ! -- set and store names
981  packobj => getbndfromlist(this%gwfbndlist, ip)
982  budtxt = adjustl(packobj%text)
983  call this%gwfpackages(iterm)%set_name(packobj%packName, budtxt)
984  this%flowpacknamearray(iterm) = packobj%packName
985  iterm = iterm + 1
986  !
987  ! -- if this package has a mover associated with it, then add another
988  ! term that corresponds to the mover flows
989  imover = packobj%imover
990  if (packobj%isadvpak /= 0) imover = 0
991  if (imover /= 0) then
992  budtxt = trim(adjustl(packobj%text))//'-TO-MVR'
993  call this%gwfpackages(iterm)%set_name(packobj%packName, budtxt)
994  this%flowpacknamearray(iterm) = packobj%packName
995  this%igwfmvrterm(iterm) = 1
996  iterm = iterm + 1
997  end if
998  end do
1000 
1001  !> @brief Allocate budget packages
1002  !!
1003  !! gwfpackages is an array of PackageBudget objects.
1004  !! This routine allocates gwfpackages to the proper size and initializes some
1005  !! member variables.
1006  !<
1007  subroutine allocate_gwfpackages(this, ngwfterms)
1008  ! -- modules
1009  use constantsmodule, only: lenmempath
1011  ! -- dummy
1012  class(flowmodelinterfacetype) :: this
1013  integer(I4B), intent(in) :: ngwfterms
1014  ! -- local
1015  integer(I4B) :: n
1016  character(len=LENMEMPATH) :: memPath
1017  !
1018  ! -- direct allocate
1019  allocate (this%gwfpackages(ngwfterms))
1020  allocate (this%flowpacknamearray(ngwfterms))
1021  !
1022  ! -- mem_allocate
1023  call mem_allocate(this%igwfmvrterm, ngwfterms, 'IGWFMVRTERM', this%memoryPath)
1024  !
1025  ! -- initialize
1026  this%nflowpack = ngwfterms
1027  do n = 1, this%nflowpack
1028  this%igwfmvrterm(n) = 0
1029  this%flowpacknamearray(n) = ''
1030  !
1031  ! -- Create a mempath for each individual flow package data set
1032  ! of the form, MODELNAME/FMI-FTn
1033  write (mempath, '(a, i0)') trim(this%memoryPath)//'-FT', n
1034  call this%gwfpackages(n)%initialize(mempath)
1035  end do
1036  end subroutine allocate_gwfpackages
1037 
1038  !> @brief Deallocate memory in the gwfpackages array
1039  subroutine deallocate_gwfpackages(this)
1040  class(flowmodelinterfacetype) :: this
1041  integer(I4B) :: n
1042 
1043  do n = 1, this%nflowpack
1044  call this%gwfpackages(n)%da()
1045  end do
1046  end subroutine deallocate_gwfpackages
1047 
1048  !> @brief Find the package index for the package with the given name
1049  subroutine get_package_index(this, name, idx)
1050  use bndmodule, only: bndtype, getbndfromlist
1051  class(flowmodelinterfacetype) :: this
1052  character(len=*), intent(in) :: name
1053  integer(I4B), intent(inout) :: idx
1054  ! -- local
1055  integer(I4B) :: ip
1056  !
1057  ! -- Look through all the packages and return the index with name
1058  idx = 0
1059  do ip = 1, size(this%flowpacknamearray)
1060  if (this%flowpacknamearray(ip) == name) then
1061  idx = ip
1062  exit
1063  end if
1064  end do
1065  if (idx == 0) then
1066  call store_error('Error in get_package_index. Could not find '//name, &
1067  terminate=.true.)
1068  end if
1069  end subroutine get_package_index
1070 
1071 end module flowmodelinterfacemodule
This module contains the base boundary package.
class(bndtype) function, pointer, public getbndfromlist(list, idx)
Get boundary from package list.
subroutine, public budgetobject_cr_bfr(this, name, ibinun, iout, colconv1, colconv2)
Create a new budget object from a binary flow file.
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
integer(i4b), parameter lenpackagename
maximum length of the package name
Definition: Constants.f90:23
integer(i4b), parameter lenvarname
maximum length of a variable name
Definition: Constants.f90:17
real(dp), parameter dhalf
real constant 1/2
Definition: Constants.f90:68
real(dp), parameter dem6
real constant 1e-6
Definition: Constants.f90:109
real(dp), parameter dzero
real constant zero
Definition: Constants.f90:65
integer(i4b), parameter lenbudtxt
maximum length of a budget component names
Definition: Constants.f90:37
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:27
real(dp), parameter done
real constant 1
Definition: Constants.f90:76
Definition: Dis.f90:1
subroutine allocate_scalars(this)
Allocate scalars.
subroutine fmi_ar(this, ibound)
Allocate the package.
subroutine allocate_gwfpackages(this, ngwfterms)
Allocate budget packages.
subroutine deallocate_gwfpackages(this)
Deallocate memory in the gwfpackages array.
subroutine read_options(this)
Read options from input file.
subroutine finalize_hfr(this)
Finalize the head file reader.
subroutine fmi_df(this, dis, idryinactive)
Define the flow model interface.
subroutine get_package_index(this, name, idx)
Find the package index for the package with the given name.
subroutine advance_bfr(this)
Advance the budget file reader.
subroutine initialize_gwfterms_from_gwfbndlist(this)
Initialize gwf terms from a GWF exchange.
subroutine initialize_hfr(this)
Initialize the head file reader.
subroutine fmi_da(this)
Deallocate variables.
subroutine read_packagedata(this)
Read packagedata block from input file.
subroutine advance_hfr(this)
Advance the head file reader.
subroutine initialize_gwfterms_from_bfr(this)
Initialize gwf terms from budget file.
subroutine finalize_bfr(this)
Finalize the budget file reader.
subroutine allocate_arrays(this, nodes)
Allocate arrays.
subroutine initialize_bfr(this)
Initialize the budget file reader.
subroutine, public urdaux(naux, inunit, iout, lloc, istart, istop, auxname, line, text)
Read auxiliary variables from an input line.
integer(i4b) function, public getunit()
Get a free unit number.
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
This module defines variable data types.
Definition: kind.f90:8
This module contains the base numerical package type.
character(len=20) access
Definition: OpenSpec.f90:7
character(len=20) form
Definition: OpenSpec.f90:7
This module contains the PackageBudgetModule Module.
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
integer(i4b) function, public count_errors()
Return number of errors.
Definition: Sim.f90:59
subroutine, public store_error_unit(iunit, terminate)
Store the file unit number.
Definition: Sim.f90:168
This module contains simulation variables.
Definition: SimVariables.f90:9
character(len=maxcharlen) errmsg
error message string
integer(i4b), pointer, public kstp
current time step number
Definition: tdis.f90:24
integer(i4b), pointer, public kper
current stress period number
Definition: tdis.f90:23
@ brief BndType
Structured grid discretization.
Definition: Dis2d.f90:23
Structured grid discretization.
Definition: Dis.f90:23
Unstructured grid discretization.
Definition: Disu.f90:28
Vertex grid discretization.
Definition: Disv2d.f90:24
Vertex grid discretization.
Definition: Disv.f90:24
A generic heterogeneous doubly-linked list.
Definition: List.f90:14
Derived type for storing flows.