MODFLOW 6  version 6.7.0.dev2
USGS Modular Hydrologic Model
GridFileReader.f90
Go to the documentation of this file.
2 
3  use kindmodule
5  use simvariablesmodule, only: errmsg
6  use constantsmodule, only: linelength
10 
11  implicit none
12 
13  public :: gridfilereadertype
14 
16  private
17  integer(I4B), public :: inunit !< file unit
18  ! header
19  character(len=10), public :: grid_type !< DIS, DISV, DISU, etc
20  integer(I4B), public :: version !< binary grid file format version
21  integer(I4B) :: ntxt !< number of variables
22  integer(I4B) :: lentxt !< header line length per variable
23  ! index
24  type(hashtabletype), pointer :: dim !< map variable name to number of dims
25  type(hashtabletype), pointer :: pos !< map variable name to position in file
26  type(hashtabletype), pointer :: typ !< map variable name to type (1=int, 2=dbl)
27  type(hashtabletype), pointer :: shp_idx !< map variable name to index in shp
28  integer(I4B), allocatable :: shp(:) !< flat array of variable shapes
29  character(len=10), allocatable, public :: keys(:) !< variable names
30  contains
31  procedure, public :: initialize
32  procedure, public :: finalize
33  procedure, public :: read_int
34  procedure, public :: read_dbl
35  procedure, public :: read_int_1d
36  procedure, public :: read_dbl_1d
37  procedure, public :: read_charstr
38  procedure, public :: read_grid_shape
39  procedure, private :: read_header
40  procedure, private :: read_header_meta
41  procedure, private :: read_header_body
42  end type gridfilereadertype
43 
44 contains
45 
46  !> @Brief Initialize the grid file reader.
47  subroutine initialize(this, iu)
48  class(gridfilereadertype) :: this
49  integer(I4B), intent(in) :: iu
50 
51  this%inunit = iu
52  call hash_table_cr(this%dim)
53  call hash_table_cr(this%pos)
54  call hash_table_cr(this%typ)
55  call hash_table_cr(this%shp_idx)
56  allocate (this%shp(0))
57  call this%read_header()
58 
59  end subroutine initialize
60 
61  !> @brief Finalize the grid file reader.
62  subroutine finalize(this)
63  class(gridfilereadertype) :: this
64 
65  close (this%inunit)
66  call hash_table_da(this%dim)
67  call hash_table_da(this%pos)
68  call hash_table_da(this%typ)
69  call hash_table_da(this%shp_idx)
70  deallocate (this%shp)
71 
72  end subroutine finalize
73 
74  !> @brief Read the file's self-describing header. Internal use only.
75  subroutine read_header(this)
76  class(gridfilereadertype) :: this
77  call this%read_header_meta()
78  call this%read_header_body()
79  end subroutine read_header
80 
81  !> @brief Read self-describing metadata (first four lines). Internal use only.
82  subroutine read_header_meta(this)
83  ! dummy
84  class(gridfilereadertype) :: this
85  ! local
86  character(len=50) :: line
87  integer(I4B) :: lloc, istart, istop
88  integer(I4B) :: ival
89  real(DP) :: rval
90 
91  ! grid type
92  read (this%inunit) line
93  lloc = 1
94  call urword(line, lloc, istart, istop, 1, ival, rval, 0, 0)
95  if (line(istart:istop) /= 'GRID') then
96  call store_error('Binary grid file must begin with "GRID". '//&
97  &'Found: '//line(istart:istop))
98  call store_error_unit(this%inunit)
99  end if
100  call urword(line, lloc, istart, istop, 1, ival, rval, 0, 0)
101  this%grid_type = line(istart:istop)
102 
103  ! version
104  read (this%inunit) line
105  lloc = 1
106  call urword(line, lloc, istart, istop, 0, ival, rval, 0, 0)
107  call urword(line, lloc, istart, istop, 2, ival, rval, 0, 0)
108  this%version = ival
109 
110  ! ntxt
111  read (this%inunit) line
112  lloc = 1
113  call urword(line, lloc, istart, istop, 0, ival, rval, 0, 0)
114  call urword(line, lloc, istart, istop, 2, ival, rval, 0, 0)
115  this%ntxt = ival
116 
117  ! lentxt
118  read (this%inunit) line
119  lloc = 1
120  call urword(line, lloc, istart, istop, 0, ival, rval, 0, 0)
121  call urword(line, lloc, istart, istop, 2, ival, rval, 0, 0)
122  this%lentxt = ival
123 
124  end subroutine read_header_meta
125 
126  !> @brief Read the header body section (text following first
127  !< four "meta" lines) and build an index. Internal use only.
128  subroutine read_header_body(this)
129  ! dummy
130  class(gridfilereadertype) :: this
131  ! local
132  character(len=:), allocatable :: body
133  character(len=:), allocatable :: line
134  character(len=10) :: key, dtype
135  real(DP) :: rval
136  integer(I4B) :: i, lloc, istart, istop, ival, pos
137  integer(I4B) :: nvars, ndim, dim, ishp
138  integer(I4B), allocatable :: shp(:)
139 
140  allocate (this%keys(this%ntxt))
141  allocate (character(len=this%lentxt*this%ntxt) :: body)
142  allocate (character(len=this%lentxt) :: line)
143 
144  nvars = 0
145  read (this%inunit) body
146  inquire (this%inunit, pos=pos)
147  do i = 1, this%lentxt * this%ntxt, this%lentxt
148  line = body(i:i + this%lentxt - 1)
149  lloc = 1
150 
151  ! key
152  lloc = 1
153  call urword(line, lloc, istart, istop, 1, ival, rval, 0, 0)
154  key = line(istart:istop)
155  nvars = nvars + 1
156  this%keys(nvars) = key
157 
158  ! type
159  call urword(line, lloc, istart, istop, 1, ival, rval, 0, 0)
160  dtype = line(istart:istop)
161  if (dtype == "INTEGER") then
162  call this%typ%add(key, 1)
163  else if (dtype == "DOUBLE") then
164  call this%typ%add(key, 2)
165  else if (dtype == "CHARACTER") then
166  call this%typ%add(key, 3)
167  end if
168 
169  ! dims
170  call urword(line, lloc, istart, istop, 0, ival, rval, 0, 0)
171  call urword(line, lloc, istart, istop, 2, ival, rval, 0, 0)
172  ndim = ival
173  call this%dim%add(key, ndim)
174 
175  ! shape
176  if (allocated(shp)) deallocate (shp)
177  allocate (shp(ndim))
178  if (ndim > 0) then
179  do dim = 1, ndim
180  call urword(line, lloc, istart, istop, 2, ival, rval, 0, 0)
181  shp(dim) = ival
182  end do
183  ishp = size(this%shp)
184  call expandarray(this%shp, increment=ndim)
185  this%shp(ishp + 1:ishp + ndim) = shp
186  call this%shp_idx%add(key, ishp + 1)
187  end if
188 
189  ! position
190  call this%pos%add(key, pos)
191  if (ndim == 0) then
192  if (dtype == "INTEGER") then
193  pos = pos + 4
194  else if (dtype == "DOUBLE") then
195  pos = pos + 8
196  end if
197  else
198  if (dtype == "INTEGER") then
199  pos = pos + (product(shp) * 4)
200  else if (dtype == "DOUBLE") then
201  pos = pos + (product(shp) * 8)
202  else if (dtype == "CHARACTER") then
203  pos = pos + (product(shp) * 8)
204  end if
205  end if
206  end do
207 
208  rewind(this%inunit)
209 
210  end subroutine read_header_body
211 
212  !> @brief Read an integer scalar from a grid file.
213  function read_int(this, key) result(v)
214  class(gridfilereadertype), intent(inout) :: this
215  character(len=*), intent(in) :: key
216  integer(I4B) :: v
217  ! local
218  integer(I4B) :: ndim, pos, typ
219  character(len=:), allocatable :: msg
220 
221  msg = 'Variable '//trim(key)//' is not an integer scalar'
222  ndim = this%dim%get(key)
223  if (ndim /= 0) then
224  write (errmsg, '(a)') msg
225  call store_error(errmsg, terminate=.true.)
226  end if
227  typ = this%typ%get(key)
228  if (typ /= 1) then
229  write (errmsg, '(a)') msg
230  call store_error(errmsg, terminate=.true.)
231  end if
232  pos = this%pos%get(key)
233  read (this%inunit, pos=pos) v
234  rewind(this%inunit)
235 
236  end function read_int
237 
238  !> @brief Read a double precision scalar from a grid file.
239  function read_dbl(this, key) result(v)
240  class(gridfilereadertype), intent(inout) :: this
241  character(len=*), intent(in) :: key
242  real(dp) :: v
243  ! local
244  integer(I4B) :: ndim, pos, typ
245  character(len=:), allocatable :: msg
246 
247  msg = 'Variable '//trim(key)//' is not a double precision scalar'
248  ndim = this%dim%get(key)
249  if (ndim /= 0) then
250  write (errmsg, '(a)') msg
251  call store_error(errmsg, terminate=.true.)
252  end if
253  typ = this%typ%get(key)
254  if (typ /= 2) then
255  write (errmsg, '(a)') msg
256  call store_error(errmsg, terminate=.true.)
257  end if
258  pos = this%pos%get(key)
259  read (this%inunit, pos=pos) v
260  rewind(this%inunit)
261 
262  end function read_dbl
263 
264  !> @brief Read a 1D integer array from a grid file.
265  function read_int_1d(this, key) result(v)
266  class(gridfilereadertype), intent(inout) :: this
267  character(len=*), intent(in) :: key
268  integer(I4B), allocatable :: v(:)
269  ! local
270  integer(I4B) :: idx, ndim, nvals, pos, typ
271  character(len=:), allocatable :: msg
272 
273  msg = 'Variable '//trim(key)//' is not a 1D integer array'
274  ndim = this%dim%get(key)
275  if (ndim /= 1) then
276  write (errmsg, '(a)') msg
277  call store_error(errmsg, terminate=.true.)
278  end if
279  typ = this%typ%get(key)
280  if (typ /= 1) then
281  write (errmsg, '(a)') msg
282  call store_error(errmsg, terminate=.true.)
283  end if
284  idx = this%shp_idx%get(key)
285  pos = this%pos%get(key)
286  nvals = this%shp(idx)
287  allocate (v(nvals))
288  read (this%inunit, pos=pos) v
289  rewind(this%inunit)
290 
291  end function read_int_1d
292 
293  !> @brief Read a 1D double array from a grid file.
294  function read_dbl_1d(this, key) result(v)
295  class(gridfilereadertype), intent(inout) :: this
296  character(len=*), intent(in) :: key
297  real(dp), allocatable :: v(:)
298  ! local
299  integer(I4B) :: idx, ndim, nvals, pos, typ
300  character(len=:), allocatable :: msg
301 
302  msg = 'Variable '//trim(key)//' is not a 1D double array'
303  ndim = this%dim%get(key)
304  if (ndim /= 1) then
305  write (errmsg, '(a)') msg
306  call store_error(errmsg, terminate=.true.)
307  end if
308  typ = this%typ%get(key)
309  if (typ /= 2) then
310  write (errmsg, '(a)') msg
311  call store_error(errmsg, terminate=.true.)
312  end if
313  idx = this%shp_idx%get(key)
314  pos = this%pos%get(key)
315  nvals = this%shp(idx)
316  allocate (v(nvals))
317  read (this%inunit, pos=pos) v
318  rewind(this%inunit)
319 
320  end function read_dbl_1d
321 
322  !> @brief Read a character string from a grid file.
323  function read_charstr(this, key) result(charstr)
324  class(gridfilereadertype), intent(inout) :: this
325  character(len=*), intent(in) :: key
326  character(len=:), allocatable :: charstr
327  ! local
328  integer(I4B) :: idx, ndim, nvals, pos, typ
329  character(len=:), allocatable :: msg
330 
331  msg = 'Variable '//trim(key)//' is not a character array'
332  ndim = this%dim%get(key)
333  if (ndim /= 1) then
334  write (errmsg, '(a)') msg
335  call store_error(errmsg, terminate=.true.)
336  end if
337  typ = this%typ%get(key)
338  if (typ /= 3) then
339  write (errmsg, '(a)') msg
340  call store_error(errmsg, terminate=.true.)
341  end if
342  idx = this%shp_idx%get(key)
343  pos = this%pos%get(key)
344  nvals = this%shp(idx)
345  allocate (character(nvals) :: charstr)
346  read (this%inunit, pos=pos) charstr
347  rewind(this%inunit)
348  end function read_charstr
349 
350  !> @brief Read the grid shape from a grid file.
351  function read_grid_shape(this) result(v)
352  ! dummy
353  class(gridfilereadertype) :: this
354  integer(I4B), allocatable :: v(:)
355 
356  select case (this%grid_type)
357  case ("DIS")
358  allocate (v(3))
359  v(1) = this%read_int("NLAY")
360  v(2) = this%read_int("NROW")
361  v(3) = this%read_int("NCOL")
362  case ("DISV")
363  allocate (v(2))
364  v(1) = this%read_int("NLAY")
365  v(2) = this%read_int("NCPL")
366  case ("DISU")
367  allocate (v(1))
368  v(1) = this%read_int("NODES")
369  case ("DIS2D")
370  allocate (v(2))
371  v(1) = this%read_int("NROW")
372  v(2) = this%read_int("NCOL")
373  case ("DISV2D")
374  allocate (v(1))
375  v(1) = this%read_int("NODES")
376  case ("DISV1D")
377  allocate (v(1))
378  v(1) = this%read_int("NCELLS")
379  end select
380 
381  end function read_grid_shape
382 
383 end module gridfilereadermodule
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:45
subroutine initialize(this, iu)
@Brief Initialize the grid file reader.
subroutine read_header(this)
Read the file's self-describing header. Internal use only.
subroutine read_header_meta(this)
Read self-describing metadata (first four lines). Internal use only.
integer(i4b) function read_int(this, key)
Read an integer scalar from a grid file.
subroutine read_header_body(this)
Read the header body section (text following first.
subroutine finalize(this)
Finalize the grid file reader.
real(dp) function, dimension(:), allocatable read_dbl_1d(this, key)
Read a 1D double array from a grid file.
character(len=:) function, allocatable read_charstr(this, key)
Read a character string from a grid file.
integer(i4b) function, dimension(:), allocatable read_int_1d(this, key)
Read a 1D integer array from a grid file.
real(dp) function read_dbl(this, key)
Read a double precision scalar from a grid file.
integer(i4b) function, dimension(:), allocatable read_grid_shape(this)
Read the grid shape from a grid file.
A chaining hash map for integers.
Definition: HashTable.f90:7
subroutine, public hash_table_cr(map)
Create a hash table.
Definition: HashTable.f90:46
subroutine, public hash_table_da(map)
Deallocate the hash table.
Definition: HashTable.f90:64
subroutine, public openfile(iu, iout, fname, ftype, fmtarg_opt, accarg_opt, filstat_opt, mode_opt)
Open a file.
Definition: InputOutput.f90:30
subroutine, public urword(line, icol, istart, istop, ncode, n, r, iout, in)
Extract a word from a string.
This module defines variable data types.
Definition: kind.f90:8
This module contains simulation methods.
Definition: Sim.f90:10
subroutine, public store_error(msg, terminate)
Store an error message.
Definition: Sim.f90:92
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