MODFLOW 6  version 6.7.0.dev2
USGS Modular Hydrologic Model
HeadFileReader.f90
Go to the documentation of this file.
2 
3  use kindmodule
6 
7  implicit none
8 
9  private
11 
13  character(len=16) :: text
14  integer(I4B) :: ncol, nrow, ilay
15  contains
16  procedure :: get_str
17  end type headfileheadertype
18 
20  integer(I4B) :: nlay
21  real(dp), dimension(:), allocatable :: head
22  contains
23  procedure :: initialize
24  procedure :: read_header
25  procedure :: read_record
26  procedure :: rewind
27  procedure :: finalize
28  end type headfilereadertype
29 
30 contains
31 
32  !< @brief initialize
33  !<
34  subroutine initialize(this, iu, iout)
35  ! -- dummy
36  class(headfilereadertype) :: this
37  integer(I4B), intent(in) :: iu
38  integer(I4B), intent(in) :: iout
39  ! -- local
40  integer(I4B) :: kstp_last, kper_last
41  logical :: success
42  !
43  this%inunit = iu
44  this%nlay = 0
45  call this%rewind()
46  !
47  ! -- Read the first head data record to set kstp_last, kstp_last
48  call this%read_record(success)
49  kstp_last = this%header%kstp
50  kper_last = this%header%kper
51  call this%rewind()
52  !
53  ! -- Determine number of records within a time step
54  if (iout > 0) &
55  write (iout, '(a)') &
56  'Reading binary file to determine number of records per time step.'
57  do
58  call this%read_record(success, iout)
59  if (.not. success) exit
60  if (kstp_last /= this%header%kstp .or. kper_last /= this%header%kper) exit
61  this%nlay = this%nlay + 1
62  end do
63  call this%rewind()
64  if (iout > 0) &
65  write (iout, '(a, i0, a)') 'Detected ', this%nlay, &
66  ' unique records in binary file.'
67  end subroutine initialize
68 
69  !< @brief read header only
70  !<
71  subroutine read_header(this, success, iout)
72  ! -- dummy
73  class(headfilereadertype), intent(inout) :: this
74  logical, intent(out) :: success
75  integer(I4B), intent(in), optional :: iout
76  ! -- local
77  integer(I4B) :: iostat, pos
78  !
79  success = .true.
80  select type (h => this%header)
81  type is (headfileheadertype)
82  h%kstp = 0
83  h%kper = 0
84  h%text = ''
85  h%ncol = 0
86  h%nrow = 0
87  h%ilay = 0
88  inquire (unit=this%inunit, pos=h%pos)
89  read (this%inunit, iostat=iostat) h%kstp, h%kper, &
90  h%pertim, h%totim, h%text, h%ncol, h%nrow, h%ilay
91  if (iostat /= 0) then
92  success = .false.
93  if (iostat < 0) this%endoffile = .true.
94  return
95  end if
96  inquire (unit=this%inunit, pos=pos)
97  this%header%size = pos - this%header%pos
98  end select
99  end subroutine read_header
100 
101  !< @brief read record
102  !<
103  subroutine read_record(this, success, iout)
104  ! -- modules
106  ! -- dummy
107  class(headfilereadertype), intent(inout) :: this
108  logical, intent(out) :: success
109  integer(I4B), intent(in), optional :: iout
110  ! -- local
111  integer(I4B) :: iout_opt
112  integer(I4B) :: ncol, nrow
113  !
114  if (present(iout)) then
115  iout_opt = iout
116  else
117  iout_opt = 0
118  end if
119  !
120  call this%read_header(success, iout_opt)
121  if (.not. success) return
122  !
123  select type (h => this%header)
124  type is (headfileheadertype)
125  ncol = h%ncol
126  nrow = h%nrow
127  end select
128  !
129  ! -- allocate head to proper size
130  if (.not. allocated(this%head)) then
131  allocate (this%head(ncol * nrow))
132  else
133  if (size(this%head) /= ncol * nrow) then
134  deallocate (this%head)
135  allocate (this%head(ncol * nrow))
136  end if
137  end if
138  !
139  ! -- read the head array
140  read (this%inunit) this%head
141  !
142  call this%peek_record()
143  end subroutine read_record
144 
145  !< @brief finalize
146  !<
147  subroutine finalize(this)
148  class(headfilereadertype) :: this
149  close (this%inunit)
150  if (allocated(this%head)) deallocate (this%head)
151  if (allocated(this%header)) deallocate (this%header)
152  if (allocated(this%headernext)) deallocate (this%headernext)
153  end subroutine finalize
154 
155  !> @brief Get a string representation of the head file header.
156  function get_str(this) result(str)
157  class(headfileheadertype), intent(in) :: this
158  character(len=:), allocatable :: str
159  character(len=LENBIGLINE) :: temp
160 
161  write (temp, '(*(G0))') &
162  'Head file header (pos: ', this%pos, &
163  ', kper: ', this%kper, &
164  ', kstp: ', this%kstp, &
165  ', pertim: ', this%pertim, &
166  ', totim: ', this%totim, &
167  ', text: ', trim(this%text), &
168  ', ncol: ', this%ncol, &
169  ', nrow: ', this%nrow, &
170  ', ilay: ', this%ilay, &
171  ')'
172  str = trim(temp)
173  end function get_str
174 
175  subroutine rewind (this)
176  class(headfilereadertype), intent(inout) :: this
177 
178  rewind(this%inunit)
179  this%endoffile = .false.
180  if (allocated(this%header)) deallocate (this%header)
181  if (allocated(this%headernext)) deallocate (this%headernext)
182  allocate (headfileheadertype :: this%header)
183  allocate (headfileheadertype :: this%headernext)
184  this%header%pos = 1
185  this%headernext%pos = 1
186  end subroutine rewind
187 
188 end module headfilereadermodule
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 lenhugeline
maximum length of a huge line
Definition: Constants.f90:16
integer(i4b), parameter lenbigline
maximum length of a big line
Definition: Constants.f90:15
subroutine finalize(this)
subroutine read_record(this, success, iout)
subroutine initialize(this, iu, iout)
subroutine read_header(this, success, iout)
subroutine rewind(this)
character(len=:) function, allocatable get_str(this)
Get a string representation of the head file header.
subroutine, public fseek_stream(iu, offset, whence, status)
Move the file pointer.
This module defines variable data types.
Definition: kind.f90:8