MODFLOW 6  version 6.7.0.dev3
USGS Modular Hydrologic Model
gridfilereadermodule Module Reference

Data Types

type  gridfilereadertype
 

Functions/Subroutines

subroutine initialize (this, iu)
 @Brief Initialize the grid file reader. More...
 
subroutine finalize (this)
 Finalize the grid file reader. More...
 
subroutine read_header (this)
 Read the file's self-describing header. Internal use only. More...
 
subroutine read_header_meta (this)
 Read self-describing metadata (first four lines). Internal use only. More...
 
subroutine read_header_body (this)
 Read the header body section (text following first. More...
 
integer(i4b) function read_int (this, key)
 Read an integer scalar from a grid file. More...
 
real(dp) function read_dbl (this, key)
 Read a double precision scalar from a grid file. More...
 
integer(i4b) function, dimension(:), allocatable read_int_1d (this, key)
 Read a 1D integer array from a grid file. More...
 
subroutine read_int_1d_into (this, key, v)
 Read a 1D integer array into a preallocated array. More...
 
real(dp) function, dimension(:), allocatable read_dbl_1d (this, key)
 Read a 1D double array from a grid file. More...
 
subroutine read_dbl_1d_into (this, key, v)
 Read a 1D double array into a preallocated array. More...
 
character(len=:) function, allocatable read_charstr (this, key)
 Read a character string from a grid file. More...
 
subroutine read_charstr_into (this, key, charstr)
 Read a character string into a preallocated string. More...
 
integer(i4b) function, dimension(:), allocatable read_grid_shape (this)
 Read the grid shape from a grid file. More...
 
logical(lgp) function, allocatable has_variable (this, key)
 

Function/Subroutine Documentation

◆ finalize()

subroutine gridfilereadermodule::finalize ( class(gridfilereadertype this)

Definition at line 70 of file GridFileReader.f90.

71  class(GridFileReaderType) :: this
72 
73  close (this%inunit)
74  call hash_table_da(this%dim)
75  call hash_table_da(this%pos)
76  call hash_table_da(this%typ)
77  call hash_table_da(this%shp_idx)
78  deallocate (this%shp)
79 
Here is the call graph for this function:

◆ has_variable()

logical(lgp) function, allocatable gridfilereadermodule::has_variable ( class(gridfilereadertype this,
character(len=*), intent(in)  key 
)

Definition at line 514 of file GridFileReader.f90.

515  class(GridFileReaderType) :: this
516  character(len=*), intent(in) :: key
517  logical(LGP), allocatable :: has
518 
519  has = this%dim%get(key) /= 0

◆ initialize()

subroutine gridfilereadermodule::initialize ( class(gridfilereadertype this,
integer(i4b), intent(in)  iu 
)

Definition at line 55 of file GridFileReader.f90.

56  class(GridFileReaderType) :: this
57  integer(I4B), intent(in) :: iu
58 
59  this%inunit = iu
60  call hash_table_cr(this%dim)
61  call hash_table_cr(this%pos)
62  call hash_table_cr(this%typ)
63  call hash_table_cr(this%shp_idx)
64  allocate (this%shp(0))
65  call this%read_header()
66 
Here is the call graph for this function:

◆ read_charstr()

character(len=:) function, allocatable gridfilereadermodule::read_charstr ( class(gridfilereadertype), intent(inout)  this,
character(len=*), intent(in)  key 
)

Allocates and returns a new character string containing the data.

Definition at line 415 of file GridFileReader.f90.

416  class(GridFileReaderType), intent(inout) :: this
417  character(len=*), intent(in) :: key
418  character(len=:), allocatable :: charstr
419  ! local
420  integer(I4B) :: idx, ndim, nvals, pos, typ
421  character(len=:), allocatable :: msg
422 
423  msg = 'Variable '//trim(key)//' is not a character array'
424  ndim = this%dim%get(key)
425  if (ndim /= 1) then
426  write (errmsg, '(a)') msg
427  call store_error(errmsg, terminate=.true.)
428  end if
429  typ = this%typ%get(key)
430  if (typ /= 3) then
431  write (errmsg, '(a)') msg
432  call store_error(errmsg, terminate=.true.)
433  end if
434  idx = this%shp_idx%get(key)
435  pos = this%pos%get(key)
436  nvals = this%shp(idx)
437  allocate (character(nvals) :: charstr)
438  read (this%inunit, pos=pos) charstr
439  rewind(this%inunit)
Here is the call graph for this function:

◆ read_charstr_into()

subroutine gridfilereadermodule::read_charstr_into ( class(gridfilereadertype), intent(inout)  this,
character(len=*), intent(in)  key,
character(len=:), intent(inout), allocatable  charstr 
)

Populates a preallocated character string. If the string is not allocated or is the wrong length, it will be (re)allocated to the correct length.

Definition at line 446 of file GridFileReader.f90.

447  class(GridFileReaderType), intent(inout) :: this
448  character(len=*), intent(in) :: key
449  character(len=:), allocatable, intent(inout) :: charstr
450  ! local
451  integer(I4B) :: idx, ndim, nvals, pos, typ
452  character(len=:), allocatable :: msg
453 
454  msg = 'Variable '//trim(key)//' is not a character array'
455  ndim = this%dim%get(key)
456  if (ndim /= 1) then
457  write (errmsg, '(a)') msg
458  call store_error(errmsg, terminate=.true.)
459  end if
460  typ = this%typ%get(key)
461  if (typ /= 3) then
462  write (errmsg, '(a)') msg
463  call store_error(errmsg, terminate=.true.)
464  end if
465  idx = this%shp_idx%get(key)
466  pos = this%pos%get(key)
467  nvals = this%shp(idx)
468  ! reallocate if not allocated or wrong length
469  if (allocated(charstr)) then
470  if (len(charstr) /= nvals) then
471  deallocate (charstr)
472  allocate (character(nvals) :: charstr)
473  end if
474  else
475  allocate (character(nvals) :: charstr)
476  end if
477  read (this%inunit, pos=pos) charstr
478  rewind(this%inunit)
Here is the call graph for this function:

◆ read_dbl()

real(dp) function gridfilereadermodule::read_dbl ( class(gridfilereadertype), intent(inout)  this,
character(len=*), intent(in)  key 
)

Definition at line 247 of file GridFileReader.f90.

248  class(GridFileReaderType), intent(inout) :: this
249  character(len=*), intent(in) :: key
250  real(DP) :: v
251  ! local
252  integer(I4B) :: ndim, pos, typ
253  character(len=:), allocatable :: msg
254 
255  msg = 'Variable '//trim(key)//' is not a double precision scalar'
256  ndim = this%dim%get(key)
257  if (ndim /= 0) then
258  write (errmsg, '(a)') msg
259  call store_error(errmsg, terminate=.true.)
260  end if
261  typ = this%typ%get(key)
262  if (typ /= 2) then
263  write (errmsg, '(a)') msg
264  call store_error(errmsg, terminate=.true.)
265  end if
266  pos = this%pos%get(key)
267  read (this%inunit, pos=pos) v
268  rewind(this%inunit)
269 
Here is the call graph for this function:

◆ read_dbl_1d()

real(dp) function, dimension(:), allocatable gridfilereadermodule::read_dbl_1d ( class(gridfilereadertype), intent(inout)  this,
character(len=*), intent(in)  key 
)

Allocates and returns a new array containing the data.

Definition at line 345 of file GridFileReader.f90.

346  class(GridFileReaderType), intent(inout) :: this
347  character(len=*), intent(in) :: key
348  real(DP), allocatable :: v(:)
349  ! local
350  integer(I4B) :: idx, ndim, nvals, pos, typ
351  character(len=:), allocatable :: msg
352 
353  msg = 'Variable '//trim(key)//' is not a 1D double array'
354  ndim = this%dim%get(key)
355  if (ndim /= 1) then
356  write (errmsg, '(a)') msg
357  call store_error(errmsg, terminate=.true.)
358  end if
359  typ = this%typ%get(key)
360  if (typ /= 2) then
361  write (errmsg, '(a)') msg
362  call store_error(errmsg, terminate=.true.)
363  end if
364  idx = this%shp_idx%get(key)
365  pos = this%pos%get(key)
366  nvals = this%shp(idx)
367  allocate (v(nvals))
368  read (this%inunit, pos=pos) v
369  rewind(this%inunit)
370 
Here is the call graph for this function:

◆ read_dbl_1d_into()

subroutine gridfilereadermodule::read_dbl_1d_into ( class(gridfilereadertype), intent(inout)  this,
character(len=*), intent(in)  key,
real(dp), dimension(:), intent(inout)  v 
)

Populates a preallocated array. Array must already be allocated to the correct size. This version is compatible with both allocatable arrays and memory-manager-allocated pointer targets.

Definition at line 378 of file GridFileReader.f90.

379  class(GridFileReaderType), intent(inout) :: this
380  character(len=*), intent(in) :: key
381  real(DP), dimension(:), intent(inout) :: v
382  ! local
383  integer(I4B) :: idx, ndim, nvals, pos, typ
384  character(len=:), allocatable :: msg
385 
386  msg = 'Variable '//trim(key)//' is not a 1D double array'
387  ndim = this%dim%get(key)
388  if (ndim /= 1) then
389  write (errmsg, '(a)') msg
390  call store_error(errmsg, terminate=.true.)
391  end if
392  typ = this%typ%get(key)
393  if (typ /= 2) then
394  write (errmsg, '(a)') msg
395  call store_error(errmsg, terminate=.true.)
396  end if
397  idx = this%shp_idx%get(key)
398  pos = this%pos%get(key)
399  nvals = this%shp(idx)
400  ! verify array is correct size
401  if (size(v) /= nvals) then
402  write (errmsg, '(a,i0,a,i0)') &
403  'Array size mismatch for '//trim(key)//': expected ', &
404  nvals, ', got ', size(v)
405  call store_error(errmsg, terminate=.true.)
406  end if
407  read (this%inunit, pos=pos) v
408  rewind(this%inunit)
409 
Here is the call graph for this function:

◆ read_grid_shape()

integer(i4b) function, dimension(:), allocatable gridfilereadermodule::read_grid_shape ( class(gridfilereadertype this)

Definition at line 482 of file GridFileReader.f90.

483  ! dummy
484  class(GridFileReaderType) :: this
485  integer(I4B), allocatable :: v(:)
486 
487  select case (this%grid_type)
488  case ("DIS")
489  allocate (v(3))
490  v(1) = this%read_int("NLAY")
491  v(2) = this%read_int("NROW")
492  v(3) = this%read_int("NCOL")
493  case ("DISV")
494  allocate (v(2))
495  v(1) = this%read_int("NLAY")
496  v(2) = this%read_int("NCPL")
497  case ("DISU")
498  allocate (v(1))
499  v(1) = this%read_int("NODES")
500  case ("DIS2D")
501  allocate (v(2))
502  v(1) = this%read_int("NROW")
503  v(2) = this%read_int("NCOL")
504  case ("DISV2D")
505  allocate (v(1))
506  v(1) = this%read_int("NODES")
507  case ("DISV1D")
508  allocate (v(1))
509  v(1) = this%read_int("NCELLS")
510  end select
511 

◆ read_header()

subroutine gridfilereadermodule::read_header ( class(gridfilereadertype this)

Definition at line 83 of file GridFileReader.f90.

84  class(GridFileReaderType) :: this
85  call this%read_header_meta()
86  call this%read_header_body()

◆ read_header_body()

subroutine gridfilereadermodule::read_header_body ( class(gridfilereadertype this)

Definition at line 136 of file GridFileReader.f90.

137  ! dummy
138  class(GridFileReaderType) :: this
139  ! local
140  character(len=:), allocatable :: body
141  character(len=:), allocatable :: line
142  character(len=10) :: key, dtype
143  real(DP) :: rval
144  integer(I4B) :: i, lloc, istart, istop, ival, pos
145  integer(I4B) :: nvars, ndim, dim, ishp
146  integer(I4B), allocatable :: shp(:)
147 
148  allocate (this%keys(this%ntxt))
149  allocate (character(len=this%lentxt*this%ntxt) :: body)
150  allocate (character(len=this%lentxt) :: line)
151 
152  nvars = 0
153  read (this%inunit) body
154  inquire (this%inunit, pos=pos)
155  do i = 1, this%lentxt * this%ntxt, this%lentxt
156  line = body(i:i + this%lentxt - 1)
157  lloc = 1
158 
159  ! key
160  lloc = 1
161  call urword(line, lloc, istart, istop, 1, ival, rval, 0, 0)
162  key = line(istart:istop)
163  nvars = nvars + 1
164  this%keys(nvars) = key
165 
166  ! type
167  call urword(line, lloc, istart, istop, 1, ival, rval, 0, 0)
168  dtype = line(istart:istop)
169  if (dtype == "INTEGER") then
170  call this%typ%add(key, 1)
171  else if (dtype == "DOUBLE") then
172  call this%typ%add(key, 2)
173  else if (dtype == "CHARACTER") then
174  call this%typ%add(key, 3)
175  end if
176 
177  ! dims
178  call urword(line, lloc, istart, istop, 0, ival, rval, 0, 0)
179  call urword(line, lloc, istart, istop, 2, ival, rval, 0, 0)
180  ndim = ival
181  call this%dim%add(key, ndim)
182 
183  ! shape
184  if (allocated(shp)) deallocate (shp)
185  allocate (shp(ndim))
186  if (ndim > 0) then
187  do dim = 1, ndim
188  call urword(line, lloc, istart, istop, 2, ival, rval, 0, 0)
189  shp(dim) = ival
190  end do
191  ishp = size(this%shp)
192  call expandarray(this%shp, increment=ndim)
193  this%shp(ishp + 1:ishp + ndim) = shp
194  call this%shp_idx%add(key, ishp + 1)
195  end if
196 
197  ! position
198  call this%pos%add(key, pos)
199  if (ndim == 0) then
200  if (dtype == "INTEGER") then
201  pos = pos + 4
202  else if (dtype == "DOUBLE") then
203  pos = pos + 8
204  end if
205  else
206  if (dtype == "INTEGER") then
207  pos = pos + (product(shp) * 4)
208  else if (dtype == "DOUBLE") then
209  pos = pos + (product(shp) * 8)
210  else if (dtype == "CHARACTER") then
211  pos = pos + (product(shp) * 8)
212  end if
213  end if
214  end do
215 
216  rewind(this%inunit)
217 
Here is the call graph for this function:

◆ read_header_meta()

subroutine gridfilereadermodule::read_header_meta ( class(gridfilereadertype this)

Definition at line 90 of file GridFileReader.f90.

91  ! dummy
92  class(GridFileReaderType) :: this
93  ! local
94  character(len=50) :: line
95  integer(I4B) :: lloc, istart, istop
96  integer(I4B) :: ival
97  real(DP) :: rval
98 
99  ! grid type
100  read (this%inunit) line
101  lloc = 1
102  call urword(line, lloc, istart, istop, 1, ival, rval, 0, 0)
103  if (line(istart:istop) /= 'GRID') then
104  call store_error('Binary grid file must begin with "GRID". '//&
105  &'Found: '//line(istart:istop))
106  call store_error_unit(this%inunit)
107  end if
108  call urword(line, lloc, istart, istop, 1, ival, rval, 0, 0)
109  this%grid_type = line(istart:istop)
110 
111  ! version
112  read (this%inunit) line
113  lloc = 1
114  call urword(line, lloc, istart, istop, 0, ival, rval, 0, 0)
115  call urword(line, lloc, istart, istop, 2, ival, rval, 0, 0)
116  this%version = ival
117 
118  ! ntxt
119  read (this%inunit) line
120  lloc = 1
121  call urword(line, lloc, istart, istop, 0, ival, rval, 0, 0)
122  call urword(line, lloc, istart, istop, 2, ival, rval, 0, 0)
123  this%ntxt = ival
124 
125  ! lentxt
126  read (this%inunit) line
127  lloc = 1
128  call urword(line, lloc, istart, istop, 0, ival, rval, 0, 0)
129  call urword(line, lloc, istart, istop, 2, ival, rval, 0, 0)
130  this%lentxt = ival
131 
Here is the call graph for this function:

◆ read_int()

integer(i4b) function gridfilereadermodule::read_int ( class(gridfilereadertype), intent(inout)  this,
character(len=*), intent(in)  key 
)

Definition at line 221 of file GridFileReader.f90.

222  class(GridFileReaderType), intent(inout) :: this
223  character(len=*), intent(in) :: key
224  integer(I4B) :: v
225  ! local
226  integer(I4B) :: ndim, pos, typ
227  character(len=:), allocatable :: msg
228 
229  msg = 'Variable '//trim(key)//' is not an integer scalar'
230  ndim = this%dim%get(key)
231  if (ndim /= 0) then
232  write (errmsg, '(a)') msg
233  call store_error(errmsg, terminate=.true.)
234  end if
235  typ = this%typ%get(key)
236  if (typ /= 1) then
237  write (errmsg, '(a)') msg
238  call store_error(errmsg, terminate=.true.)
239  end if
240  pos = this%pos%get(key)
241  read (this%inunit, pos=pos) v
242  rewind(this%inunit)
243 
Here is the call graph for this function:

◆ read_int_1d()

integer(i4b) function, dimension(:), allocatable gridfilereadermodule::read_int_1d ( class(gridfilereadertype), intent(inout)  this,
character(len=*), intent(in)  key 
)

Allocates and returns a new array containing the data.

Definition at line 275 of file GridFileReader.f90.

276  class(GridFileReaderType), intent(inout) :: this
277  character(len=*), intent(in) :: key
278  integer(I4B), allocatable :: v(:)
279  ! local
280  integer(I4B) :: idx, ndim, nvals, pos, typ
281  character(len=:), allocatable :: msg
282 
283  msg = 'Variable '//trim(key)//' is not a 1D integer array'
284  ndim = this%dim%get(key)
285  if (ndim /= 1) then
286  write (errmsg, '(a)') msg
287  call store_error(errmsg, terminate=.true.)
288  end if
289  typ = this%typ%get(key)
290  if (typ /= 1) then
291  write (errmsg, '(a)') msg
292  call store_error(errmsg, terminate=.true.)
293  end if
294  idx = this%shp_idx%get(key)
295  pos = this%pos%get(key)
296  nvals = this%shp(idx)
297  allocate (v(nvals))
298  read (this%inunit, pos=pos) v
299  rewind(this%inunit)
300 
Here is the call graph for this function:

◆ read_int_1d_into()

subroutine gridfilereadermodule::read_int_1d_into ( class(gridfilereadertype), intent(inout)  this,
character(len=*), intent(in)  key,
integer(i4b), dimension(:), intent(inout)  v 
)

Populates a preallocated array. Array must already be allocated to the correct size. This version is compatible with both allocatable arrays and memory-manager-allocated pointer targets.

Definition at line 308 of file GridFileReader.f90.

309  class(GridFileReaderType), intent(inout) :: this
310  character(len=*), intent(in) :: key
311  integer(I4B), dimension(:), intent(inout) :: v
312  ! local
313  integer(I4B) :: idx, ndim, nvals, pos, typ
314  character(len=:), allocatable :: msg
315 
316  msg = 'Variable '//trim(key)//' is not a 1D integer array'
317  ndim = this%dim%get(key)
318  if (ndim /= 1) then
319  write (errmsg, '(a)') msg
320  call store_error(errmsg, terminate=.true.)
321  end if
322  typ = this%typ%get(key)
323  if (typ /= 1) then
324  write (errmsg, '(a)') msg
325  call store_error(errmsg, terminate=.true.)
326  end if
327  idx = this%shp_idx%get(key)
328  pos = this%pos%get(key)
329  nvals = this%shp(idx)
330  ! verify array is correct size
331  if (size(v) /= nvals) then
332  write (errmsg, '(a,i0,a,i0)') &
333  'Array size mismatch for '//trim(key)//': expected ', &
334  nvals, ', got ', size(v)
335  call store_error(errmsg, terminate=.true.)
336  end if
337  read (this%inunit, pos=pos) v
338  rewind(this%inunit)
339 
Here is the call graph for this function: