Neko 0.9.99
A portable framework for high-order spectral element flow simulations
Loading...
Searching...
No Matches
point_zone.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 zone as a subset of GLL points in the mesh
35 use stack, only: stack_i4_t
36 use num_types, only: rp
38 use dofmap, only: dofmap_t
39 use json_module, only: json_file
41 use device
42 use, intrinsic :: iso_c_binding, only: c_ptr, c_null_ptr, c_associated
43 implicit none
44 private
45
47 type, public, abstract :: point_zone_t
49 integer, allocatable :: mask(:)
51 type(c_ptr) :: mask_d = c_null_ptr
53 type(stack_i4_t), private :: scratch
55 integer :: size = 0
58 logical, private :: finalized = .false.
60 character(len=80) :: name
62 logical :: invert = .false.
63 contains
65 procedure, pass(this) :: init_base => point_zone_init_base
67 procedure, pass(this) :: free_base => point_zone_free_base
69 procedure, pass(this) :: finalize => point_zone_finalize
71 procedure, pass(this) :: add => point_zone_add
74 procedure, pass(this) :: map => point_zone_map
76 procedure(point_zone_init), pass(this), deferred :: init
78 procedure(point_zone_free), pass(this), deferred :: free
80 procedure(point_zone_criterion), pass(this), deferred :: criterion
81 end type point_zone_t
82
84 type, public :: point_zone_wrapper_t
85 class(point_zone_t), allocatable :: pz
87
89 type, public :: point_zone_pointer_t
90 class(point_zone_t), pointer :: pz => null()
92
93 abstract interface
94
102 pure function point_zone_criterion(this, x, y, z, j, k, l, e) &
103 result(is_inside)
104 import :: point_zone_t
105 import :: rp
106 class(point_zone_t), intent(in) :: this
107 real(kind=rp), intent(in) :: x
108 real(kind=rp), intent(in) :: y
109 real(kind=rp), intent(in) :: z
110 integer, intent(in) :: j
111 integer, intent(in) :: k
112 integer, intent(in) :: l
113 integer, intent(in) :: e
114 logical :: is_inside
115 end function point_zone_criterion
116 end interface
117
118 abstract interface
119
122 subroutine point_zone_init(this, json, size)
123 import :: point_zone_t
124 import :: json_file
125 import :: dofmap_t
126 class(point_zone_t), intent(inout) :: this
127 type(json_file), intent(inout) :: json
128 integer, intent(in) :: size
129 end subroutine point_zone_init
130 end interface
131
132 abstract interface
133
134 subroutine point_zone_free(this)
135 import :: point_zone_t
136 class(point_zone_t), intent(inout) :: this
137 end subroutine point_zone_free
138 end interface
139
140 interface
141
146 module subroutine point_zone_factory(object, json, dof)
147 class(point_zone_t), allocatable, intent(inout) :: object
148 type(json_file), intent(inout) :: json
149 type(dofmap_t), intent(inout), optional :: dof
150 end subroutine point_zone_factory
151 end interface
152
153 interface
154
157 module subroutine point_zone_allocator(object, type_name)
158 class(point_zone_t), allocatable, intent(inout) :: object
159 character(len=:), allocatable, intent(in) :: type_name
160 end subroutine point_zone_allocator
161 end interface
162
163 !
164 ! Machinery for injecting user-defined types
165 !
166
170 abstract interface
171 subroutine point_zone_allocate(obj)
172 import point_zone_t
173 class(point_zone_t), allocatable, intent(inout) :: obj
174 end subroutine point_zone_allocate
175 end interface
176
177 interface
178
179 module subroutine register_point_zone(type_name, allocator)
180 character(len=*), intent(in) :: type_name
181 procedure(point_zone_allocate), pointer, intent(in) :: allocator
182 end subroutine register_point_zone
183 end interface
184
185 ! A name-allocator pair for user-defined types. A helper type to define a
186 ! registry of custom allocators.
187 type allocator_entry
188 character(len=20) :: type_name
189 procedure(point_zone_allocate), pointer, nopass :: allocator
190 end type allocator_entry
191
193 type(allocator_entry), allocatable :: point_zone_registry(:)
194
196 integer :: point_zone_registry_size = 0
197
198 public :: point_zone_factory, point_zone_allocator, register_point_zone, &
199 point_zone_allocate
200
201contains
202
208 subroutine point_zone_init_base(this, size, name, invert)
209 class(point_zone_t), intent(inout) :: this
210 integer, intent(in), optional :: size
211 character(len=*), intent(in) :: name
212 logical, intent(in) :: invert
213
214 call point_zone_free_base(this)
215
216 if (present(size)) then
217 call this%scratch%init(size)
218 else
219 call this%scratch%init()
220 end if
221
222 this%name = trim(name)
223 this%invert = invert
224
225 end subroutine point_zone_init_base
226
228 subroutine point_zone_free_base(this)
229 class(point_zone_t), intent(inout) :: this
230 if (allocated(this%mask)) then
231 deallocate(this%mask)
232 end if
233
234 this%finalized = .false.
235 this%size = 0
236
237 call this%scratch%free()
238
239 if (c_associated(this%mask_d)) then
240 call device_free(this%mask_d)
241 end if
242
243 end subroutine point_zone_free_base
244
246 subroutine point_zone_finalize(this)
247 class(point_zone_t), intent(inout) :: this
248 integer, pointer :: tp(:)
249 integer :: i
250
251 if (.not. this%finalized) then
252
253 if (this%scratch%size() .ne. 0) then
254
255 allocate(this%mask(this%scratch%size()))
256
257 tp => this%scratch%array()
258 do i = 1, this%scratch%size()
259 this%mask(i) = tp(i)
260 end do
261
262 this%size = this%scratch%size()
263
264 call this%scratch%clear()
265
266 if (neko_bcknd_device .eq. 1) then
267 call device_map(this%mask, this%mask_d, this%size)
268 call device_memcpy(this%mask, this%mask_d, this%size, &
269 host_to_device, sync = .false.)
270 end if
271
272 else
273
274 this%size = 0
275 call this%scratch%clear()
276
277 end if
278
279 this%finalized = .true.
280
281 end if
282
283 end subroutine point_zone_finalize
284
289 subroutine point_zone_add(this, idx)
290 class(point_zone_t), intent(inout) :: this
291 integer, intent(inout) :: idx
292
293 if (this%finalized) then
294 call neko_error('Point zone already finalized')
295 end if
296
297 call this%scratch%push(idx)
298
299 end subroutine point_zone_add
300
304 subroutine point_zone_map(this, dof)
305 class(point_zone_t), intent(inout) :: this
306 type(dofmap_t), intent(in) :: dof
307
308 integer :: i, ix, iy, iz, ie, nlindex(4), lx, idx
309 real(kind=rp) :: x, y, z
310
311 lx = dof%Xh%lx
312
313 do i = 1, dof%size()
314 nlindex = nonlinear_index(i, lx, lx, lx)
315 x = dof%x(nlindex(1), nlindex(2), nlindex(3), nlindex(4))
316 y = dof%y(nlindex(1), nlindex(2), nlindex(3), nlindex(4))
317 z = dof%z(nlindex(1), nlindex(2), nlindex(3), nlindex(4))
318 ix = nlindex(1)
319 iy = nlindex(2)
320 iz = nlindex(3)
321 ie = nlindex(4)
322
323 if (this%invert .neqv. this%criterion(x, y, z, ix, iy, iz, ie)) then
324 idx = i
325 call this%add(idx)
326 end if
327 end do
328
329 end subroutine point_zone_map
330
331end module point_zone
__inline__ __device__ void nonlinear_index(const int idx, const int lx, int *index)
Definition bc_utils.h:44
Map a Fortran array to a device (allocate and associate)
Definition device.F90:72
Copy data between host and device (or device and device)
Definition device.F90:66
Defines the criterion of selection of a GLL point to the point_zone.
The common constructor using a JSON object.
Device abstraction, common interface for various accelerators.
Definition device.F90:34
integer, parameter, public host_to_device
Definition device.F90:47
subroutine, public device_free(x_d)
Deallocate memory on the device.
Definition device.F90:208
Defines a mapping of the degrees of freedom.
Definition dofmap.f90:35
NEKTON map.
Definition map.f90:3
Build configurations.
integer, parameter neko_bcknd_device
integer, parameter, public rp
Global precision used in computations.
Definition num_types.f90:12
subroutine point_zone_free_base(this)
Destructor for the point_zone_t base type.
subroutine point_zone_add(this, idx)
Adds a point's linear index to the scratch stack.
subroutine point_zone_finalize(this)
Builds the mask from the scratch stack.
subroutine point_zone_init_base(this, size, name, invert)
Constructor for the point_zone_t base type.
subroutine point_zone_map(this, dof)
Maps the GLL points that verify a point_zone's criterion by adding them to the stack.
Implements a dynamic stack ADT.
Definition stack.f90:35
Utilities.
Definition utils.f90:35
A helper type to build a list of pointers to point_zones.
Base abstract type for point zones.
A helper type to build a list of polymorphic point_zones.
Integer based stack.
Definition stack.f90:63