39 use json_module,
only: json_file
42 use,
intrinsic :: iso_c_binding, only: c_ptr, c_null_ptr, c_associated
49 integer,
allocatable :: mask(:)
51 type(c_ptr) :: mask_d = c_null_ptr
58 logical,
private :: finalized = .false.
60 character(len=80) :: name
62 logical :: invert = .false.
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
127 type(json_file),
intent(inout) :: json
128 integer,
intent(in) :: size
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
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
171 subroutine point_zone_allocate(obj)
173 class(point_zone_t),
allocatable,
intent(inout) :: obj
174 end subroutine point_zone_allocate
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
188 character(len=20) :: type_name
189 procedure(point_zone_allocate),
pointer,
nopass :: allocator
190 end type allocator_entry
196 integer :: point_zone_registry_size = 0
198 public :: point_zone_factory, point_zone_allocator, register_point_zone, &
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
214 call point_zone_free_base(this)
216 if (
present(size))
then
217 call this%scratch%init(size)
219 call this%scratch%init()
222 this%name = trim(name)
225 end subroutine point_zone_init_base
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)
234 this%finalized = .false.
237 call this%scratch%free()
239 if (c_associated(this%mask_d))
then
243 end subroutine point_zone_free_base
246 subroutine point_zone_finalize(this)
247 class(point_zone_t),
intent(inout) :: this
248 integer,
pointer :: tp(:)
251 if (.not. this%finalized)
then
253 if (this%scratch%size() .ne. 0)
then
255 allocate(this%mask(this%scratch%size()))
257 tp => this%scratch%array()
258 do i = 1, this%scratch%size()
262 this%size = this%scratch%size()
264 call this%scratch%clear()
267 call device_map(this%mask, this%mask_d, this%size)
275 call this%scratch%clear()
279 this%finalized = .true.
283 end subroutine point_zone_finalize
289 subroutine point_zone_add(this, idx)
290 class(point_zone_t),
intent(inout) :: this
291 integer,
intent(inout) :: idx
293 if (this%finalized)
then
294 call neko_error(
'Point zone already finalized')
297 call this%scratch%push(idx)
299 end subroutine point_zone_add
304 subroutine point_zone_map(this, dof)
305 class(point_zone_t),
intent(inout) :: this
308 integer :: i, ix, iy, iz, ie, nlindex(4), lx, idx
309 real(kind=
rp) :: x, y, z
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))
323 if (this%invert .neqv. this%criterion(x, y, z, ix, iy, iz, ie))
then
329 end subroutine point_zone_map
__inline__ __device__ void nonlinear_index(const int idx, const int lx, int *index)
Map a Fortran array to a device (allocate and associate)
Copy data between host and device (or device and device)
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.
integer, parameter, public host_to_device
subroutine, public device_free(x_d)
Deallocate memory on the device.
Defines a mapping of the degrees of freedom.
integer, parameter neko_bcknd_device
integer, parameter, public rp
Global precision used in computations.
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.
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.