Neko  0.8.99
A portable framework for high-order spectral element flow simulations
point_zone_registry.f90
Go to the documentation of this file.
1 ! Copyright (c) 2019-2024, The Neko Authors
2 ! All rights reserved.
3 !
4 ! Redistribution and use in source and binary forms, with or without
5 ! modification, are permitted provided that the following conditions
6 ! are met:
7 !
8 ! * Redistributions of source code must retain the above copyright
9 ! notice, this list of conditions and the following disclaimer.
10 !
11 ! * Redistributions in binary form must reproduce the above
12 ! copyright notice, this list of conditions and the following
13 ! disclaimer in the documentation and/or other materials provided
14 ! with the distribution.
15 !
16 ! * Neither the name of the authors nor the names of its
17 ! contributors may be used to endorse or promote products derived
18 ! from this software without specific prior written permission.
19 !
20 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21 ! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22 ! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
23 ! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
24 ! COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
25 ! INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
26 ! BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
27 ! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
28 ! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
29 ! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
30 ! ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
31 ! POSSIBILITY OF SUCH DAMAGE.
32 !
33 ! Implements a point zone registry for storing point zones.
36  point_zone_factory
38  use dofmap, only : dofmap_t
39  use mesh, only : mesh_t
40  use space, only : space_t, gll
41  use utils, only : neko_error
42  use json_utils, only : json_get
43  use json_module, only : json_file, json_core, json_value
44  implicit none
45  private
46 
49  type(point_zone_wrapper_t), allocatable :: point_zones(:)
51  integer, private :: n = 0
53  integer, private :: expansion_size
54  contains
56  procedure, private, pass(this) :: expand
58  procedure, pass(this) :: init => point_zone_registry_init
60  procedure, pass(this) :: free => point_zone_registry_free
62  procedure, pass(this) :: add_point_zone_from_json
64  procedure, pass(this) :: n_point_zones
67  procedure, pass(this) :: get_point_zone_by_index
69  procedure, pass(this) :: get_point_zone_by_name
72  procedure, pass(this) :: get_expansion_size
75  procedure, pass(this) :: get_size
77  procedure, pass(this) :: point_zone_exists
78  generic :: get_point_zone => get_point_zone_by_index, &
80  generic :: add_point_zone => add_point_zone_from_json
81  end type point_zone_registry_t
82 
85 
86 contains
96  subroutine point_zone_registry_init(this, json, msh, expansion_size)
97  class(point_zone_registry_t), intent(inout) :: this
98  type(json_file), intent(inout) :: json
99  type(mesh_t), target, intent(inout) :: msh
100  integer, optional, intent(in) :: expansion_size
101 
102  ! Json low-level manipulator.
103  type(json_core) :: core
104  ! Pointer to the source_terms JSON object and the individual sources.
105  type(json_value), pointer :: source_object, source_pointer
106  ! Buffer for serializing the json.
107  character(len=:), allocatable :: buffer
108  ! A single source term as its own json_file.
109  type(json_file) :: source_subdict
110  logical :: found
111  integer :: n_zones, i, izone
112  character(len=:), allocatable :: type_name
113 
114  ! Parameters used to setup the GLL space.
115  integer :: order
116  type(space_t), target :: Xh
117  type(dofmap_t) :: dof
118 
119 
120  call json_get(json, 'case.numerics.polynomial_order', order)
121  order = order + 1 ! add 1 to get poly order
122 
123  if (msh%gdim .eq. 2) then
124  call xh%init(gll, order, order)
125  else
126  call xh%init(gll, order, order, order)
127  end if
128  dof = dofmap_t(msh, xh)
129 
130  call this%free()
131 
132  if (present(expansion_size)) then
133  this%expansion_size = expansion_size
134  else
135  this%expansion_size = 10
136  end if
137 
138  this%n = 0
139 
140  !
141  ! Count if there are any point zones defined in the json
142  !
143  if (json%valid_path('case.point_zones')) then
144 
145  call json%get_core(core)
146  call json%get('case.point_zones', source_object, found)
147 
148  n_zones = core%count(source_object)
149  this%n = n_zones
150 
151  allocate(this%point_zones(n_zones))
152 
153  ! Initialize all the primitive zones
154  izone = 1
155  do i = 1, n_zones
156 
157  ! Create a new json containing just the subdict for this source.
158  call core%get_child(source_object, i, source_pointer, found)
159  call core%print_to_string(source_pointer, buffer)
160  call source_subdict%load_from_string(buffer)
161 
162  call json_get(source_subdict, "geometry", type_name)
163  if (trim(type_name) .ne. "combine") then
164  call point_zone_factory(this%point_zones(izone)%pz, &
165  source_subdict, dof)
166  izone = izone + 1
167  end if
168  end do
169 
170  ! Now initialize the combine zones
171  do i = 1, n_zones
172 
173  ! Create a new json containing just the subdict for this source.
174  call core%get_child(source_object, i, source_pointer, found)
175  call core%print_to_string(source_pointer, buffer)
176  call source_subdict%load_from_string(buffer)
177 
178  call json_get(source_subdict, "geometry", type_name)
179  if (trim(type_name) .eq. "combine") then
180  call build_combine_point_zone(this%point_zones(izone)%pz, &
181  source_subdict, dof)
182  izone = izone + 1
183  end if
184  end do
185 
186  end if
187 
188  end subroutine point_zone_registry_init
189 
196  subroutine build_combine_point_zone(object, json, dof)
197  class(point_zone_t), allocatable, target, intent(inout) :: object
198  type(json_file), intent(inout) :: json
199  type(dofmap_t), intent(inout) :: dof
200 
201  type(combine_point_zone_t), pointer :: cpz
202  integer :: i, i_external
203 
204  allocate(combine_point_zone_t::object)
205 
206  ! Here we initialize all the names of the zones to combine
207  call object%init(json, dof%size())
208 
209  select type (object)
210  type is (combine_point_zone_t)
211  cpz => object
212  class default
213  end select
214 
215  i_external = 1
216  ! Load the external zones in the combine zone array
217  do i = cpz%n_internal_zones + 1, cpz%n_zones
218  cpz%zones(i)%pz => &
219  neko_point_zone_registry%get_point_zone(cpz%names(i_external))
220  end do
221 
222  call object%map(dof)
223  call object%finalize()
224 
225  end subroutine build_combine_point_zone
226 
228  subroutine point_zone_registry_free(this)
229  class(point_zone_registry_t), intent(inout) :: this
230  integer :: i
231 
232  if (allocated(this%point_zones)) then
233 
234  do i = 1, this%n_point_zones()
235  call this%point_zones(i)%pz%free()
236  end do
237 
238  deallocate(this%point_zones)
239 
240  end if
241 
242  this%n = 0
243  this%expansion_size = 0
244  end subroutine point_zone_registry_free
245 
247  subroutine expand(this)
248  class(point_zone_registry_t), intent(inout) :: this
249  type(point_zone_wrapper_t), allocatable :: temp(:)
250  integer :: i
251 
252  allocate(temp(this%n + this%expansion_size))
253  temp(1:this%n) = this%point_zones(1:this%n)
254  call move_alloc(temp, this%point_zones)
255 
256  end subroutine expand
257 
261  subroutine add_point_zone_from_json(this, json, dof)
262  class(point_zone_registry_t), intent(inout) :: this
263  type(json_file), intent(inout) :: json
264  type(dofmap_t), target, intent(inout) :: dof
265 ! type(h_cptr_t) :: key
266  character(len=:), allocatable :: str_read
267  integer :: i
268 
269  !
270  ! Allocate the point zones array as it was not necessarily done
271  ! in init
272  !
273  if (.not. allocated(this%point_zones)) then
274  allocate(this%point_zones(this%expansion_size))
275  end if
276 
277  call json_get(json, "name", str_read)
278 
279  ! Check if point zone exists with the input name
280  if (this%point_zone_exists(trim(str_read))) then
281  call neko_error("Field with name " // trim(str_read) // &
282  " is already registered")
283  end if
284 
285  !
286  ! This will always be true if point_zones was allocated in
287  ! init.
288  !
289  if (this%n_point_zones() .eq. this%get_size()) then
290  call this%expand()
291  end if
292 
293  this%n = this%n + 1
294 
295  ! initialize the point_zone at the appropriate index
296  call point_zone_factory(this%point_zones(this%n)%pz, json, dof)
297 
298  ! generate a key for the name lookup map and assign it to the index
299  ! key%ptr = c_loc(fld_name)
300  ! call this%name_index_map%set(key, this%n)
301 
302  ! write(*,*) "HTABLE DATA, ", this%name_index_map%get(key, i)
303  end subroutine add_point_zone_from_json
304 
306  pure function n_point_zones(this) result(n)
307  class(point_zone_registry_t), intent(in) :: this
308  integer :: n
309 
310  n = this%n
311  end function n_point_zones
312 
317  pure function get_size(this) result(n)
318  class(point_zone_registry_t), intent(in) :: this
319  integer :: n
320 
321  n = size(this%point_zones)
322  end function get_size
323 
326  pure function get_expansion_size(this) result(n)
327  class(point_zone_registry_t), intent(in) :: this
328  integer :: n
329 
330  n = this%expansion_size
331  end function get_expansion_size
332 
336  function get_point_zone_by_index(this, i) result(pz)
337  class(point_zone_registry_t), target, intent(in) :: this
338  integer, intent(in) :: i
339  class(point_zone_t), pointer :: pz
340 
341  if (i < 1) then
342  call neko_error("Field index must be > 1")
343  else if (i > this%n_point_zones()) then
344  call neko_error("Field index exceeds number of stored point_zones")
345  end if
346 
347  pz => this%point_zones(i)%pz
348  end function get_point_zone_by_index
349 
352  function get_point_zone_by_name(this, name) result(pz)
353  class(point_zone_registry_t), target, intent(in) :: this
354  character(len=*), intent(in) :: name
355  class(point_zone_t), pointer :: pz
356  logical :: found
357  integer :: i
358 
359  found = .false.
360  do i = 1, this%n_point_zones()
361  if (trim(this%point_zones(i)%pz%name) .eq. trim(name)) then
362  pz => this%point_zones(i)%pz
363  found = .true.
364  exit
365  end if
366  end do
367 
368  if (.not. found) then
369  call neko_error("Point zone " // trim(name) // &
370  " could not be found in the registry")
371  end if
372  end function get_point_zone_by_name
373 
376  function point_zone_exists(this, name) result(found)
377  class(point_zone_registry_t), target, intent(in) :: this
378  character(len=*), intent(in) :: name
379  logical :: found
380  integer :: i
381 
382  found = .false.
383  do i = 1, this%n_point_zones()
384  if (trim(this%point_zones(i)%pz%name) .eq. trim(name)) then
385  found = .true.
386  exit
387  end if
388  end do
389  end function point_zone_exists
390 
391 end module point_zone_registry
Retrieves a parameter by name or throws an error.
Definition: json_utils.f90:44
Defines a mapping of the degrees of freedom.
Definition: dofmap.f90:35
Utilities for retrieving parameters from the case files.
Definition: json_utils.f90:34
Defines a mesh.
Definition: mesh.f90:34
subroutine build_combine_point_zone(object, json, dof)
Constructs a combine_point_zone_t object.
subroutine expand(this)
Expand the point_zones array so as to accomodate more point_zones.
subroutine point_zone_registry_free(this)
Destructor.
pure integer function n_point_zones(this)
Returns the number of point zones in the registry.
subroutine point_zone_registry_init(this, json, msh, expansion_size)
Constructor, reading from json point zones.
logical function point_zone_exists(this, name)
Checks if a point zone exists in the registry.
pure integer function get_size(this)
Returns the total size of the point_zones array (not the number of point zones in the registry!...
type(point_zone_registry_t), target, public neko_point_zone_registry
Global point_zone registry.
subroutine add_point_zone_from_json(this, json, dof)
Adds a point zone object to the registry from a json object.
class(point_zone_t) function, pointer get_point_zone_by_name(this, name)
Retrieves a point zone in the registry by its name.
pure integer function get_expansion_size(this)
Returns the expansion size with which the point_zone_registry_t was initialized.
class(point_zone_t) function, pointer get_point_zone_by_index(this, i)
Retrieves a point zone in the registry by its index in the point_zones array.
Defines a function space.
Definition: space.f90:34
integer, parameter, public gll
Definition: space.f90:48
Utilities.
Definition: utils.f90:35
A point zone that combines different point zones.
Base abstract type for point zones.
Definition: point_zone.f90:47
A helper type to build a list of polymorphic point_zones.
Definition: point_zone.f90:84
The function space for the SEM solution fields.
Definition: space.f90:62