Line | Branch | Exec | Source |
---|---|---|---|
1 | module raffle__distribs | ||
2 | !! Module for handling distribution functions. | ||
3 | !! | ||
4 | !! This module contains the types and subroutines for generating distribution | ||
5 | !! fucntions for individual materials. | ||
6 | !! The distribution functions are used as fingerprints for atomic structures | ||
7 | !! to identify similarities and differences between structures. | ||
8 | use raffle__constants, only: real32, pi | ||
9 | use raffle__io_utils, only: stop_program, print_warning | ||
10 | use raffle__misc, only: strip_null, sort_str | ||
11 | use raffle__misc_maths, only: triangular_number | ||
12 | use raffle__misc_linalg, only: get_angle, get_improper_dihedral_angle, modu | ||
13 | use raffle__geom_rw, only: basis_type, get_element_properties | ||
14 | use raffle__geom_extd, only: extended_basis_type | ||
15 | use raffle__element_utils, only: & | ||
16 | element_type, element_bond_type, & | ||
17 | element_database, element_bond_database | ||
18 | implicit none | ||
19 | |||
20 | |||
21 | private | ||
22 | |||
23 | public :: distribs_base_type, distribs_type, get_distrib | ||
24 | |||
25 | |||
26 | type :: distribs_base_type | ||
27 | !! Base type for distribution functions. | ||
28 | real(real32), dimension(:,:), allocatable :: df_2body | ||
29 | !! 2-body distribution function. | ||
30 | real(real32), dimension(:,:), allocatable :: df_3body | ||
31 | !! 3-body distribution function. | ||
32 | real(real32), dimension(:,:), allocatable :: df_4body | ||
33 | !! 4-body distribution function. | ||
34 | end type distribs_base_type | ||
35 | |||
36 | type, extends(distribs_base_type) :: distribs_type | ||
37 | !! Type for distribution functions. | ||
38 | !! | ||
39 | !! This type contains the distribution functions for a single atomic | ||
40 | !! structure. It also contains other structure properties, including: | ||
41 | !! - energy | ||
42 | !! - stoichiometry | ||
43 | !! - elements | ||
44 | !! - number of atoms | ||
45 | integer :: num_atoms = 0 | ||
46 | !! Number of atoms in the structure. | ||
47 | real(real32) :: energy = 0.0_real32 | ||
48 | !! Energy of the structure. | ||
49 | real(real32) :: energy_above_hull = 0.0_real32 | ||
50 | !! Energy above the hull of the structure. | ||
51 | logical :: from_host = .false. | ||
52 | !! Boolean whether the structure is derived from the host. | ||
53 | integer, dimension(:), allocatable :: stoichiometry | ||
54 | !! Stoichiometry of the structure. | ||
55 | character(len=3), dimension(:), allocatable :: element_symbols | ||
56 | !! Elements contained within the structure. | ||
57 | integer, dimension(:), allocatable :: num_pairs, num_per_species | ||
58 | !! Number of pairs and number of pairs per species. | ||
59 | real(real32), dimension(:), allocatable :: weight_pair, weight_per_species | ||
60 | !! Weights for the 2-body and species distribution functions. | ||
61 | contains | ||
62 | procedure, pass(this) :: calculate | ||
63 | end type distribs_type | ||
64 | |||
65 | |||
66 | contains | ||
67 | |||
68 | !############################################################################### | ||
69 | 14 | subroutine set_bond_radius_to_default(elements) | |
70 | !! Set the bond radius to the default value. | ||
71 | !! | ||
72 | !! The default value is the average of the covalent radii of the elements. | ||
73 | implicit none | ||
74 | |||
75 | ! Arguments | ||
76 | character(len=3), dimension(2), intent(in) :: elements | ||
77 | !! Element symbols. | ||
78 | |||
79 | ! Local variables | ||
80 | integer :: idx1, idx2 | ||
81 | !! Index of the elements in the element database. | ||
82 | real(real32) :: radius, radius1, radius2 | ||
83 | !! Average of covalent radii. | ||
84 | character(256) :: warn_msg | ||
85 | |||
86 | |||
87 | |||
88 | write(warn_msg,'("No bond data for element pair ",A," and ",A)') & | ||
89 | 14 | elements(1), elements(2) | |
90 | warn_msg = trim(warn_msg) // & | ||
91 | achar(13) // achar(10) // & | ||
92 |
2/4✓ Branch 2 taken 14 times.
✗ Branch 3 not taken.
✓ Branch 6 taken 14 times.
✗ Branch 7 not taken.
|
14 | "Setting bond to average of covalent radii" |
93 | 14 | call print_warning(warn_msg) | |
94 |
1/10✗ Branch 0 not taken.
✓ Branch 1 taken 14 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 8 not taken.
✗ Branch 9 not taken.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
|
14 | if(.not.allocated(element_database)) allocate(element_database(0)) |
95 | idx1 = findloc([ element_database(:)%name ], & | ||
96 |
6/8✗ Branch 0 not taken.
✓ Branch 1 taken 14 times.
✓ Branch 3 taken 29 times.
✓ Branch 4 taken 14 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 14 times.
✓ Branch 7 taken 29 times.
✓ Branch 8 taken 14 times.
|
72 | elements(1), dim=1) |
97 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 13 times.
|
14 | if(idx1.lt.1)then |
98 | 1 | call get_element_properties(elements(1), radius=radius1) | |
99 | element_database = [ element_database, & | ||
100 |
11/16✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✓ Branch 3 taken 1 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✓ Branch 7 taken 2 times.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 1 times.
✓ Branch 15 taken 2 times.
✓ Branch 16 taken 1 times.
|
6 | element_type(name=elements(1), radius=radius1) ] |
101 | 1 | idx1 = size(element_database) | |
102 | end if | ||
103 | idx2 = findloc([ element_database(:)%name ], & | ||
104 |
6/8✗ Branch 0 not taken.
✓ Branch 1 taken 14 times.
✓ Branch 3 taken 30 times.
✓ Branch 4 taken 14 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 14 times.
✓ Branch 7 taken 30 times.
✓ Branch 8 taken 14 times.
|
74 | elements(2), dim=1) |
105 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 13 times.
|
14 | if(idx2.lt.1)then |
106 | 1 | call get_element_properties(elements(2), radius=radius2) | |
107 | element_database = [ element_database, & | ||
108 |
11/16✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✓ Branch 7 taken 3 times.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 1 times.
✓ Branch 15 taken 3 times.
✓ Branch 16 taken 1 times.
|
9 | element_type(name=elements(2), radius=radius2) ] |
109 | 1 | idx2 = size(element_database) | |
110 | end if | ||
111 | radius = ( element_database(idx1)%radius + & | ||
112 | 14 | element_database(idx2)%radius ) / 2._real32 | |
113 |
2/2✓ Branch 0 taken 6 times.
✓ Branch 1 taken 8 times.
|
14 | if(.not.allocated(element_bond_database)) & |
114 |
4/8✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 6 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 6 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 6 times.
|
6 | allocate(element_bond_database(0)) |
115 | element_bond_database = [ element_bond_database, & | ||
116 | element_bond_type(elements=[ & | ||
117 | elements(1), & | ||
118 | elements(2) & | ||
119 | ], radius=radius) & | ||
120 |
13/18✗ Branch 0 not taken.
✓ Branch 1 taken 14 times.
✓ Branch 3 taken 21 times.
✓ Branch 4 taken 14 times.
✓ Branch 5 taken 28 times.
✓ Branch 6 taken 14 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 14 times.
✓ Branch 9 taken 35 times.
✓ Branch 10 taken 14 times.
✓ Branch 11 taken 14 times.
✗ Branch 12 not taken.
✗ Branch 13 not taken.
✓ Branch 14 taken 14 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 14 times.
✓ Branch 17 taken 35 times.
✓ Branch 18 taken 14 times.
|
133 | ] |
121 | call sort_str( & | ||
122 | element_bond_database(size(element_bond_database))%element & | ||
123 | 14 | ) | |
124 | |||
125 | 14 | end subroutine set_bond_radius_to_default | |
126 | !############################################################################### | ||
127 | |||
128 | |||
129 | !############################################################################### | ||
130 | 27 | subroutine calculate(this, basis, & | |
131 | nbins, width, sigma, cutoff_min, cutoff_max, radius_distance_tol) | ||
132 | !! Calculate the distribution functions for the container. | ||
133 | !! | ||
134 | !! This procedure calculates the 2-, 3-, and 4-body distribution function | ||
135 | !! for a given atomic structure (i.e. basis). | ||
136 | implicit none | ||
137 | |||
138 | ! Arguments | ||
139 | class(distribs_type), intent(inout) :: this | ||
140 | !! Parent of the procedure. Instance of distribution functions container. | ||
141 | type(basis_type), intent(in) :: basis | ||
142 | !! Atomic structure. | ||
143 | integer, dimension(3), intent(in), optional :: nbins | ||
144 | !! Optional. Number of bins for the distribution functions. | ||
145 | real(real32), dimension(3), intent(in), optional :: width, sigma | ||
146 | !! Optional. Width and sigma for the distribution functions. | ||
147 | real(real32), dimension(3), intent(in), optional :: cutoff_min, cutoff_max | ||
148 | !! Optional. Cutoff minimum and maximum for the distribution functions. | ||
149 | real(real32), dimension(4), intent(in), optional :: radius_distance_tol | ||
150 | !! Tolerance for the distance between atoms for 3- and 4-body. | ||
151 | |||
152 | ! Local variables | ||
153 | integer, dimension(3) :: nbins_ | ||
154 | !! Number of bins for the distribution functions. | ||
155 | real(real32), dimension(3) :: sigma_ | ||
156 | !! Sigma for the distribution functions. | ||
157 | real(real32), dimension(3) :: width_ | ||
158 | !! Width of the bins for the distribution functions. | ||
159 | real(real32), dimension(3) :: cutoff_min_ | ||
160 | !! Cutoff minimum for the distribution functions. | ||
161 | real(real32), dimension(3) :: cutoff_max_ | ||
162 | !! Cutoff maximum for the distribution functions. | ||
163 | 27 | type(element_bond_type), dimension(:), allocatable :: bond_info | |
164 | !! Bond information for radii. | ||
165 | real(real32), dimension(4) :: radius_distance_tol_ | ||
166 | !! Tolerance for the distance between atoms for 3- and 4-body. | ||
167 | |||
168 | |||
169 | integer :: i, b, itmp1, idx | ||
170 | !! Loop index. | ||
171 | integer :: is, js, ia, ja, ka, la | ||
172 | !! Loop index. | ||
173 | integer :: num_pairs | ||
174 | !! Number of pairs and angles. | ||
175 | real(real32) :: bondlength | ||
176 | !! Temporary real variables. | ||
177 | logical :: success | ||
178 | !! Boolean for success. | ||
179 |
6/6✓ Branch 0 taken 81 times.
✓ Branch 1 taken 27 times.
✓ Branch 2 taken 243 times.
✓ Branch 3 taken 81 times.
✓ Branch 4 taken 81 times.
✓ Branch 5 taken 27 times.
|
432 | type(extended_basis_type) :: basis_extd |
180 | !! Extended basis of the system. | ||
181 |
6/6✓ Branch 0 taken 81 times.
✓ Branch 1 taken 27 times.
✓ Branch 2 taken 243 times.
✓ Branch 3 taken 81 times.
✓ Branch 4 taken 81 times.
✓ Branch 5 taken 27 times.
|
432 | type(extended_basis_type) :: neighbour_basis |
182 | !! Basis for storing neighbour data. | ||
183 | real(real32), dimension(3) :: eta | ||
184 | !! Parameters for the distribution functions. | ||
185 | 27 | real(real32), allocatable, dimension(:) :: angle_list, bondlength_list, & | |
186 | 27 | distance | |
187 | !! Temporary real arrays. | ||
188 | 27 | integer, allocatable, dimension(:,:) :: pair_index | |
189 | !! Index of element pairs. | ||
190 | |||
191 | |||
192 | !--------------------------------------------------------------------------- | ||
193 | ! initialise optional variables | ||
194 | !--------------------------------------------------------------------------- | ||
195 |
1/2✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
|
27 | if(present(cutoff_min))then |
196 | 27 | cutoff_min_ = cutoff_min | |
197 | else | ||
198 | ✗ | cutoff_min_ = [0.5_real32, 0._real32, 0._real32] | |
199 | end if | ||
200 |
1/2✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
|
27 | if(present(cutoff_max))then |
201 | 27 | cutoff_max_ = cutoff_max | |
202 | else | ||
203 | ✗ | cutoff_max_ = [6._real32, pi, pi] | |
204 | end if | ||
205 |
1/2✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
|
27 | if(present(width))then |
206 | 27 | width_ = width | |
207 | else | ||
208 | ✗ | width_ = [0.25_real32, pi/64._real32, pi/64._real32] | |
209 | end if | ||
210 |
1/2✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
|
27 | if(present(sigma))then |
211 | 27 | sigma_ = sigma | |
212 | else | ||
213 | ✗ | sigma_ = [0.1_real32, 0.1_real32, 0.1_real32] | |
214 | end if | ||
215 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 27 times.
|
27 | if(present(nbins))then |
216 | ✗ | nbins_ = nbins | |
217 | ✗ | width_ = ( cutoff_max_ - cutoff_min_ )/real( nbins_ - 1, real32 ) | |
218 | else | ||
219 |
2/2✓ Branch 0 taken 81 times.
✓ Branch 1 taken 27 times.
|
108 | nbins_ = 1 + nint( (cutoff_max_ - cutoff_min_)/width_ ) |
220 | end if | ||
221 |
1/2✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
|
27 | if(present(radius_distance_tol))then |
222 | 27 | radius_distance_tol_ = radius_distance_tol | |
223 | else | ||
224 | ✗ | radius_distance_tol_ = [1.5_real32, 2.5_real32, 3._real32, 6._real32] | |
225 | end if | ||
226 | |||
227 | |||
228 | |||
229 | !--------------------------------------------------------------------------- | ||
230 | ! get the number of pairs of species | ||
231 | ! (this uses a combination calculator with repetition) | ||
232 | !--------------------------------------------------------------------------- | ||
233 | num_pairs = nint( & | ||
234 | gamma(real(basis%nspec + 2, real32)) / & | ||
235 | ( gamma(real(basis%nspec, real32)) * gamma( 3._real32 ) ) & | ||
236 | 27 | ) | |
237 |
7/14✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 27 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 27 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 27 times.
|
27 | allocate(this%element_symbols(basis%nspec)) |
238 |
2/2✓ Branch 0 taken 34 times.
✓ Branch 1 taken 27 times.
|
61 | do is = 1, basis%nspec |
239 | 61 | this%element_symbols(is) = strip_null(basis%spec(is)%name) | |
240 | end do | ||
241 | 27 | i = 0 | |
242 |
9/16✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 27 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 27 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 27 times.
✓ Branch 17 taken 42 times.
✓ Branch 18 taken 27 times.
|
69 | allocate(bond_info(num_pairs)) |
243 |
9/18✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✓ Branch 4 taken 27 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 27 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 27 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 27 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 27 times.
|
27 | allocate(pair_index(basis%nspec,basis%nspec)) |
244 |
2/2✓ Branch 0 taken 34 times.
✓ Branch 1 taken 27 times.
|
61 | do is = 1, basis%nspec, 1 |
245 |
2/2✓ Branch 0 taken 42 times.
✓ Branch 1 taken 34 times.
|
103 | do js = is, basis%nspec, 1 |
246 | 42 | i = i + 1 | |
247 | 42 | pair_index(js,is) = i | |
248 | 42 | pair_index(is,js) = i | |
249 | call bond_info(i)%set( & | ||
250 | this%element_symbols(is), & | ||
251 | this%element_symbols(js), success & | ||
252 | 42 | ) | |
253 |
2/2✓ Branch 0 taken 28 times.
✓ Branch 1 taken 14 times.
|
42 | if(success) cycle |
254 | call set_bond_radius_to_default( [ & | ||
255 | this%element_symbols(is), & | ||
256 | this%element_symbols(js) & | ||
257 |
2/2✓ Branch 0 taken 28 times.
✓ Branch 1 taken 14 times.
|
42 | ] ) |
258 | call bond_info(i)%set( & | ||
259 | this%element_symbols(is), & | ||
260 | this%element_symbols(js), success & | ||
261 | 48 | ) | |
262 | end do | ||
263 | end do | ||
264 | |||
265 | |||
266 | !--------------------------------------------------------------------------- | ||
267 | ! get the stoichiometry, energy, and number of atoms | ||
268 | !--------------------------------------------------------------------------- | ||
269 |
4/8✗ Branch 0 not taken.
✓ Branch 1 taken 27 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✓ Branch 4 taken 27 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 34 times.
✓ Branch 7 taken 27 times.
|
61 | this%stoichiometry = basis%spec(:)%num |
270 | 27 | this%energy = basis%energy | |
271 | 27 | this%num_atoms = basis%natom | |
272 | |||
273 | |||
274 | !--------------------------------------------------------------------------- | ||
275 | ! calculate the gaussian width and allocate the distribution functions | ||
276 | !--------------------------------------------------------------------------- | ||
277 |
2/2✓ Branch 0 taken 81 times.
✓ Branch 1 taken 27 times.
|
108 | eta = 1._real32 / ( 2._real32 * sigma_**2._real32 ) |
278 |
9/16✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 27 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 27 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 27 times.
✓ Branch 17 taken 42 times.
✓ Branch 18 taken 27 times.
|
69 | allocate(this%num_pairs(num_pairs), source = 0) |
279 |
9/16✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 27 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 27 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 27 times.
✓ Branch 17 taken 34 times.
✓ Branch 18 taken 27 times.
|
61 | allocate(this%num_per_species(basis%nspec), source = 0) |
280 |
9/16✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 27 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 27 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 27 times.
✓ Branch 17 taken 42 times.
✓ Branch 18 taken 27 times.
|
69 | allocate(this%weight_pair(num_pairs), source = 0._real32) |
281 |
9/16✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 27 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 27 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 27 times.
✓ Branch 17 taken 34 times.
✓ Branch 18 taken 27 times.
|
61 | allocate(this%weight_per_species(basis%nspec), source = 0._real32) |
282 |
13/22✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✓ Branch 4 taken 27 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 27 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 27 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 27 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 27 times.
✓ Branch 21 taken 42 times.
✓ Branch 22 taken 27 times.
✓ Branch 23 taken 9282 times.
✓ Branch 24 taken 42 times.
|
9351 | allocate(this%df_2body(nbins_(1), num_pairs), source = 0._real32) |
283 |
13/22✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✓ Branch 4 taken 27 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 27 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 27 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 27 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 27 times.
✓ Branch 21 taken 34 times.
✓ Branch 22 taken 27 times.
✓ Branch 23 taken 2754 times.
✓ Branch 24 taken 34 times.
|
2815 | allocate(this%df_3body(nbins_(2), basis%nspec), source = 0._real32) |
284 |
13/22✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✓ Branch 4 taken 27 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 27 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 27 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 27 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 27 times.
✓ Branch 21 taken 34 times.
✓ Branch 22 taken 27 times.
✓ Branch 23 taken 2754 times.
✓ Branch 24 taken 34 times.
|
2815 | allocate(this%df_4body(nbins_(3), basis%nspec), source = 0._real32) |
285 | |||
286 | |||
287 | !--------------------------------------------------------------------------- | ||
288 | ! create the extended basis and neighbour basis | ||
289 | !--------------------------------------------------------------------------- | ||
290 | 27 | call basis_extd%copy(basis) | |
291 | 27 | call basis_extd%create_images( max_bondlength = cutoff_max_(1) ) | |
292 |
7/14✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 27 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 27 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 27 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 27 times.
|
27 | allocate(bondlength_list(basis_extd%natom+basis_extd%num_images)) |
293 | |||
294 |
7/12✗ Branch 0 not taken.
✓ Branch 1 taken 27 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 27 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✓ Branch 9 taken 27 times.
✓ Branch 10 taken 27 times.
✓ Branch 11 taken 27 times.
✗ Branch 12 not taken.
✗ Branch 13 not taken.
✓ Branch 14 taken 27 times.
|
54 | allocate(neighbour_basis%spec(1)) |
295 |
7/12✗ Branch 0 not taken.
✓ Branch 1 taken 27 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 27 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✓ Branch 9 taken 27 times.
✓ Branch 10 taken 27 times.
✓ Branch 11 taken 27 times.
✗ Branch 12 not taken.
✗ Branch 13 not taken.
✓ Branch 14 taken 27 times.
|
54 | allocate(neighbour_basis%image_spec(1)) |
296 | ✗ | allocate(neighbour_basis%spec(1)%atom( & | |
297 | sum(basis_extd%spec(:)%num)+sum(basis_extd%image_spec(:)%num), 3 & | ||
298 |
12/20✓ Branch 0 taken 34 times.
✓ Branch 1 taken 27 times.
✓ Branch 2 taken 34 times.
✓ Branch 3 taken 27 times.
✓ Branch 4 taken 27 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 27 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 27 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 27 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 27 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 27 times.
|
95 | ) ) |
299 | ✗ | allocate(neighbour_basis%image_spec(1)%atom( & | |
300 | sum(basis_extd%spec(:)%num)+sum(basis_extd%image_spec(:)%num), 3 & | ||
301 |
12/20✓ Branch 0 taken 34 times.
✓ Branch 1 taken 27 times.
✓ Branch 2 taken 34 times.
✓ Branch 3 taken 27 times.
✓ Branch 4 taken 27 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 27 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 27 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 27 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 27 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 27 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 27 times.
|
95 | ) ) |
302 | 27 | neighbour_basis%nspec = basis%nspec | |
303 | 27 | neighbour_basis%natom = 0 | |
304 | 27 | neighbour_basis%num_images = 0 | |
305 |
4/4✓ Branch 0 taken 81 times.
✓ Branch 1 taken 27 times.
✓ Branch 2 taken 243 times.
✓ Branch 3 taken 81 times.
|
351 | neighbour_basis%lat = basis%lat |
306 | |||
307 | |||
308 | !--------------------------------------------------------------------------- | ||
309 | ! calculate the distribution functions | ||
310 | !--------------------------------------------------------------------------- | ||
311 |
2/2✓ Branch 0 taken 34 times.
✓ Branch 1 taken 27 times.
|
61 | do is = 1, basis%nspec |
312 |
2/2✓ Branch 0 taken 185 times.
✓ Branch 1 taken 34 times.
|
246 | do ia = 1, basis%spec(is)%num |
313 |
7/14✓ Branch 0 taken 185 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 185 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 185 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 185 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 185 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 185 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 185 times.
|
185 | allocate(distance(basis_extd%natom+basis_extd%num_images)) |
314 | 185 | neighbour_basis%spec(1)%num = 0 | |
315 | 185 | neighbour_basis%image_spec(1)%num = 0 | |
316 |
2/2✓ Branch 0 taken 235 times.
✓ Branch 1 taken 185 times.
|
420 | do js = 1, basis%nspec |
317 | 235 | itmp1 = 0 | |
318 | |||
319 | !------------------------------------------------------------------ | ||
320 | ! loop over all atoms inside the unit cell | ||
321 | !------------------------------------------------------------------ | ||
322 |
2/2✓ Branch 0 taken 1377 times.
✓ Branch 1 taken 235 times.
|
1612 | atom_loop: do ja = 1, basis_extd%spec(js)%num |
323 | |||
324 | associate( vector => matmul( & | ||
325 | [ & | ||
326 | basis_extd%spec(js)%atom(ja,1:3) - & | ||
327 | basis_extd%spec(is)%atom(ia,1:3) & | ||
328 | ], basis_extd%lat ) & | ||
329 | 235 | ) | |
330 | 1377 | bondlength = modu( vector ) | |
331 | |||
332 | if( & | ||
333 | 1377 | bondlength .lt. cutoff_min_(1) .or. & | |
334 | bondlength .gt. cutoff_max_(1) & | ||
335 | 185 | ) cycle atom_loop | |
336 | |||
337 | ! add 2-body bond to store if within tolerances for 3-body | ||
338 | ! distance | ||
339 | if( & | ||
340 | bondlength .ge. ( & | ||
341 | bond_info(pair_index(is, js))%radius_covalent * & | ||
342 | radius_distance_tol_(1) & | ||
343 |
2/2✓ Branch 0 taken 406 times.
✓ Branch 1 taken 786 times.
|
1192 | ) .and. & |
344 | bondlength .le. ( & | ||
345 | bond_info(pair_index(is, js))%radius_covalent * & | ||
346 | radius_distance_tol_(2) & | ||
347 | ) & | ||
348 | ) then | ||
349 | neighbour_basis%spec(1)%num = & | ||
350 | 406 | neighbour_basis%spec(1)%num + 1 | |
351 | neighbour_basis%spec(1)%atom( & | ||
352 |
2/2✓ Branch 0 taken 1218 times.
✓ Branch 1 taken 406 times.
|
1624 | neighbour_basis%spec(1)%num,1:3) = vector |
353 | end if | ||
354 | |||
355 | ! add 2-body bond to store if within tolerances for 4-body | ||
356 | ! distance | ||
357 | if( & | ||
358 | bondlength .ge. ( & | ||
359 | bond_info(pair_index(is, js))%radius_covalent * & | ||
360 | radius_distance_tol_(3) & | ||
361 |
2/2✓ Branch 0 taken 724 times.
✓ Branch 1 taken 468 times.
|
1192 | ) .and. & |
362 | bondlength .le. ( & | ||
363 | bond_info(pair_index(is, js))%radius_covalent * & | ||
364 | radius_distance_tol_(4) & | ||
365 | ) & | ||
366 | ) then | ||
367 | neighbour_basis%image_spec(1)%num = & | ||
368 | 724 | neighbour_basis%image_spec(1)%num + 1 | |
369 | neighbour_basis%image_spec(1)%atom( & | ||
370 |
2/2✓ Branch 0 taken 2172 times.
✓ Branch 1 taken 724 times.
|
2896 | neighbour_basis%image_spec(1)%num,1:3) = vector |
371 | end if | ||
372 | |||
373 | !if(js.lt.js.or.(is.eq.js.and.ja.le.ia)) cycle | ||
374 | 1192 | itmp1 = itmp1 + 1 | |
375 | 1192 | bondlength_list(itmp1) = bondlength | |
376 |
6/6✓ Branch 0 taken 4131 times.
✓ Branch 1 taken 1377 times.
✓ Branch 2 taken 4131 times.
✓ Branch 3 taken 1377 times.
✓ Branch 5 taken 185 times.
✓ Branch 6 taken 1192 times.
|
10831 | distance(itmp1) = 1._real32 |
377 | |||
378 | end associate | ||
379 | end do atom_loop | ||
380 | |||
381 | |||
382 | !------------------------------------------------------------------ | ||
383 | ! loop over all image atoms outside of the unit cell | ||
384 | !------------------------------------------------------------------ | ||
385 |
2/2✓ Branch 0 taken 70704 times.
✓ Branch 1 taken 235 times.
|
70939 | image_loop: do ja = 1, basis_extd%image_spec(js)%num |
386 | associate( vector => matmul( & | ||
387 | [ & | ||
388 | basis_extd%image_spec(js)%atom(ja,1:3) - & | ||
389 | basis_extd%spec(is)%atom(ia,1:3) & | ||
390 | ], basis_extd%lat ) & | ||
391 | 235 | ) | |
392 | |||
393 | 70704 | bondlength = modu( vector ) | |
394 | |||
395 | if( & | ||
396 | 70704 | bondlength .lt. cutoff_min_(1) .or. & | |
397 | bondlength .gt. cutoff_max_(1) & | ||
398 | 47478 | ) cycle image_loop | |
399 | |||
400 | ! add 2-body bond to store if within tolerances for 3-body | ||
401 | ! distance | ||
402 | if( & | ||
403 | bondlength .ge. ( & | ||
404 | bond_info(pair_index(is, js))%radius_covalent * & | ||
405 | radius_distance_tol_(1) & | ||
406 |
2/2✓ Branch 0 taken 628 times.
✓ Branch 1 taken 22598 times.
|
23226 | ) .and. & |
407 | bondlength .le. ( & | ||
408 | bond_info(pair_index(is, js))%radius_covalent * & | ||
409 | radius_distance_tol_(2) & | ||
410 | ) & | ||
411 | ) then | ||
412 | neighbour_basis%spec(1)%num = & | ||
413 | 628 | neighbour_basis%spec(1)%num + 1 | |
414 | neighbour_basis%spec(1)%atom( & | ||
415 | neighbour_basis%spec(1)%num,1:3 & | ||
416 |
2/2✓ Branch 0 taken 1884 times.
✓ Branch 1 taken 628 times.
|
2512 | ) = vector |
417 | end if | ||
418 | |||
419 | ! add 2-body bond to store if within tolerances for 4-body | ||
420 | ! distance | ||
421 | if( & | ||
422 | bondlength .ge. ( & | ||
423 | bond_info(pair_index(is, js))%radius_covalent * & | ||
424 | radius_distance_tol_(3) & | ||
425 |
2/2✓ Branch 0 taken 9286 times.
✓ Branch 1 taken 13940 times.
|
23226 | ) .and. & |
426 | bondlength .le. ( & | ||
427 | bond_info(pair_index(is, js))%radius_covalent * & | ||
428 | radius_distance_tol_(4) & | ||
429 | ) & | ||
430 | ) then | ||
431 | neighbour_basis%image_spec(1)%num = & | ||
432 | 9286 | neighbour_basis%image_spec(1)%num + 1 | |
433 | neighbour_basis%image_spec(1)%atom( & | ||
434 | neighbour_basis%image_spec(1)%num,1:3 & | ||
435 |
2/2✓ Branch 0 taken 27858 times.
✓ Branch 1 taken 9286 times.
|
37144 | ) = vector |
436 | end if | ||
437 | |||
438 | 23226 | itmp1 = itmp1 + 1 | |
439 | 23226 | bondlength_list(itmp1) = bondlength | |
440 |
6/6✓ Branch 0 taken 212112 times.
✓ Branch 1 taken 70704 times.
✓ Branch 2 taken 212112 times.
✓ Branch 3 taken 70704 times.
✓ Branch 5 taken 47478 times.
✓ Branch 6 taken 23226 times.
|
518154 | distance(itmp1) = 1._real32 |
441 | |||
442 | end associate | ||
443 | end do image_loop | ||
444 | |||
445 | !------------------------------------------------------------------ | ||
446 | ! calculate the 2-body distribution function contributions from | ||
447 | ! atom (is,ia) for species pair (is,js) | ||
448 | !------------------------------------------------------------------ | ||
449 |
1/2✓ Branch 0 taken 235 times.
✗ Branch 1 not taken.
|
420 | if(itmp1.gt.0)then |
450 | this%df_2body(:,pair_index(is, js)) = & | ||
451 | this%df_2body(:,pair_index(is, js)) + & | ||
452 | get_distrib( & | ||
453 | bondlength_list(:itmp1), & | ||
454 | nbins_(1), eta(1), width_(1), & | ||
455 | cutoff_min_(1), & | ||
456 | scale_list = distance(:itmp1) & | ||
457 |
3/4✗ Branch 0 not taken.
✓ Branch 1 taken 235 times.
✓ Branch 3 taken 51935 times.
✓ Branch 4 taken 235 times.
|
52170 | ) |
458 | this%weight_pair(pair_index(is, js)) = & | ||
459 | this%weight_pair(pair_index(is, js)) + & | ||
460 | 4._real32 * sum( & | ||
461 | ( & | ||
462 | bond_info(pair_index(is, js))%radius_covalent / & | ||
463 | bondlength_list(:itmp1) ) ** 2 & | ||
464 |
2/2✓ Branch 0 taken 24418 times.
✓ Branch 1 taken 235 times.
|
24653 | ) |
465 | this%num_pairs(pair_index(is, js)) = & | ||
466 | 235 | this%num_pairs(pair_index(is, js)) + itmp1 | |
467 | this%weight_per_species(is) = & | ||
468 | this%weight_per_species(is) + & | ||
469 | 4._real32 * sum( & | ||
470 | ( & | ||
471 | bond_info(pair_index(is, js))%radius_covalent / & | ||
472 | bondlength_list(:itmp1) ) ** 2 & | ||
473 |
2/2✓ Branch 0 taken 24418 times.
✓ Branch 1 taken 235 times.
|
24653 | ) |
474 | 235 | this%num_per_species(is) = this%num_per_species(is) + itmp1 | |
475 | end if | ||
476 | |||
477 | end do | ||
478 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 185 times.
|
185 | deallocate(distance) |
479 | |||
480 | |||
481 | !--------------------------------------------------------------------- | ||
482 | ! calculate the 3-body distribution function for atom (is,ia) | ||
483 | !--------------------------------------------------------------------- | ||
484 |
2/2✓ Branch 0 taken 12 times.
✓ Branch 1 taken 173 times.
|
185 | if(neighbour_basis%spec(1)%num.le.1) cycle |
485 | associate( & | ||
486 | num_angles => & | ||
487 | triangular_number( neighbour_basis%spec(1)%num - 1 ) & | ||
488 | ) | ||
489 |
14/28✓ Branch 1 taken 173 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✓ Branch 4 taken 173 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 173 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 173 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 173 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 173 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 173 times.
✓ Branch 18 taken 173 times.
✗ Branch 19 not taken.
✗ Branch 20 not taken.
✓ Branch 21 taken 173 times.
✗ Branch 22 not taken.
✓ Branch 23 taken 173 times.
✗ Branch 24 not taken.
✓ Branch 25 taken 173 times.
✗ Branch 26 not taken.
✓ Branch 27 taken 173 times.
✗ Branch 29 not taken.
✓ Branch 30 taken 173 times.
✗ Branch 32 not taken.
✓ Branch 33 taken 173 times.
|
173 | allocate( angle_list(num_angles), distance(num_angles) ) |
490 | end associate | ||
491 | 173 | do concurrent ( ja = 1:neighbour_basis%spec(1)%num:1 ) | |
492 |
2/2✓ Branch 0 taken 1034 times.
✓ Branch 1 taken 173 times.
|
1207 | do concurrent ( ka = ja + 1:neighbour_basis%spec(1)%num:1 ) |
493 | idx = nint( & | ||
494 | (ja - 1) * (neighbour_basis%spec(1)%num - ja / 2.0) + & | ||
495 | (ka - ja) & | ||
496 | 4541 | ) | |
497 | angle_list(idx) = get_angle( & | ||
498 | [ neighbour_basis%spec(1)%atom(ja,:3) ], & | ||
499 | [ neighbour_basis%spec(1)%atom(ka,:3) ] & | ||
500 |
12/16✗ Branch 0 not taken.
✓ Branch 1 taken 4541 times.
✓ Branch 3 taken 13623 times.
✓ Branch 4 taken 4541 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 4541 times.
✓ Branch 7 taken 13623 times.
✓ Branch 8 taken 4541 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 4541 times.
✓ Branch 12 taken 13623 times.
✓ Branch 13 taken 4541 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 4541 times.
✓ Branch 16 taken 13623 times.
✓ Branch 17 taken 4541 times.
|
59033 | ) |
501 | distance(idx) = & | ||
502 | ( & | ||
503 | modu(neighbour_basis%spec(1)%atom(ja,:3)) ** 2 * & | ||
504 | modu(neighbour_basis%spec(1)%atom(ka,:3)) ** 2 & | ||
505 |
2/2✓ Branch 0 taken 4541 times.
✓ Branch 1 taken 1034 times.
|
5575 | ) |
506 | end do | ||
507 | end do | ||
508 | ! a NaN in the angle refers to one where two of the vectors are | ||
509 | ! parallel, so the angle is undefined | ||
510 |
2/2✓ Branch 0 taken 4541 times.
✓ Branch 1 taken 173 times.
|
4714 | do i = 1, size(angle_list) |
511 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 4541 times.
|
4714 | if(isnan(angle_list(i)))then |
512 | ✗ | angle_list(i) = -huge(1._real32) | |
513 | ✗ | distance(i) = 1._real32 | |
514 | end if | ||
515 | end do | ||
516 | this%df_3body(:,is) = this%df_3body(:,is) + & | ||
517 | get_distrib( & | ||
518 | angle_list, & | ||
519 | nbins_(2), eta(2), width_(2), & | ||
520 | cutoff_min_(2), & | ||
521 | scale_list = distance & | ||
522 |
3/4✗ Branch 0 not taken.
✓ Branch 1 taken 173 times.
✓ Branch 3 taken 13013 times.
✓ Branch 4 taken 173 times.
|
13186 | ) |
523 |
2/4✗ Branch 0 not taken.
✓ Branch 1 taken 173 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 173 times.
|
173 | deallocate( angle_list, distance ) |
524 | |||
525 | |||
526 | !--------------------------------------------------------------------- | ||
527 | ! calculate the 4-body distribution function for atom (is,ia) | ||
528 | !--------------------------------------------------------------------- | ||
529 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 173 times.
|
173 | if(neighbour_basis%image_spec(1)%num.eq.0) cycle |
530 | associate( & | ||
531 | num_angles => & | ||
532 | triangular_number( neighbour_basis%spec(1)%num - 1 ) * & | ||
533 | neighbour_basis%image_spec(1)%num & | ||
534 | ) | ||
535 |
14/28✓ Branch 1 taken 173 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✓ Branch 4 taken 173 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 173 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 173 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 173 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 173 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 173 times.
✓ Branch 18 taken 173 times.
✗ Branch 19 not taken.
✗ Branch 20 not taken.
✓ Branch 21 taken 173 times.
✗ Branch 22 not taken.
✓ Branch 23 taken 173 times.
✗ Branch 24 not taken.
✓ Branch 25 taken 173 times.
✗ Branch 26 not taken.
✓ Branch 27 taken 173 times.
✗ Branch 29 not taken.
✓ Branch 30 taken 173 times.
✗ Branch 32 not taken.
✓ Branch 33 taken 173 times.
|
173 | allocate( angle_list(num_angles), distance(num_angles) ) |
536 | end associate | ||
537 | 173 | idx = 0 | |
538 | do concurrent ( & | ||
539 | ja = 1:neighbour_basis%spec(1)%num:1, & | ||
540 | la = 1:neighbour_basis%image_spec(1)%num:1 & | ||
541 | 10151 | ) | |
542 |
4/4✓ Branch 0 taken 9978 times.
✓ Branch 1 taken 173 times.
✓ Branch 2 taken 61308 times.
✓ Branch 3 taken 9978 times.
|
71459 | do concurrent ( ka = ja + 1:neighbour_basis%spec(1)%num:1 ) |
543 | idx = nint( & | ||
544 | (ja - 1) * (neighbour_basis%spec(1)%num - ja / 2.0) + & | ||
545 | (ka - ja - 1) & | ||
546 | 278094 | ) * neighbour_basis%image_spec(1)%num + la | |
547 | angle_list(idx) = & | ||
548 | get_improper_dihedral_angle( & | ||
549 | [ neighbour_basis%spec(1)%atom(ja,:3) ], & | ||
550 | [ neighbour_basis%spec(1)%atom(ka,:3) ], & | ||
551 | [ neighbour_basis%image_spec(1)%atom(la,:3) ] & | ||
552 |
18/24✗ Branch 0 not taken.
✓ Branch 1 taken 278094 times.
✓ Branch 3 taken 834282 times.
✓ Branch 4 taken 278094 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 278094 times.
✓ Branch 7 taken 834282 times.
✓ Branch 8 taken 278094 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 278094 times.
✓ Branch 12 taken 834282 times.
✓ Branch 13 taken 278094 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 278094 times.
✓ Branch 16 taken 834282 times.
✓ Branch 17 taken 278094 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 278094 times.
✓ Branch 21 taken 834282 times.
✓ Branch 22 taken 278094 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 278094 times.
✓ Branch 25 taken 834282 times.
✓ Branch 26 taken 278094 times.
|
5283786 | ) |
553 | distance(idx) = & | ||
554 | modu(neighbour_basis%spec(1)%atom(ja,:3)) ** 2 * & | ||
555 | modu(neighbour_basis%spec(1)%atom(ka,:3)) ** 2 * & | ||
556 |
2/2✓ Branch 0 taken 278094 times.
✓ Branch 1 taken 61308 times.
|
339402 | modu(neighbour_basis%image_spec(1)%atom(la,:3)) ** 2 |
557 | end do | ||
558 | end do | ||
559 | ! a NaN in the angle refers to one where two of the vectors are | ||
560 | ! parallel, so the angle is undefined | ||
561 |
2/2✓ Branch 0 taken 278094 times.
✓ Branch 1 taken 173 times.
|
278267 | do i = 1, size(angle_list) |
562 |
2/2✓ Branch 0 taken 18230 times.
✓ Branch 1 taken 259864 times.
|
278267 | if(isnan(angle_list(i)))then |
563 | 18230 | angle_list(i) = -huge(1._real32) | |
564 | 18230 | distance(i) = 1._real32 | |
565 | end if | ||
566 | end do | ||
567 | this%df_4body(:,is) = this%df_4body(:,is) + & | ||
568 | get_distrib( & | ||
569 | angle_list, & | ||
570 | nbins_(3), eta(3), width_(3), & | ||
571 | cutoff_min_(3), & | ||
572 | scale_list = distance & | ||
573 |
3/4✗ Branch 0 not taken.
✓ Branch 1 taken 173 times.
✓ Branch 3 taken 13013 times.
✓ Branch 4 taken 173 times.
|
13186 | ) |
574 |
2/4✗ Branch 0 not taken.
✓ Branch 1 taken 173 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 173 times.
|
207 | deallocate( angle_list, distance ) |
575 | |||
576 | end do | ||
577 | end do | ||
578 | |||
579 | !--------------------------------------------------------------------------- | ||
580 | ! apply the cutoff function to the 2-body distribution function | ||
581 | !--------------------------------------------------------------------------- | ||
582 |
2/2✓ Branch 0 taken 5967 times.
✓ Branch 1 taken 27 times.
|
5994 | do b = 1, nbins_(1) |
583 | this%df_2body(b,:) = this%df_2body(b,:) / ( cutoff_min_(1) + & | ||
584 |
2/2✓ Branch 0 taken 9282 times.
✓ Branch 1 taken 5967 times.
|
15276 | width_(1) * real(b-1, real32) ) ** 2 |
585 | end do | ||
586 | |||
587 | |||
588 | !--------------------------------------------------------------------------- | ||
589 | ! renormalise the distribution functions so that area under the curve is 1 | ||
590 | !--------------------------------------------------------------------------- | ||
591 |
2/2✓ Branch 0 taken 42 times.
✓ Branch 1 taken 27 times.
|
69 | do i = 1, num_pairs |
592 |
4/6✓ Branch 0 taken 2213 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 42 times.
✓ Branch 3 taken 2171 times.
✓ Branch 4 taken 42 times.
✗ Branch 5 not taken.
|
2240 | if(any(abs(this%df_2body(:,i)).gt.1.E-6))then |
593 |
4/4✓ Branch 0 taken 9282 times.
✓ Branch 1 taken 42 times.
✓ Branch 2 taken 9282 times.
✓ Branch 3 taken 42 times.
|
18606 | this%df_2body(:,i) = this%df_2body(:,i) / sum(this%df_2body(:,i)) |
594 | end if | ||
595 | end do | ||
596 |
2/2✓ Branch 0 taken 34 times.
✓ Branch 1 taken 27 times.
|
61 | do is = 1, basis%nspec |
597 |
6/6✓ Branch 0 taken 1066 times.
✓ Branch 1 taken 3 times.
✓ Branch 2 taken 31 times.
✓ Branch 3 taken 1035 times.
✓ Branch 4 taken 31 times.
✓ Branch 5 taken 3 times.
|
1069 | if(any(abs(this%df_3body(:,is)).gt.1.E-6))then |
598 |
4/4✓ Branch 0 taken 2559 times.
✓ Branch 1 taken 31 times.
✓ Branch 2 taken 2559 times.
✓ Branch 3 taken 31 times.
|
5149 | this%df_3body(:,is) = this%df_3body(:,is) / sum(this%df_3body(:,is)) |
599 | end if | ||
600 |
6/6✓ Branch 0 taken 226 times.
✓ Branch 1 taken 3 times.
✓ Branch 2 taken 31 times.
✓ Branch 3 taken 195 times.
✓ Branch 4 taken 31 times.
✓ Branch 5 taken 3 times.
|
256 | if(any(abs(this%df_4body(:,is)).gt.1.E-6))then |
601 |
4/4✓ Branch 0 taken 2559 times.
✓ Branch 1 taken 31 times.
✓ Branch 2 taken 2559 times.
✓ Branch 3 taken 31 times.
|
5149 | this%df_4body(:,is) = this%df_4body(:,is) / sum(this%df_4body(:,is)) |
602 | end if | ||
603 | end do | ||
604 | |||
605 | |||
606 | !--------------------------------------------------------------------------- | ||
607 | ! check for NaN in the distribution functions | ||
608 | !--------------------------------------------------------------------------- | ||
609 |
6/8✓ Branch 0 taken 42 times.
✓ Branch 1 taken 27 times.
✓ Branch 2 taken 9282 times.
✓ Branch 3 taken 42 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 9282 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
|
9351 | if(any(isnan(this%df_2body)))then |
610 | ✗ | call stop_program('NaN in 2-body distribution function') | |
611 | end if | ||
612 |
6/8✓ Branch 0 taken 34 times.
✓ Branch 1 taken 27 times.
✓ Branch 2 taken 2754 times.
✓ Branch 3 taken 34 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2754 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
|
2815 | if(any(isnan(this%df_3body)))then |
613 | ✗ | call stop_program('NaN in 3-body distribution function') | |
614 | end if | ||
615 |
6/8✓ Branch 0 taken 34 times.
✓ Branch 1 taken 27 times.
✓ Branch 2 taken 2754 times.
✓ Branch 3 taken 34 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2754 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
|
2815 | if(any(isnan(this%df_4body)))then |
616 | ✗ | call stop_program('NaN in 4-body distribution function') | |
617 | end if | ||
618 | |||
619 |
25/42✓ Branch 0 taken 27 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 27 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 27 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 27 times.
✓ Branch 7 taken 27 times.
✓ Branch 8 taken 27 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 27 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 27 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 27 times.
✓ Branch 15 taken 27 times.
✓ Branch 16 taken 27 times.
✗ Branch 17 not taken.
✗ Branch 18 not taken.
✓ Branch 19 taken 27 times.
✓ Branch 20 taken 27 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 27 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 27 times.
✗ Branch 25 not taken.
✓ Branch 26 taken 27 times.
✗ Branch 27 not taken.
✓ Branch 28 taken 34 times.
✓ Branch 29 taken 27 times.
✓ Branch 30 taken 34 times.
✗ Branch 31 not taken.
✓ Branch 32 taken 27 times.
✗ Branch 33 not taken.
✓ Branch 34 taken 27 times.
✗ Branch 35 not taken.
✓ Branch 36 taken 34 times.
✓ Branch 37 taken 27 times.
✓ Branch 38 taken 34 times.
✗ Branch 39 not taken.
✗ Branch 40 not taken.
✓ Branch 41 taken 27 times.
|
149 | end subroutine calculate |
620 | !############################################################################### | ||
621 | |||
622 | |||
623 | !############################################################################### | ||
624 |
1/2✓ Branch 0 taken 599 times.
✗ Branch 1 not taken.
|
599 | function get_distrib(value_list, nbins, eta, width, cutoff_min, & |
625 |
2/4✓ Branch 0 taken 599 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 599 times.
✗ Branch 3 not taken.
|
599 | scale_list ) result(output) |
626 | !! Calculate the angular distribution function for a list of values. | ||
627 | implicit none | ||
628 | |||
629 | ! Arguments | ||
630 | integer, intent(in) :: nbins | ||
631 | !! Number of bins for the distribution functions. | ||
632 | real(real32), intent(in) :: eta, width, cutoff_min | ||
633 | !! Parameters for the distribution functions. | ||
634 | real(real32), dimension(:), intent(in) :: value_list | ||
635 | !! List of angles. | ||
636 | real(real32), dimension(:), intent(in) :: scale_list | ||
637 | !! List of scaling for each angle (distance**3 or distance**4) | ||
638 | real(real32), dimension(nbins) :: output | ||
639 | !! Distribution function for the list of values. | ||
640 | |||
641 | ! Local variables | ||
642 | integer :: i, j, b, bin | ||
643 | !! Loop index. | ||
644 | integer :: max_num_steps | ||
645 | !! Maximum number of steps. | ||
646 | integer, dimension(3,2) :: loop_limits | ||
647 | !! Loop limits for the 3-body distribution function. | ||
648 | |||
649 | |||
650 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 599 times.
|
599 | max_num_steps = ceiling( sqrt(16._real32/eta) / width ) |
651 |
2/2✓ Branch 0 taken 81939 times.
✓ Branch 1 taken 599 times.
|
82538 | output = 0._real32 |
652 | |||
653 | !--------------------------------------------------------------------------- | ||
654 | ! calculate the distribution function for a list of values | ||
655 | !--------------------------------------------------------------------------- | ||
656 |
2/2✓ Branch 0 taken 307071 times.
✓ Branch 1 taken 599 times.
|
307670 | do i = 1, size(value_list), 1 |
657 | |||
658 | !------------------------------------------------------------------------ | ||
659 | ! get the bin closest to the value | ||
660 | !------------------------------------------------------------------------ | ||
661 | 307071 | bin = nint( ( value_list(i) - cutoff_min ) / width ) + 1 | |
662 | if( & | ||
663 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 307071 times.
|
307071 | bin .lt. 1 - max_num_steps .or. & |
664 | bin .gt. nbins + max_num_steps & | ||
665 | ✗ | ) cycle | |
666 | |||
667 | |||
668 | !------------------------------------------------------------------------ | ||
669 | ! calculate the gaussian for this bond | ||
670 | !------------------------------------------------------------------------ | ||
671 | loop_limits(:,1) = & | ||
672 |
2/2✓ Branch 0 taken 921213 times.
✓ Branch 1 taken 307071 times.
|
1228284 | [ min(nbins, bin), min(nbins, bin + max_num_steps), 1 ] |
673 | loop_limits(:,2) = & | ||
674 |
2/2✓ Branch 0 taken 921213 times.
✓ Branch 1 taken 307071 times.
|
1228284 | [ max(0, bin - 1), max(1, bin - max_num_steps), -1 ] |
675 | |||
676 | |||
677 | !------------------------------------------------------------------------ | ||
678 | ! do forward and backward loops to add gaussian from its centre | ||
679 | !------------------------------------------------------------------------ | ||
680 | 599 | do concurrent ( j = 1:2 ) | |
681 | do concurrent ( & | ||
682 | b = loop_limits(1,j):loop_limits(2,j):loop_limits(3,j) & | ||
683 |
2/2✓ Branch 0 taken 614142 times.
✓ Branch 1 taken 307071 times.
|
921213 | ) |
684 | output(b) = output(b) + & | ||
685 | exp( & | ||
686 | -eta * ( & | ||
687 | value_list(i) - & | ||
688 | ( width * real(b-1, real32) + cutoff_min ) & | ||
689 | ) ** 2._real32 & | ||
690 |
2/2✓ Branch 0 taken 7880674 times.
✓ Branch 1 taken 614142 times.
|
8494816 | ) / scale_list(i) |
691 | end do | ||
692 | end do | ||
693 | end do | ||
694 |
2/2✓ Branch 0 taken 81939 times.
✓ Branch 1 taken 599 times.
|
82538 | output = output * sqrt( eta / pi ) / real(size(value_list,1),real32) |
695 | |||
696 | 599 | end function get_distrib | |
697 | !############################################################################### | ||
698 | |||
699 | ✗ | end module raffle__distribs | |
700 |