Neko 1.99.1
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
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
82
85
86contains
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 call dof%init(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 call xh%free()
189 call dof%free()
190
191 end subroutine point_zone_registry_init
192
199 subroutine build_combine_point_zone(object, json, dof)
200 class(point_zone_t), allocatable, target, intent(inout) :: object
201 type(json_file), intent(inout) :: json
202 type(dofmap_t), intent(inout) :: dof
203
204 type(combine_point_zone_t), pointer :: cpz
205 integer :: i, i_external
206
207 allocate(combine_point_zone_t::object)
208
209 ! Here we initialize all the names of the zones to combine
210 call object%init(json, dof%size())
211
212 select type (object)
213 type is (combine_point_zone_t)
214 cpz => object
215 class default
216 end select
217
218 i_external = 1
219 ! Load the external zones in the combine zone array
220 do i = cpz%n_internal_zones + 1, cpz%n_zones
221 cpz%zones(i)%pz => &
222 neko_point_zone_registry%get_point_zone(cpz%names(i_external))
223 end do
224
225 call object%map(dof)
226 call object%finalize()
227
228 end subroutine build_combine_point_zone
229
232 class(point_zone_registry_t), intent(inout) :: this
233 integer :: i
234
235 if (allocated(this%point_zones)) then
236
237 do i = 1, this%n_point_zones()
238 call this%point_zones(i)%pz%free()
239 end do
240
241 deallocate(this%point_zones)
242
243 end if
244
245 this%n = 0
246 this%expansion_size = 0
247 end subroutine point_zone_registry_free
248
250 subroutine expand(this)
251 class(point_zone_registry_t), intent(inout) :: this
252 type(point_zone_wrapper_t), allocatable :: temp(:)
253
254 allocate(temp(this%n + this%expansion_size))
255 temp(1:this%n) = this%point_zones(1:this%n)
256 call move_alloc(temp, this%point_zones)
257
258 end subroutine expand
259
263 subroutine add_point_zone_from_json(this, json, dof)
264 class(point_zone_registry_t), intent(inout) :: this
265 type(json_file), intent(inout) :: json
266 type(dofmap_t), target, intent(inout) :: dof
267! type(h_cptr_t) :: key
268 character(len=:), allocatable :: str_read
269
270 !
271 ! Allocate the point zones array as it was not necessarily done
272 ! in init
273 !
274 if (.not. allocated(this%point_zones)) then
275 allocate(this%point_zones(this%expansion_size))
276 end if
277
278 call json_get(json, "name", str_read)
279
280 ! Check if point zone exists with the input name
281 if (this%point_zone_exists(trim(str_read))) then
282 call neko_error("Field with name " // trim(str_read) // &
283 " is already registered")
284 end if
285
286 !
287 ! This will always be true if point_zones was allocated in
288 ! init.
289 !
290 if (this%n_point_zones() .eq. this%get_size()) then
291 call this%expand()
292 end if
293
294 this%n = this%n + 1
295
296 ! initialize the point_zone at the appropriate index
297 call point_zone_factory(this%point_zones(this%n)%pz, json, dof)
298
299 ! generate a key for the name lookup map and assign it to the index
300 ! key%ptr = c_loc(fld_name)
301 ! call this%name_index_map%set(key, this%n)
302
303 ! write(*,*) "HTABLE DATA, ", this%name_index_map%get(key, i)
304 end subroutine add_point_zone_from_json
305
307 pure function n_point_zones(this) result(n)
308 class(point_zone_registry_t), intent(in) :: this
309 integer :: n
310
311 n = this%n
312 end function n_point_zones
313
318 pure function get_size(this) result(n)
319 class(point_zone_registry_t), intent(in) :: this
320 integer :: n
321
322 n = size(this%point_zones)
323 end function get_size
324
327 pure function get_expansion_size(this) result(n)
328 class(point_zone_registry_t), intent(in) :: this
329 integer :: n
330
331 n = this%expansion_size
332 end function get_expansion_size
333
337 function get_point_zone_by_index(this, i) result(pz)
338 class(point_zone_registry_t), target, intent(in) :: this
339 integer, intent(in) :: i
340 class(point_zone_t), pointer :: pz
341
342 if (i < 1) then
343 call neko_error("Field index must be > 1")
344 else if (i > this%n_point_zones()) then
345 call neko_error("Field index exceeds number of stored point_zones")
346 end if
347
348 pz => this%point_zones(i)%pz
349 end function get_point_zone_by_index
350
353 function get_point_zone_by_name(this, name) result(pz)
354 class(point_zone_registry_t), target, intent(in) :: this
355 character(len=*), intent(in) :: name
356 class(point_zone_t), pointer :: pz
357 logical :: found
358 integer :: i
359
360 found = .false.
361 do i = 1, this%n_point_zones()
362 if (trim(this%point_zones(i)%pz%name) .eq. trim(name)) then
363 pz => this%point_zones(i)%pz
364 found = .true.
365 exit
366 end if
367 end do
368
369 if (.not. found) then
370 call neko_error("Point zone " // trim(name) // &
371 " could not be found in the registry")
372 end if
373 end function get_point_zone_by_name
374
377 function point_zone_exists(this, name) result(found)
378 class(point_zone_registry_t), target, intent(in) :: this
379 character(len=*), intent(in) :: name
380 logical :: found
381 integer :: i
382
383 found = .false.
384 do i = 1, this%n_point_zones()
385 if (trim(this%point_zones(i)%pz%name) .eq. trim(name)) then
386 found = .true.
387 exit
388 end if
389 end do
390 end function point_zone_exists
391
392end module point_zone_registry
Retrieves a parameter by name or throws an error.
Generic buffer that is extended with buffers of varying rank.
Definition buffer.F90:34
Defines a mapping of the degrees of freedom.
Definition dofmap.f90:35
Utilities for retrieving parameters from the case files.
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:49
Utilities.
Definition utils.f90:35
A point zone that combines different point zones.
Base abstract type for point zones.
A helper type to build a list of polymorphic point_zones.
The function space for the SEM solution fields.
Definition space.f90:63