Octopus
box_cylinder.F90
Go to the documentation of this file.
1!! Copyright (C) 2021 M. Oliveira, K. Lively, A. Obzhirov, I. Albar
2!!
3!! This program is free software; you can redistribute it and/or modify
4!! it under the terms of the GNU General Public License as published by
5!! the Free Software Foundation; either version 2, or (at your option)
6!! any later version.
7!!
8!! This program is distributed in the hope that it will be useful,
9!! but WITHOUT ANY WARRANTY; without even the implied warranty of
10!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11!! GNU General Public License for more details.
12!!
13!! You should have received a copy of the GNU General Public License
14!! along with this program; if not, write to the Free Software
15!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
16!! 02110-1301, USA.
17!!
18
19#include "global.h"
20
22 use box_oct_m
24 use debug_oct_m
25 use global_oct_m
26 use, intrinsic :: iso_fortran_env
30 use unit_oct_m
32
33 implicit none
34
35 private
36 public :: box_cylinder_t
37
40 type, extends(box_shape_t) :: box_cylinder_t
41 private
42 real(real64), public :: radius
43 real(real64), public :: half_length
44
45 logical :: periodic_boundaries = .false.
46 contains
47 procedure :: shape_contains_points => box_cylinder_shape_contains_points
48 procedure :: get_surface_points => box_cylinder_shape_get_surface_points
49 procedure :: get_surface_point_info => box_cylinder_shape_get_surface_point_info
50 procedure :: write_info => box_cylinder_write_info
51 procedure :: short_info => box_cylinder_short_info
53 end type box_cylinder_t
54
55 interface box_cylinder_t
56 procedure box_cylinder_constructor
57 end interface box_cylinder_t
58
59contains
60
61 !--------------------------------------------------------------
62 function box_cylinder_constructor(dim, center, axes, radius, length, namespace, periodic_boundaries) result(box)
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
71
72 integer :: idir
73
75
76 ! Sanity checks
77 if (dim <= 2) then
78 message(1) = "Cannot create a cylinder in 1D or 2D. Use sphere if you want a circle."
79 call messages_fatal(1, namespace=namespace)
80 end if
81
82 ! Allocate memory
83 safe_allocate(box)
84
85 ! Initialize box
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)
88 box%radius = radius
89 box%half_length = m_half*length
90
91 if (present(periodic_boundaries)) then
92 box%periodic_boundaries = periodic_boundaries
93 end if
94
95 box%bounding_box_l(1) = m_half*length + abs(center(1))
96 box%bounding_box_l(2:dim) = radius + abs(center(2:dim))
97
99 end function box_cylinder_constructor
100
101 !--------------------------------------------------------------
102 subroutine box_cylinder_finalize(this)
103 type(box_cylinder_t), intent(inout) :: this
104
105 push_sub(box_cylinder_finalize)
106
107 call box_shape_end(this)
108
109 pop_sub(box_cylinder_finalize)
110 end subroutine box_cylinder_finalize
111
112 !--------------------------------------------------------------
113 recursive function box_cylinder_shape_contains_points(this, nn, xx) result(contained)
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)
118
119 integer :: ip
120 real(real64) :: rr2, vv(this%dim)
121
122 do ip = 1, nn
123 vv = xx(ip, 1:this%dim) - this%center(1:this%dim)
124
125 ! First check if we are "inside" along the axis direction. If not, do not bother checking the other directions.
126 if (.not. this%periodic_boundaries) then
127 contained(ip) = abs(vv(1)) <= this%half_length + box_boundary_delta .neqv. this%is_inside_out()
128 else
129 ! When periodic, we exclude one of the faces from the box. Also, we
130 ! never consider the box to be inside out along the periodic dimension.
131 contained(ip) = abs(vv(1) + box_boundary_delta) <= this%half_length
132 end if
133 if (.not. contained(ip)) cycle
134
135 ! Check if we are inside along the directions perpendicular to the axis
136 rr2 = sum(vv(2:this%dim)**2)
137 contained(ip) = rr2 <= (this%radius + box_boundary_delta)**2 .neqv. this%is_inside_out()
138 end do
139
142 !--------------------------------------------------------------
146 function box_cylinder_shape_get_surface_points(this, namespace, mesh_spacing, nn, xx, number_of_layers) result(surface_points)
147 class(box_cylinder_t), intent(in) :: this
148 type(namespace_t), intent(in) :: namespace
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
153
154 logical :: surface_points(1:nn)
155 real(real64) :: shrink(this%dim)
156 real(real64), parameter :: compression = 0.94_real64
157 class(box_cylinder_t), pointer :: shrinked_box
158 ! TODO: See Issue 705 (ftroisi) - Helmholtz decomposition refinement
159 ! The axis of the cylinder is always in the first direction of the box_shape. So the following assert checks that the spacing
160 ! in the other two direction (which define the circle) is the same (to avoid problems due to deformation effects)
161 assert(abs(mesh_spacing(2) - mesh_spacing(3)) < m_epsilon)
162
163 ! First of all determine how much the shrink should be based on the spacing in each direction
164 shrink(1) = 1 - (1 - box_boundary_delta) * (mesh_spacing(1) / this%half_length)
165 shrink(2) = 1 - compression * (mesh_spacing(2) / this%radius)
166
167 ! First of all we create a shrunk cylindric box
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)
170
171 ! Then we look for points of the old box that are not containted in the smaller box
172 ! box_parallelepiped_shape_contains_points will return the point contained in the shrinked box,
173 ! but we are interested in the ones not contained, as they will the surface points of the original parallelepiped
174 surface_points = .not. box_cylinder_shape_contains_points(shrinked_box, nn, xx)
175 safe_deallocate_p(shrinked_box)
176
178
179 !--------------------------------------------------------------
180 subroutine box_cylinder_shape_get_surface_point_info(this, point_coordinates, mesh_spacing, normal_vector, surface_element)
181 class(box_cylinder_t), intent(in) :: this
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
186
188
189 ! Compute the normal vector to the surface point
190
191 ! For a cylinder, the normal vector to a point is the normal to a circle if we are on its side while if we are on one of
192 ! its flat surfaces it is simply a vector of type (1,0,0)
193
194 ! So first of all we have to determine in which face we are. We know that the cylinder is along the first direction
195 ! defined by the box_shape_t basis vectors (which is x). To do that let us divide the vector containing the coordinates
196 ! of the point by the maximum length of the parallelepiped
197 normal_vector = (point_coordinates - this%center) / [this%half_length, this%radius, this%radius]
198
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)
202 else
203 ! in this case we are on the circle
204 normal_vector(1) = m_zero
205 surface_element = mesh_spacing(1)**2
206 end if
207
210
211 !--------------------------------------------------------------
212 subroutine box_cylinder_write_info(this, iunit, namespace)
213 class(box_cylinder_t), intent(in) :: this
214 integer, optional, intent(in) :: iunit
215 type(namespace_t), optional, intent(in) :: namespace
216
218
219 write(message(1),'(2x,a)') 'Type = cylinder'
220 write(message(2),'(2x,3a,f7.3)') 'Radius [', trim(units_abbrev(units_out%length)), '] = ', &
221 units_from_atomic(units_out%length, this%radius)
222 write(message(3),'(2x,3a,f7.3)') 'Xlength [', trim(units_abbrev(units_out%length)), '] = ', &
223 units_from_atomic(units_out%length, this%half_length)
224 call messages_info(3, iunit=iunit, namespace=namespace)
225
227 end subroutine box_cylinder_write_info
228
229 !--------------------------------------------------------------
230 character(len=BOX_INFO_LEN) function box_cylinder_short_info(this, unit_length) result(info)
231 class(box_cylinder_t), intent(in) :: this
232 type(unit_t), intent(in) :: unit_length
233
235
236 write(info, '(a,f11.6,a,a,a,f11.6,a,a)') 'BoxShape = cylinder, Radius =', units_from_atomic(unit_length, this%radius), ' ', &
237 trim(units_abbrev(unit_length)), '; Xlength =', units_from_atomic(unit_length, this%half_length), ' ', &
238 trim(units_abbrev(unit_length))
241 end function box_cylinder_short_info
242
243end module box_cylinder_oct_m
244
245!! Local Variables:
246!! mode: f90
247!! coding: utf-8
248!! End:
subroutine info()
Definition: em_resp.F90:1096
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
Definition: box.F90:132
subroutine, public box_shape_init(this, namespace, dim, center, bounding_box_min, bounding_box_max, axes)
Definition: box_shape.F90:175
subroutine, public box_shape_end(this)
Definition: box_shape.F90:271
real(real64), parameter, public m_two
Definition: global.F90:189
real(real64), parameter, public m_zero
Definition: global.F90:187
real(real64), parameter, public m_epsilon
Definition: global.F90:203
real(real64), parameter, public m_half
Definition: global.F90:193
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
Definition: messages.F90:624
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:420
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
Definition: unit.F90:132
character(len=20) pure function, public units_abbrev(this)
Definition: unit.F90:223
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...
Definition: box_shape.F90:134