Neko  0.8.1
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-2021, 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.
37  use dofmap, only: dofmap_t
38  use mesh, only: mesh_t
39  use space, only: space_t, gll
40  use utils, only: neko_error
41  use json_utils, only: json_get
42  use json_module, only: json_file, json_core, json_value
43  implicit none
44  private
45 
48  type(point_zone_wrapper_t), allocatable :: point_zones(:)
50  integer, private :: n = 0
52  integer, private :: expansion_size
53  contains
55  procedure, private, pass(this) :: expand
57  procedure, pass(this) :: init => point_zone_registry_init
59  procedure, pass(this) :: free => point_zone_registry_free
61  procedure, pass(this) :: add_point_zone_from_json
63  procedure, pass(this) :: n_point_zones
66  procedure, pass(this) :: get_point_zone_by_index
68  procedure, pass(this) :: get_point_zone_by_name
71  procedure, pass(this) :: get_expansion_size
74  procedure, pass(this) :: get_size
76  procedure, pass(this) :: point_zone_exists
77  generic :: get_point_zone => get_point_zone_by_index, get_point_zone_by_name
78  generic :: add_point_zone => add_point_zone_from_json
79  end type point_zone_registry_t
80 
83 
84 contains
94  subroutine point_zone_registry_init(this, json, msh, expansion_size)
95  class(point_zone_registry_t), intent(inout):: this
96  type(json_file), intent(inout) :: json
97  type(mesh_t), target, intent(inout) :: msh
98  integer, optional, intent(in) :: expansion_size
99 
100  ! Json low-level manipulator.
101  type(json_core) :: core
102  ! Pointer to the source_terms JSON object and the individual sources.
103  type(json_value), pointer :: source_object, source_pointer
104  ! Buffer for serializing the json.
105  character(len=:), allocatable :: buffer
106  ! A single source term as its own json_file.
107  type(json_file) :: source_subdict
108  logical :: found
109  integer :: n_zones, i
110 
111  ! Parameters used to setup the GLL space.
112  integer :: order
113  type(space_t), target :: Xh
114  type(dofmap_t) :: dof
115 
116 
117  call json_get(json, 'case.numerics.polynomial_order', order)
118  order = order + 1 ! add 1 to get poly order
119 
120  if (msh%gdim .eq. 2) then
121  call xh%init(gll, order, order)
122  else
123  call xh%init(gll, order, order, order)
124  end if
125  dof = dofmap_t(msh, xh)
126 
127  call this%free()
128 
129  if (present(expansion_size)) then
130  this%expansion_size = expansion_size
131  else
132  this%expansion_size = 10
133  end if
134 
135  this%n = 0
136 
137  !
138  ! Count if there are any point zones defined in the json
139  !
140  if(json%valid_path('case.point_zones')) then
141 
142  call json%get_core(core)
143  call json%get('case.point_zones', source_object, found)
144 
145  n_zones = core%count(source_object)
146  this%n = n_zones
147 
148  allocate(this%point_zones(n_zones))
149 
150  ! Initialize every point zone
151  do i = 1, n_zones
152  ! Create a new json containing just the subdict for this source.
153  call core%get_child(source_object, i, source_pointer, found)
154  call core%print_to_string(source_pointer, buffer)
155  call source_subdict%load_from_string(buffer)
156 
157  call point_zone_factory(this%point_zones(i)%pz, source_subdict, dof)
158  end do
159  end if
160 
161  end subroutine point_zone_registry_init
162 
164  subroutine point_zone_registry_free(this)
165  class(point_zone_registry_t), intent(inout):: this
166  integer :: i
167 
168  if (allocated(this%point_zones)) then
169 
170  do i=1, this%n_point_zones()
171  call this%point_zones(i)%pz%free()
172  end do
173 
174  deallocate(this%point_zones)
175 
176  end if
177 
178  this%n = 0
179  this%expansion_size = 0
180  end subroutine point_zone_registry_free
181 
183  subroutine expand(this)
184  class(point_zone_registry_t), intent(inout) :: this
185  type(point_zone_wrapper_t), allocatable :: temp(:)
186  integer :: i
187 
188  allocate(temp(this%n + this%expansion_size))
189  temp(1:this%n) = this%point_zones(1:this%n)
190  call move_alloc(temp, this%point_zones)
191 
192  end subroutine expand
193 
197  subroutine add_point_zone_from_json(this, json, dof)
198  class(point_zone_registry_t), intent(inout) :: this
199  type(json_file), intent(inout) :: json
200  type(dofmap_t), target, intent(inout) :: dof
201 ! type(h_cptr_t) :: key
202  character(len=:), allocatable :: str_read
203  integer :: i
204 
205  !
206  ! Allocate the point zones array as it was not necessarily done
207  ! in init
208  !
209  if (.not. allocated(this%point_zones)) then
210  allocate(this%point_zones(this%expansion_size))
211  end if
212 
213  call json_get(json, "name", str_read)
214 
215  ! Check if point zone exists with the input name
216  if (this%point_zone_exists(trim(str_read))) then
217  call neko_error("Field with name " // trim(str_read) // &
218  " is already registered")
219  end if
220 
221  !
222  ! This will always be true if point_zones was allocated in
223  ! init.
224  !
225  if (this%n_point_zones() .eq. this%get_size()) then
226  call this%expand()
227  end if
228 
229  this%n = this%n + 1
230 
231  ! initialize the point_zone at the appropriate index
232  call point_zone_factory(this%point_zones(this%n)%pz, json, dof)
233 
234  ! generate a key for the name lookup map and assign it to the index
235  ! key%ptr = c_loc(fld_name)
236  ! call this%name_index_map%set(key, this%n)
237 
238  ! write(*,*) "HTABLE DATA, ", this%name_index_map%get(key, i)
239  end subroutine add_point_zone_from_json
240 
242  pure function n_point_zones(this) result(n)
243  class(point_zone_registry_t), intent(in) :: this
244  integer :: n
245 
246  n = this%n
247  end function n_point_zones
248 
253  pure function get_size(this) result(n)
254  class(point_zone_registry_t), intent(in) :: this
255  integer :: n
256 
257  n = size(this%point_zones)
258  end function get_size
259 
262  pure function get_expansion_size(this) result(n)
263  class(point_zone_registry_t), intent(in) :: this
264  integer :: n
265 
266  n = this%expansion_size
267  end function get_expansion_size
268 
272  function get_point_zone_by_index(this, i) result(pz)
273  class(point_zone_registry_t), target, intent(in) :: this
274  integer, intent(in) :: i
275  class(point_zone_t), pointer :: pz
276 
277  if (i < 1) then
278  call neko_error("Field index must be > 1")
279  else if (i > this%n_point_zones()) then
280  call neko_error("Field index exceeds number of stored point_zones")
281  endif
282 
283  pz => this%point_zones(i)%pz
284  end function get_point_zone_by_index
285 
288  function get_point_zone_by_name(this, name) result(pz)
289  class(point_zone_registry_t), target, intent(in) :: this
290  character(len=*), intent(in) :: name
291  class(point_zone_t), pointer :: pz
292  logical :: found
293  integer :: i
294 
295  found = .false.
296  do i=1, this%n_point_zones()
297  if (trim(this%point_zones(i)%pz%name) .eq. trim(name)) then
298  pz => this%point_zones(i)%pz
299  found = .true.
300  exit
301  end if
302  end do
303 
304  if (.not. found) then
305  call neko_error("Point zone " // trim(name) // &
306  " could not be found in the registry")
307  end if
308  end function get_point_zone_by_name
309 
312  function point_zone_exists(this, name) result(found)
313  class(point_zone_registry_t), target, intent(in) :: this
314  character(len=*), intent(in) :: name
315  logical :: found
316  integer :: i
317 
318  found = .false.
319  do i=1, this%n_point_zones()
320  if (trim(this%point_zones(i)%pz%name) .eq. trim(name)) then
321  found = .true.
322  exit
323  end if
324  end do
325  end function point_zone_exists
326 
327 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
Defines a factory subroutine for point zones.
subroutine, public point_zone_factory(point_zone, json, dof)
Point zone factory. Constructs, initializes, and maps the point zone 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
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:82
The function space for the SEM solution fields.
Definition: space.f90:62