26  use, 
intrinsic :: iso_fortran_env
 
   42    real(real64), 
public :: radius
 
   43    real(real64), 
public :: half_length
 
   45    logical :: periodic_boundaries = .false. 
 
   56    procedure box_cylinder_constructor
 
   63    integer,            
intent(in) :: dim
 
   64    real(real64),       
intent(in) :: center(dim)
 
   65    real(real64),       
intent(in) :: axes(dim, dim)
 
   66    real(real64),       
intent(in) :: radius
 
   67    real(real64),       
intent(in) :: length
 
   68    type(namespace_t),  
intent(in) :: namespace
 
   69    logical, 
optional,  
intent(in) :: periodic_boundaries
 
   70    class(box_cylinder_t), 
pointer :: box
 
   78      message(1) = 
"Cannot create a cylinder in 1D or 2D. Use sphere if you want a circle." 
   86    call box_shape_init(box, namespace, dim, center, bounding_box_min=[-
m_half*length, (-radius, idir=2,dim)], &
 
   87      bounding_box_max=[
m_half*length, (radius, idir=2,dim)], axes=axes)
 
   89    box%half_length = 
m_half*length
 
   91    if (
present(periodic_boundaries)) 
then 
   92      box%periodic_boundaries = periodic_boundaries
 
   95    box%bounding_box_l(1) = 
m_half*length + abs(center(1))  
 
   96    box%bounding_box_l(2:dim) = radius + abs(center(2:dim)) 
 
  103    type(box_cylinder_t), 
intent(inout) :: this
 
  114    class(box_cylinder_t), 
intent(in)  :: this
 
  115    integer,               
intent(in)  :: nn
 
  116    real(real64), 
contiguous,     
intent(in)  :: xx(:,:)
 
  117    logical :: contained(1:nn)
 
  120    real(real64) :: rr2, vv(this%dim)
 
  123      vv = xx(ip, 1:this%dim) - this%center(1:this%dim)
 
  126      if (.not. this%periodic_boundaries) 
then 
  127        contained(ip) = abs(vv(1)) <= this%half_length + 
box_boundary_delta .neqv. this%is_inside_out()
 
  133      if (.not. contained(ip)) cycle
 
  136      rr2 = sum(vv(2:this%dim)**2)
 
  137      contained(ip) = rr2 <= (this%radius + 
box_boundary_delta)**2 .neqv. this%is_inside_out()
 
  149    real(real64),          
intent(in)  :: mesh_spacing(:)
 
  150    integer,               
intent(in)  :: nn
 
  151    real(real64),          
intent(in)  :: xx(:,:)
 
  152    integer, 
optional,     
intent(in)  :: number_of_layers
 
  154    logical          :: surface_points(1:nn)
 
  155    real(real64)     :: shrink(this%dim)
 
  156    real(real64), 
parameter :: compression = 0.94_real64
 
  161    assert(abs(mesh_spacing(2) - mesh_spacing(3)) < 
m_epsilon)
 
  165    shrink(2) = 1 - compression * (mesh_spacing(2) / this%radius)
 
  168    shrinked_box => 
box_cylinder_t(this%dim, this%center, this%axes%vectors, this%radius * shrink(2), &
 
  169      m_two * this%half_length * shrink(1), namespace, periodic_boundaries=this%periodic_boundaries)
 
  175    safe_deallocate_p(shrinked_box)
 
  182    real(real64),          
intent(in)  :: point_coordinates(:)
 
  183    real(real64),          
intent(in)  :: mesh_spacing(:)
 
  184    real(real64),          
intent(out) :: normal_vector(:)
 
  185    real(real64),          
intent(out) :: surface_element
 
  197    normal_vector = (point_coordinates - this%center) / [this%half_length, this%radius, this%radius]
 
  199    if (abs(normal_vector(1)) > norm2(normal_vector(2:3))) 
then 
  200      normal_vector(2:3) = 
m_zero 
  201      surface_element = mesh_spacing(2) * mesh_spacing(3)
 
  205      surface_element = mesh_spacing(1)**2
 
  214    integer,           
optional, 
intent(in) :: iunit
 
  215    type(
namespace_t), 
optional, 
intent(in) :: namespace
 
  219    write(
message(1),
'(2x,a)') 
'Type = cylinder' 
  232    type(
unit_t),          
intent(in) :: unit_length
 
  236    write(
info, 
'(a,f11.6,a,a,a,f11.6,a,a)') 
'BoxShape = cylinder, Radius =', 
units_from_atomic(unit_length, this%radius), 
' ', &
 
character(len=box_info_len) function box_cylinder_short_info(this, unit_length)
 
subroutine box_cylinder_shape_get_surface_point_info(this, point_coordinates, mesh_spacing, normal_vector, surface_element)
 
recursive logical function, dimension(1:nn) box_cylinder_shape_contains_points(this, nn, xx)
 
logical function, dimension(1:nn) box_cylinder_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.
 
subroutine box_cylinder_write_info(this, iunit, namespace)
 
subroutine box_cylinder_finalize(this)
 
class(box_cylinder_t) function, pointer box_cylinder_constructor(dim, center, axes, radius, length, namespace, periodic_boundaries)
 
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)
 
real(real64), parameter, public m_two
 
real(real64), parameter, public m_zero
 
real(real64), parameter, public m_epsilon
 
real(real64), parameter, public m_half
 
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
 
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
 
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
 
Class implementing a cylinder box. The cylinder axis is always along the first direction defined by t...
 
Base class for more specialized boxes that are defined by a shape and have a center and basis vectors...