Octopus
volume.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
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#include "global.h"
19
20module volume_oct_m
21 use iso_c_binding
22 use global_oct_m
25 use parser_oct_m
27 use space_oct_m
28
29 implicit none
30
31 private
32 public :: &
33 volume_t, &
35 volume_end, &
38
39 type volume_t
40 private
41 integer :: n_elements
42 logical, allocatable :: join(:) ! Add or subtract the volume
43 integer, allocatable :: type(:) ! sphere, slab, etc.
44 real(real64), allocatable :: params(:,:) ! parameters of the elements
45 end type volume_t
46
47contains
48
49 subroutine volume_init(vol)
50 type(volume_t), intent(out) :: vol
51
52 vol%n_elements = 0
53 end subroutine volume_init
54
55 subroutine volume_end(vol)
56 type(volume_t), intent(inout) :: vol
57
58 safe_deallocate_a(vol%join)
59 safe_deallocate_a(vol%type)
60 safe_deallocate_a(vol%params)
61 end subroutine volume_end
62
63 subroutine volume_read_from_block(vol, namespace, block_name)
64 type(volume_t), intent(inout) :: vol
65 type(namespace_t), intent(in) :: namespace
66 character(len=*), intent(in) :: block_name
67
68 type(block_t) :: blk
69 integer :: i, j, n_par
70 character(len=100) :: str
71
72 !%Variable Volume
73 !%Type block
74 !%Default
75 !%Section Utilities::
76 !%Description
77 !% Describes a volume in space defined through the addition and substraction of
78 !% spheres. The first field is always "+" (include points inside the volume) or "-"
79 !% (exclude points inside the volume)
80 !%Option vol_sphere 10001
81 !%
82 !% <tt>%Volume
83 !% <br>&nbsp;&nbsp; "+"/"-" | vol_sphere | center_x | center_y | center_z | radius
84 !% <br>%</tt>
85 !%Option vol_slab 10002
86 !%
87 !% <tt>%Volume
88 !% <br>&nbsp;&nbsp; "+"/"-" | vol_slab | thickness
89 !% <br>%</tt>
90 !%
91 !%End
92
93 if (parse_block(namespace, block_name, blk, check_varinfo_=.false.) == 0) then
94 vol%n_elements = parse_block_n(blk)
95
96 safe_allocate(vol%join(1:vol%n_elements))
97 safe_allocate(vol%type(1:vol%n_elements))
98 safe_allocate(vol%params(1:8, 1:vol%n_elements))
99
100 vol%params = m_zero
101
102 do i = 1, vol%n_elements
103 call parse_block_string(blk, i-1, 0, str)
104 if (str == '+') then
105 vol%join(i) = .true.
106 else
107 vol%join(i) = .false.
108 end if
109
110 call parse_block_integer(blk, i-1, 1, vol%type(i))
111 select case (vol%type(i))
112 case (option__volume__vol_sphere)
113 n_par = 4 ! center point + radius
114 case (option__volume__vol_slab)
115 n_par = 1 ! thickness of the slab
116 case default
117 call messages_input_error(namespace, 'Species', "Unknown type for volume")
118 end select
119
120 do j = 1, n_par
121 call parse_block_float(blk, i-1, i+j, vol%params(j, i))
122 end do
123
124 end do
125 else
126 call messages_input_error(namespace, 'Volume')
127 end if
128 end subroutine volume_read_from_block
129
130
131 logical function volume_in_volume(space, vol, xx) result(in_vol)
132 class(space_t), intent(in) :: space
133 type(volume_t), intent(in) :: vol
134 real(real64), intent(in) :: xx(1:space%dim)
136 logical :: in_partial_volume
137 integer :: i
138 real(real64) :: r
139
140 in_vol = .false.
141 do i = 1, vol%n_elements
142 select case (vol%type(i))
143 case (option__volume__vol_sphere)
144 r = norm2(xx - vol%params(1:space%dim, i))
145 in_partial_volume = (r <= vol%params(4, i))
146
147 case (option__volume__vol_slab)
148 r = abs(xx(3))
149 in_partial_volume = (r <= vol%params(1, i))
150 end select
151
152 if (vol%join(i)) then
153 in_vol = in_vol .or. in_partial_volume
154 else
155 in_vol = in_vol .and. .not. in_partial_volume
156 end if
157 end do
158
159 end function volume_in_volume
160
161end module volume_oct_m
real(real64), parameter, public m_zero
Definition: global.F90:187
subroutine, public messages_input_error(namespace, var, details, row, column)
Definition: messages.F90:723
integer function, public parse_block(namespace, name, blk, check_varinfo_)
Definition: parser.F90:618
subroutine, public volume_read_from_block(vol, namespace, block_name)
Definition: volume.F90:157
logical function, public volume_in_volume(space, vol, xx)
Definition: volume.F90:225
subroutine, public volume_end(vol)
Definition: volume.F90:149
subroutine, public volume_init(vol)
Definition: volume.F90:143
int true(void)