MODFLOW 6  version 6.5.0.dev2
MODFLOW 6 Code Documentation
VirtualModel.f90
Go to the documentation of this file.
4  use constantsmodule, only: lenmempath
5  use kindmodule, only: i4b, lgp
6  use listmodule, only: listtype
9  implicit none
10  private
11 
12  public :: cast_as_virtual_model
14  public :: get_virtual_model
15 
17  module procedure get_virtual_model_by_id, &
19  end interface
20 
21  type, public, extends(virtualdatacontainertype) :: virtualmodeltype
22  class(numericalmodeltype), pointer :: local_model
23  ! CON
24  type(virtualinttype), pointer :: con_ianglex => null()
25  type(virtualint1dtype), pointer :: con_ia => null()
26  type(virtualint1dtype), pointer :: con_ja => null()
27  type(virtualint1dtype), pointer :: con_jas => null()
28  type(virtualint1dtype), pointer :: con_ihc => null()
29  type(virtualdbl1dtype), pointer :: con_hwva => null()
30  type(virtualdbl1dtype), pointer :: con_cl1 => null()
31  type(virtualdbl1dtype), pointer :: con_cl2 => null()
32  type(virtualdbl1dtype), pointer :: con_anglex => null()
33  ! DIS
34  type(virtualinttype), pointer :: dis_ndim => null()
35  type(virtualinttype), pointer :: dis_nodes => null()
36  type(virtualinttype), pointer :: dis_nodesuser => null()
37  type(virtualint1dtype), pointer :: dis_nodeuser => null()
38  type(virtualinttype), pointer :: dis_nja => null()
39  type(virtualinttype), pointer :: dis_njas => null()
40  type(virtualdbltype), pointer :: dis_xorigin => null()
41  type(virtualdbltype), pointer :: dis_yorigin => null()
42  type(virtualdbltype), pointer :: dis_angrot => null()
43  type(virtualdbl1dtype), pointer :: dis_xc => null()
44  type(virtualdbl1dtype), pointer :: dis_yc => null()
45  type(virtualdbl1dtype), pointer :: dis_top => null()
46  type(virtualdbl1dtype), pointer :: dis_bot => null()
47  type(virtualdbl1dtype), pointer :: dis_area => null()
48  ! Numerical Model fields
49  type(virtualinttype), pointer :: moffset => null()
50  type(virtualdbl1dtype), pointer :: x => null()
51  type(virtualdbl1dtype), pointer :: x_old => null()
52  type(virtualint1dtype), pointer :: ibound => null()
53  ! Base Model fields
54  type(virtualinttype), pointer :: idsoln => null()
55  contains
56  ! public
57  procedure :: create => vm_create
58  procedure :: prepare_stage => vm_prepare_stage
59  procedure :: destroy => vm_destroy
60  generic :: operator(==) => eq_virtual_model, eq_numerical_model
61 
62  procedure :: dis_get_nodeuser
63  procedure :: dis_noder_to_string
64 
65  ! private
66  procedure, private :: init_virtual_data
67  procedure, private :: allocate_data
68  procedure, private :: deallocate_data
69  procedure, private :: eq_virtual_model
70  procedure, private :: eq_numerical_model
71  end type virtualmodeltype
72 
73 contains
74 
75  subroutine vm_create(this, name, id, model)
76  class(virtualmodeltype) :: this
77  character(len=*) :: name
78  integer(I4B) :: id
79  class(numericalmodeltype), pointer :: model
80  ! local
81  logical(LGP) :: is_local
82 
83  is_local = associated(model)
84  call this%VirtualDataContainerType%vdc_create(name, id, is_local)
85 
86  this%local_model => model
87 
88  call this%allocate_data()
89  call this%init_virtual_data()
90 
91  end subroutine vm_create
92 
93  subroutine init_virtual_data(this)
94  class(virtualmodeltype) :: this
95 
96  ! CON
97  call this%set(this%con_ianglex%base(), 'IANGLEX', 'CON', map_all_type)
98  call this%set(this%con_ia%base(), 'IA', 'CON', map_all_type)
99  call this%set(this%con_ja%base(), 'JA', 'CON', map_all_type)
100  call this%set(this%con_jas%base(), 'JAS', 'CON', map_all_type)
101  call this%set(this%con_ihc%base(), 'IHC', 'CON', map_all_type)
102  call this%set(this%con_hwva%base(), 'HWVA', 'CON', map_all_type)
103  call this%set(this%con_cl1%base(), 'CL1', 'CON', map_all_type)
104  call this%set(this%con_cl2%base(), 'CL2', 'CON', map_all_type)
105  call this%set(this%con_anglex%base(), 'ANGLEX', 'CON', map_all_type)
106  ! DIS
107  call this%set(this%dis_ndim%base(), 'NDIM', 'DIS', map_all_type)
108  call this%set(this%dis_nodes%base(), 'NODES', 'DIS', map_all_type)
109  call this%set(this%dis_nodesuser%base(), 'NODESUSER', 'DIS', map_all_type)
110  call this%set(this%dis_nodeuser%base(), 'NODEUSER', 'DIS', map_all_type)
111  call this%set(this%dis_nja%base(), 'NJA', 'DIS', map_all_type)
112  call this%set(this%dis_njas%base(), 'NJAS', 'DIS', map_all_type)
113  call this%set(this%dis_xorigin%base(), 'XORIGIN', 'DIS', map_all_type)
114  call this%set(this%dis_yorigin%base(), 'YORIGIN', 'DIS', map_all_type)
115  call this%set(this%dis_angrot%base(), 'ANGROT', 'DIS', map_all_type)
116  call this%set(this%dis_xc%base(), 'XC', 'DIS', map_all_type)
117  call this%set(this%dis_yc%base(), 'YC', 'DIS', map_all_type)
118  call this%set(this%dis_top%base(), 'TOP', 'DIS', map_all_type)
119  call this%set(this%dis_bot%base(), 'BOT', 'DIS', map_all_type)
120  call this%set(this%dis_area%base(), 'AREA', 'DIS', map_all_type)
121  ! Numerical model
122  call this%set(this%moffset%base(), 'MOFFSET', '', map_all_type)
123  call this%set(this%x%base(), 'X', '', map_node_type)
124  call this%set(this%x_old%base(), 'XOLD', '', map_node_type)
125  call this%set(this%ibound%base(), 'IBOUND', '', map_node_type)
126  ! Base model
127  call this%set(this%idsoln%base(), 'IDSOLN', '', map_all_type)
128 
129  end subroutine init_virtual_data
130 
131  subroutine vm_prepare_stage(this, stage)
132  class(virtualmodeltype) :: this
133  integer(I4B) :: stage
134  ! local
135  integer(I4B) :: nodes, nodesuser, nja, njas
136  logical(LGP) :: is_reduced
137 
138  if (stage == stg_aft_mdl_df) then
139 
140  call this%map(this%idsoln%base(), (/stg_aft_mdl_df/))
141  call this%map(this%con_ianglex%base(), (/stg_aft_mdl_df/))
142  call this%map(this%dis_ndim%base(), (/stg_aft_mdl_df/))
143  call this%map(this%dis_nodes%base(), (/stg_aft_mdl_df/))
144  call this%map(this%dis_nodesuser%base(), (/stg_aft_mdl_df/))
145  call this%map(this%dis_nja%base(), (/stg_aft_mdl_df/))
146  call this%map(this%dis_njas%base(), (/stg_aft_mdl_df/))
147 
148  else if (stage == stg_bfr_exg_ac) then
149 
150  nodes = this%dis_nodes%get()
151  nodesuser = this%dis_nodesuser%get()
152  is_reduced = (nodes /= nodesuser)
153  call this%map(this%moffset%base(), (/stg_bfr_exg_ac/))
154  if (is_reduced) then
155  call this%map(this%dis_nodeuser%base(), nodes, (/stg_bfr_exg_ac/))
156  else
157  ! no reduction, zero sized array, never synchronize
158  call this%map(this%dis_nodeuser%base(), 0, (/stg_never/))
159  end if
160 
161  else if (stage == stg_bfr_con_df) then
162 
163  nodes = this%dis_nodes%get()
164  nja = this%dis_nja%get()
165  njas = this%dis_njas%get()
166  ! DIS
167  call this%map(this%dis_xorigin%base(), (/stg_bfr_con_df/))
168  call this%map(this%dis_yorigin%base(), (/stg_bfr_con_df/))
169  call this%map(this%dis_angrot%base(), (/stg_bfr_con_df/))
170  call this%map(this%dis_xc%base(), nodes, (/stg_bfr_con_df/))
171  call this%map(this%dis_yc%base(), nodes, (/stg_bfr_con_df/))
172  call this%map(this%dis_top%base(), nodes, (/stg_bfr_con_df/))
173  call this%map(this%dis_bot%base(), nodes, (/stg_bfr_con_df/))
174  call this%map(this%dis_area%base(), nodes, (/stg_bfr_con_df/))
175  ! CON
176  call this%map(this%con_ia%base(), nodes + 1, (/stg_bfr_con_df/))
177  call this%map(this%con_ja%base(), nja, (/stg_bfr_con_df/))
178  call this%map(this%con_jas%base(), nja, (/stg_bfr_con_df/))
179  call this%map(this%con_ihc%base(), njas, (/stg_bfr_con_df/))
180  call this%map(this%con_hwva%base(), njas, (/stg_bfr_con_df/))
181  call this%map(this%con_cl1%base(), njas, (/stg_bfr_con_df/))
182  call this%map(this%con_cl2%base(), njas, (/stg_bfr_con_df/))
183  if (this%con_ianglex%get() > 0) then
184  call this%map(this%con_anglex%base(), njas, (/stg_bfr_con_df/))
185  else
186  call this%map(this%con_anglex%base(), 0, (/stg_never/))
187  end if
188 
189  end if
190 
191  end subroutine vm_prepare_stage
192 
193  !> @brief Get user node number from reduced number
194  !<
195  function dis_get_nodeuser(this, node_reduced) result(node_user)
196  class(virtualmodeltype) :: this !< this virtual model
197  integer(I4B), intent(in) :: node_reduced !< the reduced node number
198  integer(I4B) :: node_user !< the returned user node number
199 
200  if (this%dis_nodes%get() < this%dis_nodesuser%get()) then
201  node_user = this%dis_nodeuser%get(node_reduced)
202  else
203  node_user = node_reduced
204  end if
205 
206  end function dis_get_nodeuser
207 
208  subroutine dis_noder_to_string(this, node_reduced, node_str)
209  class(virtualmodeltype) :: this !< this virtual model
210  integer(I4B), intent(in) :: node_reduced !< reduced node number
211  character(len=*), intent(inout) :: node_str !< the string representative of the user node number
212  ! local
213  character(len=11) :: nr_str
214 
215  if (this%is_local) then
216  call this%local_model%dis%noder_to_string(node_reduced, node_str)
217  else
218  ! for now this will look like: (102r)
219  write (nr_str, '(i0)') node_reduced
220  node_str = '('//trim(adjustl(nr_str))//'r)'
221  end if
222 
223  end subroutine dis_noder_to_string
224 
225  subroutine vm_destroy(this)
226  class(virtualmodeltype) :: this
227 
228  call this%VirtualDataContainerType%destroy()
229  call this%deallocate_data()
230 
231  end subroutine vm_destroy
232 
233  subroutine allocate_data(this)
234  class(virtualmodeltype) :: this
235 
236  allocate (this%con_ianglex)
237  allocate (this%con_ia)
238  allocate (this%con_ja)
239  allocate (this%con_jas)
240  allocate (this%con_ihc)
241  allocate (this%con_hwva)
242  allocate (this%con_cl1)
243  allocate (this%con_cl2)
244  allocate (this%con_anglex)
245  allocate (this%dis_ndim)
246  allocate (this%dis_nodes)
247  allocate (this%dis_nodesuser)
248  allocate (this%dis_nodeuser)
249  allocate (this%dis_nja)
250  allocate (this%dis_njas)
251  allocate (this%dis_xorigin)
252  allocate (this%dis_yorigin)
253  allocate (this%dis_angrot)
254  allocate (this%dis_xc)
255  allocate (this%dis_yc)
256  allocate (this%dis_top)
257  allocate (this%dis_bot)
258  allocate (this%dis_area)
259  allocate (this%moffset)
260  allocate (this%x)
261  allocate (this%x_old)
262  allocate (this%ibound)
263  allocate (this%idsoln)
264 
265  end subroutine allocate_data
266 
267  subroutine deallocate_data(this)
268  class(virtualmodeltype) :: this
269 
270  ! CON
271  deallocate (this%con_ianglex)
272  deallocate (this%con_ia)
273  deallocate (this%con_ja)
274  deallocate (this%con_jas)
275  deallocate (this%con_ihc)
276  deallocate (this%con_hwva)
277  deallocate (this%con_cl1)
278  deallocate (this%con_cl2)
279  deallocate (this%con_anglex)
280  ! DIS
281  deallocate (this%dis_ndim)
282  deallocate (this%dis_nodes)
283  deallocate (this%dis_nodeuser)
284  deallocate (this%dis_nja)
285  deallocate (this%dis_njas)
286  deallocate (this%dis_xorigin)
287  deallocate (this%dis_yorigin)
288  deallocate (this%dis_angrot)
289  deallocate (this%dis_xc)
290  deallocate (this%dis_yc)
291  deallocate (this%dis_top)
292  deallocate (this%dis_bot)
293  deallocate (this%dis_area)
294  ! Numerical model
295  deallocate (this%moffset)
296  deallocate (this%x)
297  deallocate (this%x_old)
298  deallocate (this%ibound)
299  ! Base model
300  deallocate (this%idsoln)
301 
302  end subroutine deallocate_data
303 
304  function get_virtual_model_from_list(model_list, idx) result(v_model)
305  type(listtype) :: model_list
306  integer(I4B) :: idx
307  class(virtualmodeltype), pointer :: v_model
308  ! local
309  class(*), pointer :: obj_ptr
310 
311  obj_ptr => model_list%GetItem(idx)
312  v_model => cast_as_virtual_model(obj_ptr)
313  return
314 
315  end function get_virtual_model_from_list
316 
317  function cast_as_virtual_model(obj_ptr) result(v_model)
318  class(*), pointer :: obj_ptr
319  class(virtualmodeltype), pointer :: v_model
320 
321  v_model => null()
322  select type (obj_ptr)
323  class is (virtualmodeltype)
324  v_model => obj_ptr
325  end select
326 
327  end function cast_as_virtual_model
328 
329  function eq_virtual_model(this, v_model) result(is_equal)
330  class(virtualmodeltype), intent(in) :: this
331  class(virtualmodeltype), intent(in) :: v_model
332  logical(LGP) :: is_equal
333 
334  is_equal = (this%id == v_model%id)
335 
336  end function eq_virtual_model
337 
338  function eq_numerical_model(this, num_model) result(is_equal)
339  class(virtualmodeltype), intent(in) :: this
340  class(numericalmodeltype), intent(in) :: num_model
341  logical(LGP) :: is_equal
342 
343  is_equal = (this%id == num_model%id)
344 
345  end function eq_numerical_model
346 
347  !> @brief Returns a virtual model with the specified id
348  !< from the global list, or null
349  function get_virtual_model_by_id(model_id) result(virtual_model)
351  integer(I4B) :: model_id
352  class(virtualmodeltype), pointer :: virtual_model
353  ! local
354  integer(I4B) :: i
355  class(*), pointer :: vm
356 
357  virtual_model => null()
358  do i = 1, virtual_model_list%Count()
359  vm => virtual_model_list%GetItem(i)
360  select type (vm)
361  class is (virtualmodeltype)
362  if (vm%id == model_id) then
363  virtual_model => vm
364  return
365  end if
366  end select
367  end do
368 
369  end function get_virtual_model_by_id
370 
371  !> @brief Returns a virtual model with the specified name
372  !< from the global list, or null
373  function get_virtual_model_by_name(model_name) result(virtual_model)
375  character(len=*) :: model_name
376  class(virtualmodeltype), pointer :: virtual_model
377  ! local
378  integer(I4B) :: i
379  class(*), pointer :: vm
380 
381  virtual_model => null()
382  do i = 1, virtual_model_list%Count()
383  vm => virtual_model_list%GetItem(i)
384  select type (vm)
385  class is (virtualmodeltype)
386  if (vm%name == model_name) then
387  virtual_model => vm
388  return
389  end if
390  end select
391  end do
392 
393  end function get_virtual_model_by_name
394 
395 end module virtualmodelmodule
This module contains simulation constants.
Definition: Constants.f90:9
integer(i4b), parameter lenmempath
maximum length of the memory path
Definition: Constants.f90:26
This module defines variable data types.
Definition: kind.f90:8
integer(i4b), parameter, public stg_aft_mdl_df
after model define
Definition: SimStages.f90:11
integer(i4b), parameter, public stg_never
never
Definition: SimStages.f90:9
integer(i4b), parameter, public stg_bfr_exg_ac
before exchange add connections (per solution)
Definition: SimStages.f90:16
integer(i4b), parameter, public stg_bfr_con_df
before connection define
Definition: SimStages.f90:14
integer(i4b), parameter, public map_all_type
Definition: VirtualBase.f90:13
integer(i4b), parameter, public map_node_type
Definition: VirtualBase.f90:14
type(listtype), public virtual_model_list
class(virtualmodeltype) function, pointer, public cast_as_virtual_model(obj_ptr)
logical(lgp) function eq_virtual_model(this, v_model)
subroutine vm_prepare_stage(this, stage)
subroutine vm_create(this, name, id, model)
integer(i4b) function dis_get_nodeuser(this, node_reduced)
Get user node number from reduced number.
class(virtualmodeltype) function, pointer get_virtual_model_by_id(model_id)
Returns a virtual model with the specified id.
subroutine deallocate_data(this)
subroutine init_virtual_data(this)
logical(lgp) function eq_numerical_model(this, num_model)
class(virtualmodeltype) function, pointer get_virtual_model_by_name(model_name)
Returns a virtual model with the specified name.
subroutine vm_destroy(this)
subroutine dis_noder_to_string(this, node_reduced, node_str)
subroutine allocate_data(this)
class(virtualmodeltype) function, pointer, public get_virtual_model_from_list(model_list, idx)
A generic heterogeneous doubly-linked list.
Definition: List.f90:10