26  use, 
intrinsic :: iso_fortran_env
 
   40    real(real64)   :: radius
 
   51    procedure box_sphere_constructor
 
   58    integer,            
intent(in) :: dim
 
   59    real(real64),       
intent(in) :: center(dim)
 
   60    real(real64),       
intent(in) :: radius
 
   61    type(namespace_t),  
intent(in) :: namespace
 
   62    class(box_sphere_t), 
pointer :: box
 
   72    call box_shape_init(box, namespace, dim, center, bounding_box_min=[(-radius, idir=1, dim)], &
 
   73      bounding_box_max=[(radius, idir=1, dim)])
 
   75    box%bounding_box_l = abs(center) + radius
 
   82    type(box_sphere_t), 
intent(inout) :: this
 
   93    class(box_sphere_t), 
intent(in)  :: this
 
   94    integer,             
intent(in)  :: nn
 
   95    real(real64), 
contiguous,   
intent(in)  :: xx(:,:)
 
   96    logical :: contained(1:nn)
 
  101      contained(ip) = sum((xx(ip, 1:this%dim) - this%center(1:this%dim))**2) <= (this%radius + 
box_boundary_delta)**2 &
 
  102        .neqv. this%is_inside_out()
 
  112    class(box_sphere_t), 
intent(in)  :: this
 
  113    type(namespace_t),   
intent(in)  :: namespace
 
  114    real(real64),        
intent(in)  :: mesh_spacing(:)
 
  115    integer,             
intent(in)  :: nn
 
  116    real(real64),        
intent(in)  :: xx(:,:)
 
  117    integer, 
optional,   
intent(in)  :: number_of_layers
 
  119    logical          :: surface_points(1:nn)
 
  120    real(real64)     :: shrink
 
  121    real(real64), 
parameter :: compression = 0.94_real64
 
  122    class(box_sphere_t), 
pointer :: shrinked_box
 
  124    assert(abs(mesh_spacing(1) - mesh_spacing(2)) < 
m_epsilon .and. abs(mesh_spacing(1) - mesh_spacing(3)) < 
m_epsilon)
 
  127    shrink = 1 - compression * (mesh_spacing(1) / this%radius)
 
  130    shrinked_box => 
box_sphere_t(this%dim, this%center, this%radius * shrink, namespace)
 
  138    safe_deallocate_p(shrinked_box)
 
  145    real(real64),        
intent(in)  :: point_coordinates(:)
 
  146    real(real64),        
intent(in)  :: mesh_spacing(:)
 
  147    real(real64),        
intent(out) :: normal_vector(:)
 
  148    real(real64),        
intent(out) :: surface_element
 
  150    real(real64) :: dtheta, dphi, rr
 
  163    normal_vector(:) = point_coordinates(:) - this%center(:)
 
  165    rr = 
sqrt(normal_vector(1)**2 + normal_vector(2)**2)
 
  167      dtheta = normal_vector(1) * normal_vector(3) / (rr * this%radius**2) * mesh_spacing(1) + &
 
  168        normal_vector(2) * normal_vector(3) / (rr * this%radius**2) * mesh_spacing(2) - rr / this%radius**2 * mesh_spacing(3)
 
  170      dphi = (- normal_vector(2) * mesh_spacing(1) + normal_vector(1) * mesh_spacing(2)) / rr**2
 
  173    normal_vector(:) = normal_vector(:) / norm2(normal_vector)
 
  176    surface_element = abs(dtheta * dphi) * this%radius**2 * 
sin(
acos(normal_vector(3)))
 
  184    integer,           
optional, 
intent(in) :: iunit
 
  189    write(
message(1),
'(2x,a)') 
'Type = sphere' 
  200    type(
unit_t),        
intent(in) :: unit_length
 
double acos(double __x) __attribute__((__nothrow__
 
double sin(double __x) __attribute__((__nothrow__
 
real(real64), parameter, public box_boundary_delta
 
subroutine, public box_shape_init(this, namespace, dim, center, bounding_box_min, bounding_box_max, axes)
 
subroutine, public box_shape_end(this)
 
subroutine box_sphere_write_info(this, iunit, namespace)
 
character(len=box_info_len) function box_sphere_short_info(this, unit_length)
 
subroutine box_sphere_finalize(this)
 
logical function, dimension(1:nn) box_sphere_shape_get_surface_points(this, namespace, mesh_spacing, nn, xx, number_of_layers)
Get a mask for the grid points telling which of them are surface points.
 
logical function, dimension(1:nn) box_sphere_shape_contains_points(this, nn, xx)
 
subroutine box_sphere_shape_get_surface_point_info(this, point_coordinates, mesh_spacing, normal_vector, surface_element)
 
class(box_sphere_t) function, pointer box_sphere_constructor(dim, center, radius, namespace)
 
real(real64), parameter, public m_zero
 
real(real64), parameter, public m_epsilon
 
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
 
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
 
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
 
character(len=20) pure function, public units_abbrev(this)
 
This module defines the unit system, used for input and output.
 
type(unit_system_t), public units_out
 
Base class for more specialized boxes that are defined by a shape and have a center and basis vectors...
 
Class implementing a spherical box.