Neko  0.9.0
A portable framework for high-order spectral element flow simulations
signed_distance.f90
Go to the documentation of this file.
1 ! Copyright (c) 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 !
35  use num_types, only: dp, rp
36  use field, only: field_t
37  use tri, only: tri_t
38  use tri_mesh, only: tri_mesh_t
39  use aabb_tree, only: aabb_tree_t
42  use utils, only: neko_error, neko_warning
43 
44  implicit none
45  private
46  public :: signed_distance_field
47 
48 contains
49 
60  subroutine signed_distance_field(field_data, object, max_distance)
61  type(field_t), intent(inout) :: field_data
62  class(*), intent(in) :: object
63  real(kind=dp), intent(in), optional :: max_distance
64 
65  real(kind=dp) :: max_dist
66 
67  if (present(max_distance)) then
68  max_dist = max_distance
69  else
70  max_dist = huge(0.0_dp)
71  end if
72 
73  select type(object)
74  type is (tri_mesh_t)
75  call signed_distance_field_tri_mesh(field_data, object, max_dist)
76 
77  class default
78  call neko_error("signed_distance_field: Object type not supported.")
79  end select
80 
81  end subroutine signed_distance_field
82 
93  subroutine signed_distance_field_tri_mesh(field_data, mesh, max_distance)
94  type(field_t), intent(inout) :: field_data
95  type(tri_mesh_t), intent(in) :: mesh
96  real(kind=dp), intent(in) :: max_distance
97 
98  integer :: total_size
99  integer :: id
100  type(aabb_tree_t) :: search_tree
101  real(kind=dp), dimension(3) :: p
102  real(kind=dp) :: distance
103 
104  ! Zero the field
105  field_data%x = 0.0_dp
106  total_size = field_data%dof%size()
107 
108  call search_tree%init(mesh%nelv)
109  call search_tree%build(mesh%el)
110 
111  if (search_tree%get_size() .ne. mesh%nelv) then
112  call neko_error("signed_distance_field_tri_mesh: &
113  & Error building the search tree.")
114  end if
115 
116  do id = 1, total_size
117  p(1) = field_data%dof%x(id, 1, 1, 1)
118  p(2) = field_data%dof%y(id, 1, 1, 1)
119  p(3) = field_data%dof%z(id, 1, 1, 1)
120 
121  distance = tri_mesh_aabb_tree(search_tree, mesh%el, p, max_distance)
122 
123  field_data%x(id, 1, 1, 1) = real(distance, kind=rp)
124  end do
125 
126  if (neko_bcknd_device .eq. 1) then
127  call neko_warning("signed_distance_field_tri_mesh:&
128  & Device version not implemented.")
129  call device_memcpy(field_data%x, field_data%x_d, field_data%size(), &
130  host_to_device, sync = .false.)
131  end if
132 
133  end subroutine signed_distance_field_tri_mesh
134 
145  function tri_mesh_brute_force(mesh, p, max_distance) result(distance)
146  use tri, only: tri_t
147  use point, only: point_t
148  use num_types, only: dp
149 
150  implicit none
151 
152  type(tri_mesh_t), intent(in) :: mesh
153  real(kind=dp), intent(in) :: p(3)
154  real(kind=dp), intent(in) :: max_distance
155 
156  integer :: id
157  real(kind=dp) :: distance, weighted_sign
158  real(kind=dp) :: cd, cs
159  real(kind=dp) :: tol = 1e-6_dp
160 
161  distance = 1e10_dp
162  weighted_sign = 0.0_dp
163 
164  do id = 1, mesh%nelv
165  call element_distance(mesh%el(id), p, cd, cs)
166 
167  ! Update the weighted sign, if the relative difference is small
168  if (abs(cd - distance) / distance .lt. tol) then
169  weighted_sign = weighted_sign + cs
170  else if (cd .lt. distance) then
171  weighted_sign = cs
172  end if
173 
174  distance = min(cd, distance)
175  end do
176 
177  distance = sign(min(distance, max_distance), weighted_sign)
178 
179  end function tri_mesh_brute_force
180 
194  function tri_mesh_aabb_tree(tree, object_list, p, max_distance) result(distance)
195  use aabb, only: aabb_t
197  use stack, only: stack_i4_t
198  implicit none
199 
200  class(aabb_tree_t), intent(in) :: tree
201  class(tri_t), dimension(:), intent(in) :: object_list
202  real(kind=dp), dimension(3), intent(in) :: p
203  real(kind=dp), intent(in) :: max_distance
204 
205  real(kind=dp) :: distance
206  real(kind=dp) :: weighted_sign
207 
208  real(kind=dp), parameter :: tol = 1.0e-6_dp
209 
210  type(stack_i4_t) :: simple_stack
211  integer :: current_index
212 
213  type(aabb_node_t) :: current_node
214  type(aabb_t) :: current_aabb
215  integer :: current_object_index
216  real(kind=dp) :: current_distance
217  real(kind=dp) :: current_sign
218 
219  type(aabb_node_t) :: left_node
220  type(aabb_node_t) :: right_node
221 
222  type(aabb_t) :: root_box
223  type(aabb_t) :: search_box
224 
225  integer :: root_index, left_index, right_index
226  real(kind=dp) :: random_value
227 
228  ! Initialize the stack and the search box
229  call simple_stack%init(size(object_list) * 2)
230  call search_box%init(p - max_distance, p + max_distance)
231 
232  ! Check if the root node overlaps the search box, if it does, push it to
233  ! the stack and update the search box to a randomly selected object.
234  root_index = tree%get_root_index()
235  root_box = tree%get_aabb(root_index)
236 
237  if (.not. root_box%overlaps(search_box)) then
238  distance = max_distance
239  weighted_sign = 1.0_dp
240  return
241  end if
242 
243  ! Grab a random object and compute the distance to it
244  call random_number(random_value)
245  current_object_index = floor(random_value * size(object_list) + 1)
246  call element_distance(object_list(current_object_index), p, distance, weighted_sign)
247  distance = distance + object_list(current_object_index)%diameter()
248 
249  ! Update the search box to the new distance and push the root node
250  call search_box%init(p - distance, p + distance)
251  call simple_stack%push(root_index)
252 
253  ! Traverse the tree and compute the signed distance to the elements
254  do while (.not. simple_stack%is_empty())
255  current_index = simple_stack%pop()
256  if (current_index .eq. aabb_null_node) cycle
257 
258  current_node = tree%get_node(current_index)
259  current_aabb = current_node%get_aabb()
260 
261  if (current_node%is_leaf()) then
262  if (distance .lt. current_node%min_distance(p)) then
263  cycle
264  end if
265 
266  current_object_index = current_node%get_object_index()
267  call element_distance(object_list(current_object_index), p, current_distance, current_sign)
268 
269  ! Update the weighted sign, if the relative difference is small
270  if (abs(current_distance - distance) / distance .lt. tol) then
271  weighted_sign = weighted_sign + current_sign
272  else if (current_distance .lt. distance) then
273  weighted_sign = current_sign
274  end if
275 
276  distance = min(distance, current_distance)
277 
278  ! Update the search box to the new distance
279  if (distance .gt. current_aabb%get_diameter()) then
280  call search_box%init(p - distance, p + distance)
281  end if
282  else
283 
284  left_index = tree%get_left_index(current_index)
285  if (left_index .ne. aabb_null_node) then
286  left_node = tree%get_left_node(current_index)
287  if (left_node%aabb%overlaps(search_box)) then
288  call simple_stack%push(left_index)
289  end if
290  end if
291 
292  right_index = tree%get_right_index(current_index)
293  if (right_index .ne. aabb_null_node) then
294  right_node = tree%get_right_node(current_index)
295  if (right_node%aabb%overlaps(search_box)) then
296  call simple_stack%push(right_index)
297  end if
298  end if
299  end if
300  end do
301 
302  if (distance .gt. max_distance) then
303  distance = max_distance
304  end if
305  distance = sign(distance, weighted_sign)
306 
307  end function tri_mesh_aabb_tree
308 
309  ! ========================================================================== !
310  ! Element distance functions
311  ! ========================================================================== !
312 
314  subroutine element_distance(element, p, distance, weighted_sign)
315  class(*), intent(in) :: element
316  real(kind=dp), dimension(3), intent(in) :: p
317  real(kind=dp), intent(out) :: distance
318  real(kind=dp), intent(out), optional :: weighted_sign
319 
320  select type(element)
321  type is (tri_t)
322  call element_distance_triangle(element, p, distance, weighted_sign)
323 
324  class default
325  print *, "Error: Element type not supported."
326  stop
327  end select
328  end subroutine element_distance
329 
330  ! -------------------------------------------------------------------------- !
331  ! Specific element distance functions
332 
350  subroutine element_distance_triangle(triangle, p, distance, weighted_sign)
351  type(tri_t), intent(in) :: triangle
352  real(kind=dp), dimension(3), intent(in) :: p
353 
354  real(kind=dp), intent(out) :: distance
355  real(kind=dp), intent(out), optional :: weighted_sign
356 
357  real(kind=dp), dimension(3) :: v1, v2, v3
358  real(kind=dp), dimension(3) :: normal
359  real(kind=dp) :: normal_length
360  real(kind=dp) :: b1, b2, b3
361 
362  real(kind=dp), dimension(3) :: projection
363  real(kind=dp), dimension(3) :: edge
364  real(kind=dp) :: tol = 1e-10_dp
365 
366  real(kind=dp) :: face_distance
367  real(kind=dp) :: t
368 
369  ! Get vertices and the normal vector
370  v1 = triangle%pts(1)%p%x
371  v2 = triangle%pts(2)%p%x
372  v3 = triangle%pts(3)%p%x
373 
374  normal = cross(v2 - v1, v3 - v1)
375  normal_length = norm2(normal)
376 
377  if (normal_length .lt. tol) then
378  distance = huge(1.0_dp)
379  weighted_sign = 0.0_dp
380  return
381  end if
382  normal = normal / normal_length
383 
384  ! Compute Barycentric coordinates to determine if the point is inside the
385  ! triangular prism, of along an edge or by a face.
386  face_distance = dot_product(p - v1, normal)
387 
388  projection = p - normal * face_distance
389  b1 = dot_product(normal, cross(v2 - v1, projection - v1)) / normal_length
390  b2 = dot_product(normal, cross(v3 - v2, projection - v2)) / normal_length
391  b3 = dot_product(normal, cross(v1 - v3, projection - v3)) / normal_length
392 
393  if (b1 .le. tol) then
394  edge = v2 - v1
395  t = dot_product(p - v1, edge) / norm2(edge)
396  t = max(0.0_dp, min(1.0_dp, t))
397 
398  projection = v1 + t * edge
399  else if (b2 .le. tol) then
400  edge = v3 - v2
401  t = dot_product(p - v2, edge) / norm2(edge)
402  t = max(0.0_dp, min(1.0_dp, t))
403 
404  projection = v2 + t * edge
405  else if (b3 .le. tol) then
406  edge = v1 - v3
407  t = dot_product(p - v3, edge) / norm2(edge)
408  t = max(0.0_dp, min(1.0_dp, t))
409 
410  projection = v3 + t * edge
411  end if
412 
413  distance = norm2(projection - p)
414  if (present(weighted_sign)) then
415  weighted_sign = face_distance / distance
416  else
417  distance = sign(distance, face_distance)
418  end if
419 
420  end subroutine element_distance_triangle
421 
426  pure function cross(a, b) result(c)
427  real(kind=dp), dimension(3), intent(in) :: a
428  real(kind=dp), dimension(3), intent(in) :: b
429  real(kind=dp), dimension(3) :: c
430 
431  c(1) = a(2) * b(3) - a(3) * b(2)
432  c(2) = a(3) * b(1) - a(1) * b(3)
433  c(3) = a(1) * b(2) - a(2) * b(1)
434 
435  end function cross
436 
437 end module signed_distance
double real
Definition: device_config.h:12
Copy data between host and device (or device and device)
Definition: device.F90:51
Axis Aligned Bounding Box (aabb) Tree data structure.
Definition: aabb_tree.f90:70
integer, parameter, public aabb_null_node
Definition: aabb_tree.f90:78
Axis Aligned Bounding Box (aabb) implementation in Fortran.
Definition: aabb.f90:71
Device abstraction, common interface for various accelerators.
Definition: device.F90:34
integer, parameter, public host_to_device
Definition: device.F90:47
Defines a field.
Definition: field.f90:34
Defines a mesh.
Definition: mesh.f90:34
Build configurations.
Definition: neko_config.f90:34
integer, parameter neko_bcknd_device
Definition: neko_config.f90:44
integer, parameter, public dp
Definition: num_types.f90:9
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
Implements a point.
Definition: point.f90:35
Project x onto X, the space of old solutions and back again.
Definition: projection.f90:63
Module containing Signed Distance Functions.
subroutine signed_distance_field_tri_mesh(field_data, mesh, max_distance)
Signed distance field for a triangular mesh.
pure real(kind=dp) function, dimension(3) cross(a, b)
Compute cross product of two vectors.
subroutine element_distance_triangle(triangle, p, distance, weighted_sign)
Signed distance function for a triangle.
real(kind=dp) function tri_mesh_aabb_tree(tree, object_list, p, max_distance)
Signed distance function using an AABB tree.
subroutine, public signed_distance_field(field_data, object, max_distance)
Signed distance field.
subroutine element_distance(element, p, distance, weighted_sign)
Main interface for the signed distance function for an element.
real(kind=dp) function tri_mesh_brute_force(mesh, p, max_distance)
Signed distance function.
Implements a dynamic stack ADT.
Definition: stack.f90:35
Defines a triangular surface mesh.
Definition: tri_mesh.f90:35
Defines a triangular element.
Definition: tri.f90:34
Utilities.
Definition: utils.f90:35
subroutine, public neko_warning(warning_msg)
Reports a warning to standard output.
Definition: utils.f90:245
Axis Aligned Bounding Box (aabb) data structure.
Definition: aabb.f90:107
Node type for the Axis Aligned Bounding Box (aabb) Tree.
Definition: aabb_tree.f90:85
Axis Aligned Bounding Box (aabb) Tree.
Definition: aabb_tree.f90:129
A point in with coordinates .
Definition: point.f90:43
Integer based stack.
Definition: stack.f90:63
Triangular element.
Definition: tri.f90:60
#define max(a, b)
Definition: tensor.cu:40