MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
gwf-obs.f90
Go to the documentation of this file.
2 
3  use kindmodule, only: dp, i4b
5  use basedismodule, only: disbasetype
6  use gwficmodule, only: gwfictype
7  use observemodule, only: observetype
8  use obsmodule, only: obstype
9  use simmodule, only: count_errors, store_error, &
11  implicit none
12 
13  private
14  public :: gwfobstype, gwf_obs_cr
15 
16  type, extends(obstype) :: gwfobstype
17  ! -- Private members
18  type(gwfictype), pointer, private :: ic => null() ! initial conditions
19  real(dp), dimension(:), pointer, contiguous, private :: x => null() ! head
20  real(dp), dimension(:), pointer, contiguous, private :: flowja => null() ! intercell flows
21 
22  contains
23 
24  ! -- Public procedures
25  procedure, public :: gwf_obs_ar
26  procedure, public :: obs_bd => gwf_obs_bd
27  procedure, public :: obs_df => gwf_obs_df
28  procedure, public :: obs_rp => gwf_obs_rp
29  procedure, public :: obs_da => gwf_obs_da
30  ! -- Private procedures
31  procedure, private :: set_pointers
32  end type gwfobstype
33 
34 contains
35 
36  !> @brief Create a new GwfObsType object
37  !!
38  !! Create observation object, allocate pointers, initialize values
39  !<
40  subroutine gwf_obs_cr(obs, inobs)
41  ! -- dummy
42  type(gwfobstype), pointer, intent(out) :: obs
43  integer(I4B), pointer, intent(in) :: inobs
44  !
45  allocate (obs)
46  call obs%allocate_scalars()
47  obs%active = .false.
48  obs%inputFilename = ''
49  obs%inUnitObs => inobs
50  !
51  ! -- Return
52  return
53  end subroutine gwf_obs_cr
54 
55  !> @brief Allocate and read
56  !<
57  subroutine gwf_obs_ar(this, ic, x, flowja)
58  ! -- dummy
59  class(gwfobstype), intent(inout) :: this
60  type(gwfictype), pointer, intent(in) :: ic
61  real(DP), dimension(:), pointer, contiguous, intent(in) :: x
62  real(DP), dimension(:), pointer, contiguous, intent(in) :: flowja
63  !
64  ! Call ar method of parent class
65  call this%obs_ar()
66  !
67  ! set pointers
68  call this%set_pointers(ic, x, flowja)
69  !
70  ! -- Return
71  return
72  end subroutine gwf_obs_ar
73 
74  !> @brief Define
75  !<
76  subroutine gwf_obs_df(this, iout, pkgname, filtyp, dis)
77  ! -- dummy
78  class(gwfobstype), intent(inout) :: this
79  integer(I4B), intent(in) :: iout
80  character(len=*), intent(in) :: pkgname
81  character(len=*), intent(in) :: filtyp
82  class(disbasetype), pointer :: dis
83  ! -- local
84  integer(I4B) :: indx
85  !
86  ! Call overridden method of parent class
87  call this%ObsType%obs_df(iout, pkgname, filtyp, dis)
88  !
89  ! -- StoreObsType arguments are: (ObserveType, cumulative, indx);
90  ! indx is returned.
91  !
92  ! -- Store obs type and assign procedure pointer for head observation type
93  call this%StoreObsType('head', .false., indx)
94  this%obsData(indx)%ProcessIdPtr => gwf_process_head_drawdown_obs_id
95  !
96  ! -- Store obs type and assign procedure pointer for drawdown observation type
97  call this%StoreObsType('drawdown', .false., indx)
98  this%obsData(indx)%ProcessIdPtr => gwf_process_head_drawdown_obs_id
99  !
100  ! -- Store obs type and assign procedure pointer for flow-ja-face observation type
101  call this%StoreObsType('flow-ja-face', .true., indx)
102  this%obsData(indx)%ProcessIdPtr => gwf_process_intercell_obs_id
103  !
104  ! -- Return
105  return
106  end subroutine gwf_obs_df
107 
108  !> @brief Save obs
109  !<
110  subroutine gwf_obs_bd(this)
111  ! -- dummy
112  class(gwfobstype), intent(inout) :: this
113  ! -- local
114  integer(I4B) :: i, jaindex, nodenumber
115  real(DP) :: v
116  character(len=100) :: msg
117  class(observetype), pointer :: obsrv => null()
118  !
119  call this%obs_bd_clear()
120  !
121  ! -- iterate through all GWF observations
122  if (this%npakobs > 0) then
123  do i = 1, this%npakobs
124  obsrv => this%pakobs(i)%obsrv
125  nodenumber = obsrv%NodeNumber
126  jaindex = obsrv%JaIndex
127  select case (obsrv%ObsTypeId)
128  case ('HEAD')
129  call this%SaveOneSimval(obsrv, this%x(nodenumber))
130  case ('DRAWDOWN')
131  v = this%ic%strt(nodenumber) - this%x(nodenumber)
132  call this%SaveOneSimval(obsrv, v)
133  case ('FLOW-JA-FACE')
134  call this%SaveOneSimval(obsrv, this%flowja(jaindex))
135  case default
136  msg = 'Error: Unrecognized observation type: '//trim(obsrv%ObsTypeId)
137  call store_error(msg)
138  end select
139  end do
140  !
141  ! -- write summary of error messages
142  if (count_errors() > 0) then
143  call store_error_unit(this%inUnitObs)
144  end if
145  end if
146  !
147  ! -- Return
148  return
149  end subroutine gwf_obs_bd
150 
151  !> @brief Do GWF observations need any checking? If so, add checks here
152  !<
153  subroutine gwf_obs_rp(this)
154  ! -- dummy
155  class(gwfobstype), intent(inout) :: this
156  !
157  ! Do GWF observations need any checking? If so, add checks here
158  !
159  ! -- Return
160  return
161  end subroutine gwf_obs_rp
162 
163  !> @brief Deallocate memory
164  !<
165  subroutine gwf_obs_da(this)
166  ! -- dummy
167  class(gwfobstype), intent(inout) :: this
168  !
169  nullify (this%ic)
170  nullify (this%x)
171  nullify (this%flowja)
172  call this%ObsType%obs_da()
173  !
174  ! -- Return
175  return
176  end subroutine gwf_obs_da
177 
178  !> @brief Set pointers
179  !<
180  subroutine set_pointers(this, ic, x, flowja)
181  ! -- dummy
182  class(gwfobstype), intent(inout) :: this
183  type(gwfictype), pointer, intent(in) :: ic
184  real(DP), dimension(:), pointer, contiguous, intent(in) :: x
185  real(DP), dimension(:), pointer, contiguous, intent(in) :: flowja
186  !
187  this%ic => ic
188  this%x => x
189  this%flowja => flowja
190  !
191  ! -- Return
192  return
193  end subroutine set_pointers
194 
195  ! -- Procedures related to GWF observations (NOT type-bound)
196 
197  !> @brief Calculate drawdown observation when requested
198  !<
199  subroutine gwf_process_head_drawdown_obs_id(obsrv, dis, inunitobs, iout)
200  ! -- dummy
201  type(observetype), intent(inout) :: obsrv
202  class(disbasetype), intent(in) :: dis
203  integer(I4B), intent(in) :: inunitobs
204  integer(I4B), intent(in) :: iout
205  ! -- local
206  integer(I4B) :: nn1
207  integer(I4B) :: icol, istart, istop
208  character(len=LINELENGTH) :: ermsg, string
209  !
210  ! -- Initialize variables
211  string = obsrv%IDstring
212  icol = 1
213  !
214  ! Get node number, with option for ID string to be either node
215  ! number or lay, row, column (when dis is structured).
216  nn1 = dis%noder_from_string(icol, istart, istop, inunitobs, &
217  iout, string, .false.)
218  !
219  if (nn1 > 0) then
220  obsrv%NodeNumber = nn1
221  else
222  ermsg = 'Error reading data from ID string'
223  call store_error(ermsg)
224  call store_error_unit(inunitobs)
225  end if
226  !
227  ! -- Return
228  return
229  end subroutine gwf_process_head_drawdown_obs_id
230 
231  !> @brief Process flow between two cells when requested
232  !<
233  subroutine gwf_process_intercell_obs_id(obsrv, dis, inunitobs, iout)
234  ! -- dummy
235  type(observetype), intent(inout) :: obsrv
236  class(disbasetype), intent(in) :: dis
237  integer(I4B), intent(in) :: inunitobs
238  integer(I4B), intent(in) :: iout
239  ! -- local
240  integer(I4B) :: nn1, nn2
241  integer(I4B) :: icol, istart, istop, jaidx
242  character(len=LINELENGTH) :: ermsg, string
243  ! formats
244 70 format('Error: No connection exists between cells identified in text: ', a)
245  !
246  ! -- Initialize variables
247  string = obsrv%IDstring
248  icol = 1
249  !
250  ! Get node number, with option for ID string to be either node
251  ! number or lay, row, column (when dis is structured).
252  nn1 = dis%noder_from_string(icol, istart, istop, inunitobs, &
253  iout, string, .false.)
254  !
255  if (nn1 > 0) then
256  obsrv%NodeNumber = nn1
257  else
258  ermsg = 'Error reading data from ID string: '//string(istart:istop)
259  call store_error(ermsg)
260  end if
261  !
262  ! Get node number, with option for ID string to be either node
263  ! number or lay, row, column (when dis is structured).
264  nn2 = dis%noder_from_string(icol, istart, istop, inunitobs, &
265  iout, string, .false.)
266  if (nn2 > 0) then
267  obsrv%NodeNumber2 = nn2
268  else
269  ermsg = 'Error reading data from ID string: '//string(istart:istop)
270  call store_error(ermsg)
271  end if
272  !
273  ! -- store JA index
274  jaidx = dis%con%getjaindex(nn1, nn2)
275  if (jaidx == 0) then
276  write (ermsg, 70) trim(string)
277  call store_error(ermsg)
278  end if
279  obsrv%JaIndex = jaidx
280  !
281  if (count_errors() > 0) then
282  call store_error_unit(inunitobs)
283  end if
284  !
285  ! -- Return
286  return
287  end subroutine gwf_process_intercell_obs_id
288 
289 end module gwfobsmodule
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter linelength
maximum length of a standard line
Definition: Constants.f90:44
integer(i4b), parameter maxobstypes
maximum number of observation types
Definition: Constants.f90:47
subroutine gwf_process_head_drawdown_obs_id(obsrv, dis, inunitobs, iout)
Calculate drawdown observation when requested.
Definition: gwf-obs.f90:200
subroutine gwf_obs_da(this)
Deallocate memory.
Definition: gwf-obs.f90:166
subroutine gwf_obs_rp(this)
Do GWF observations need any checking? If so, add checks here.
Definition: gwf-obs.f90:154
subroutine gwf_obs_bd(this)
Save obs.
Definition: gwf-obs.f90:111
subroutine gwf_obs_df(this, iout, pkgname, filtyp, dis)
Define.
Definition: gwf-obs.f90:77
subroutine, public gwf_obs_cr(obs, inobs)
Create a new GwfObsType object.
Definition: gwf-obs.f90:41
subroutine set_pointers(this, ic, x, flowja)
Set pointers.
Definition: gwf-obs.f90:181
subroutine gwf_process_intercell_obs_id(obsrv, dis, inunitobs, iout)
Process flow between two cells when requested.
Definition: gwf-obs.f90:234
subroutine gwf_obs_ar(this, ic, x, flowja)
Allocate and read.
Definition: gwf-obs.f90:58
This module defines variable data types.
Definition: kind.f90:8
This module contains the derived types ObserveType and ObsDataType.
Definition: Observe.f90:15
This module contains the derived type ObsType.
Definition: Obs.f90:127
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