Line | Branch | Exec | Source |
---|---|---|---|
1 | module raffle__place_methods | ||
2 | !! Module containing the placement methods available within RAFFLE. | ||
3 | !! | ||
4 | !! This module contains procedures to query points for atom placement. | ||
5 | !! The available placement methods are: | ||
6 | !! - void: place the atom in the gridpoint with the largest void space | ||
7 | !! - rand: place the atom at a random gridpoint | ||
8 | !! - walk: place the atom using a random walk method | ||
9 | !! - growth: place the atom using a random walk, with last placement point | ||
10 | !! as the starting point | ||
11 | !! - min: place the atom at the gridpoint with the highest viability | ||
12 | use raffle__constants, only: real32, pi | ||
13 | use raffle__misc_linalg, only: modu, inverse_3x3 | ||
14 | use raffle__geom_extd, only: extended_basis_type | ||
15 | use raffle__dist_calcs, only: & | ||
16 | get_min_dist, & | ||
17 | get_min_dist_between_point_and_species | ||
18 | use raffle__evaluator, only: evaluate_point | ||
19 | use raffle__distribs_container, only: distribs_container_type | ||
20 | implicit none | ||
21 | |||
22 | |||
23 | private | ||
24 | |||
25 | public :: & | ||
26 | place_method_void, place_method_rand, & | ||
27 | place_method_walk, place_method_growth, & | ||
28 | place_method_min | ||
29 | |||
30 | |||
31 | contains | ||
32 | |||
33 | !############################################################################### | ||
34 | 1 | function place_method_void( & | |
35 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | points, basis, atom_ignore_list, viable & |
36 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | ) result(point) |
37 | !! VOID placement method. | ||
38 | !! | ||
39 | !! This method returns the gridpoint with the lowest neighbour density. | ||
40 | !! i.e. the point with the lowest density in the cell. | ||
41 | implicit none | ||
42 | |||
43 | ! Arguments | ||
44 | real(real32), dimension(:,:), intent(in) :: points | ||
45 | !! List of gridpoints to consider. | ||
46 | type(extended_basis_type), intent(inout) :: basis | ||
47 | !! Structure to add atom to. | ||
48 | integer, dimension(:,:), intent(in) :: atom_ignore_list | ||
49 | !! List of atoms to ignore (i.e. indices of atoms not yet placed). | ||
50 | logical, intent(out) :: viable | ||
51 | !! Boolean to indicate if point is viable. | ||
52 | real(real32), dimension(3) :: point | ||
53 | !! Point to add atom to. | ||
54 | |||
55 | ! Local variables | ||
56 | integer :: best_gridpoint | ||
57 | !! Index of best gridpoint. | ||
58 | |||
59 | |||
60 | 1 | viable = .false. | |
61 | |||
62 | !--------------------------------------------------------------------------- | ||
63 | ! find the gridpoint with the largest void space | ||
64 | !--------------------------------------------------------------------------- | ||
65 |
6/10✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 943 times.
✓ Branch 7 taken 1 times.
✓ Branch 8 taken 12 times.
✓ Branch 9 taken 931 times.
|
944 | best_gridpoint = maxloc(points(4,:), dim=1) |
66 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | if(best_gridpoint.eq.0) return |
67 | |||
68 | |||
69 | !--------------------------------------------------------------------------- | ||
70 | ! return the gridpoint with the largest void space | ||
71 | !--------------------------------------------------------------------------- | ||
72 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | point = points(1:3,best_gridpoint) |
73 | 1 | viable = .true. | |
74 | |||
75 | end function place_method_void | ||
76 | !############################################################################### | ||
77 | |||
78 | |||
79 | !############################################################################### | ||
80 | 1 | function place_method_rand( distribs_container, & | |
81 | bounds, & | ||
82 |
2/4✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
|
1 | basis, atom_ignore_list, radius_list, max_attempts, viable & |
83 | 1 | ) result(point) | |
84 | !! Random placement method. | ||
85 | !! | ||
86 | !! This method places the atom at a random gridpoint. | ||
87 | implicit none | ||
88 | |||
89 | ! Arguments | ||
90 | type(distribs_container_type), intent(in) :: distribs_container | ||
91 | !! Distribution function (gvector) container. | ||
92 | real(real32), dimension(2,3), intent(in) :: bounds | ||
93 | !! Bounds of the unit cell. | ||
94 | type(extended_basis_type), intent(inout) :: basis | ||
95 | !! Structure to add atom to. | ||
96 | integer, dimension(:,:), intent(in) :: atom_ignore_list | ||
97 | !! List of atoms to ignore (i.e. indices of atoms not yet placed). | ||
98 | real(real32), dimension(:), intent(in) :: radius_list | ||
99 | !! List of radii for each pair of elements. | ||
100 | integer, intent(in) :: max_attempts | ||
101 | !! Limit on number of attempts. | ||
102 | logical, intent(out) :: viable | ||
103 | !! Boolean to indicate if point is viable. | ||
104 | real(real32), dimension(3) :: point | ||
105 | !! Point to add atom to. | ||
106 | |||
107 | ! Local variables | ||
108 | integer :: i, is, js | ||
109 | !! Loop indices. | ||
110 | real(real32) :: rtmp1 | ||
111 | !! random number. | ||
112 | real(real32), dimension(3) :: rvec1 | ||
113 | !! random vector. | ||
114 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | integer, dimension(basis%nspec,basis%nspec) :: pair_index |
115 | |||
116 | |||
117 | 1 | viable = .false. | |
118 | |||
119 | !--------------------------------------------------------------------------- | ||
120 | ! get list of element pair indices | ||
121 | ! (i.e. the index for bond_info for each element pair) | ||
122 | !--------------------------------------------------------------------------- | ||
123 | 1 | i = 0 | |
124 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | do is = 1, basis%nspec |
125 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
3 | do js = 1, basis%nspec |
126 | pair_index(is, js) = distribs_container%get_pair_index( & | ||
127 | basis%spec(is)%name, basis%spec(js)%name & | ||
128 | 2 | ) | |
129 | end do | ||
130 | end do | ||
131 | |||
132 | |||
133 | !--------------------------------------------------------------------------- | ||
134 | ! find a random gridpoint that is not too close to any other atom | ||
135 | !--------------------------------------------------------------------------- | ||
136 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | atom_loop: do i = 1, max_attempts |
137 | 1 | call random_number(rvec1) | |
138 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | point = bounds(1,:) + ( bounds(2,:) - bounds(1,:) ) * rvec1 |
139 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | do js = 1, basis%nspec |
140 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | if( & |
141 | get_min_dist_between_point_and_species( & | ||
142 | basis, point, & | ||
143 | species = js, & | ||
144 | ignore_list = atom_ignore_list & | ||
145 | ) .lt. radius_list(pair_index(atom_ignore_list(1,1),js)) * & | ||
146 | distribs_container%radius_distance_tol(1) & | ||
147 | 1 | )then | |
148 | ✗ | cycle atom_loop | |
149 | end if | ||
150 | end do | ||
151 | 1 | viable = .true. | |
152 | 1 | exit atom_loop | |
153 | end do atom_loop | ||
154 | |||
155 | 1 | end function place_method_rand | |
156 | !############################################################################### | ||
157 | |||
158 | |||
159 | !############################################################################### | ||
160 | 1 | function place_method_walk( distribs_container, & | |
161 | bounds, & | ||
162 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | basis, atom_ignore_list, & |
163 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | radius_list, max_attempts, & |
164 | step_size_coarse, step_size_fine, & | ||
165 | viable & | ||
166 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | ) result(point) |
167 | !! Random walk placement method. | ||
168 | !! | ||
169 | !! This method places the atom using a random walk method. | ||
170 | !! An initial point is chosen at random, and then points nearby are tested | ||
171 | !! to see if they are more suitable than the current point. If they are, | ||
172 | !! the query point is moved to the new point and the process is repeated. | ||
173 | !! The process is repeated, with each point being tested against a random | ||
174 | !! number. If the random number is less than the suitability of the point, | ||
175 | !! the atom is placed at that point. | ||
176 | implicit none | ||
177 | |||
178 | ! Arguments | ||
179 | type(distribs_container_type), intent(in) :: distribs_container | ||
180 | !! Distribution function (gvector) container. | ||
181 | real(real32), dimension(2,3), intent(in) :: bounds | ||
182 | !! Bounds of the unit cell. | ||
183 | type(extended_basis_type), intent(inout) :: basis | ||
184 | !! Structure to add atom to. | ||
185 | integer, intent(in) :: max_attempts | ||
186 | !! Limit on number of attempts. | ||
187 | real(real32), intent(in) :: step_size_coarse, step_size_fine | ||
188 | !! Step sizes for random walk. | ||
189 | logical, intent(out) :: viable | ||
190 | !! Boolean to indicate if point is viable. | ||
191 | integer, dimension(:,:), intent(in) :: atom_ignore_list | ||
192 | !! List of atoms to ignore (i.e. indices of atoms not yet placed). | ||
193 | real(real32), dimension(:), intent(in) :: radius_list | ||
194 | !! List of radii for each pair of elements. | ||
195 | real(real32), dimension(3) :: point | ||
196 | !! Point to add atom to. | ||
197 | |||
198 | ! Local variables | ||
199 | integer :: i, j | ||
200 | !! Loop indices. | ||
201 | integer :: nattempt, nstuck | ||
202 | !! Number of attempts and number of times stuck at same site | ||
203 | real(real32) :: rtmp1 | ||
204 | !! Random number. | ||
205 | real(real32), dimension(3) :: rvec1, abc | ||
206 | !! Random vector and lattice constants. | ||
207 | real(real32) :: crude_norm | ||
208 | !! Crude normalisation. | ||
209 | real(real32) :: site_value, test_value | ||
210 | !! Viability values. | ||
211 | real(real32), dimension(3) :: site_vector, test_vector | ||
212 | !! Vectors for gridpoints. | ||
213 | |||
214 | |||
215 | 1 | viable = .false. | |
216 | |||
217 | !--------------------------------------------------------------------------- | ||
218 | ! test a random point in the unit cell | ||
219 | !--------------------------------------------------------------------------- | ||
220 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | do i = 1, 3 |
221 | 4 | abc(i) = modu(basis%lat(i,:)) | |
222 | end do | ||
223 | 1 | i = 0 | |
224 | 452 | random_loop : do | |
225 | 453 | i = i + 1 | |
226 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 453 times.
|
453 | if(i.gt.max_attempts) return |
227 | 453 | call random_number(site_vector) | |
228 |
2/2✓ Branch 0 taken 1359 times.
✓ Branch 1 taken 453 times.
|
1812 | site_vector = bounds(1,:) + ( bounds(2,:) - bounds(1,:) ) * site_vector |
229 | |||
230 | site_value = evaluate_point( distribs_container, & | ||
231 | site_vector, atom_ignore_list(1,1), basis, & | ||
232 | atom_ignore_list, radius_list & | ||
233 | 453 | ) | |
234 | 453 | call random_number(rtmp1) | |
235 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 452 times.
|
453 | if(rtmp1.lt.site_value) exit random_loop |
236 | |||
237 | end do random_loop | ||
238 | |||
239 | |||
240 | !--------------------------------------------------------------------------- | ||
241 | ! now do a random walk to find a suitable point to place the atom | ||
242 | !--------------------------------------------------------------------------- | ||
243 | 1 | nattempt = 0 | |
244 | 1 | nstuck = 0 | |
245 | 1 | crude_norm = 0.5_real32 | |
246 | 1 | i = 0 | |
247 | 24 | walk_loop : do | |
248 | 25 | i = i + 1 | |
249 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 25 times.
|
25 | if(i.gt.max_attempts) return |
250 | !------------------------------------------------------------------------ | ||
251 | ! if we have tried 10 times, then we need to reduce the step size | ||
252 | ! get the new test point and map it back into the unit cell | ||
253 | !------------------------------------------------------------------------ | ||
254 | 25 | call random_number(rvec1) | |
255 |
2/2✓ Branch 0 taken 5 times.
✓ Branch 1 taken 20 times.
|
25 | if(nattempt.ge.10) then |
256 | test_vector = site_vector + & | ||
257 |
2/2✓ Branch 0 taken 15 times.
✓ Branch 1 taken 5 times.
|
20 | ( rvec1 * 2._real32 - 1._real32 ) * step_size_fine / abc |
258 | else | ||
259 | test_vector = site_vector + & | ||
260 |
2/2✓ Branch 0 taken 60 times.
✓ Branch 1 taken 20 times.
|
80 | ( rvec1 * 2._real32 - 1._real32 ) * step_size_coarse / abc |
261 | end if | ||
262 |
3/4✓ Branch 0 taken 75 times.
✓ Branch 1 taken 25 times.
✓ Branch 2 taken 75 times.
✗ Branch 3 not taken.
|
100 | test_vector = test_vector - floor(test_vector) |
263 |
2/2✓ Branch 0 taken 75 times.
✓ Branch 1 taken 25 times.
|
100 | do j = 1, 3 |
264 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 75 times.
|
75 | if(test_vector(j).lt.bounds(1,j) .or. test_vector(j).ge.bounds(2,j)) & |
265 | 25 | cycle walk_loop | |
266 | end do | ||
267 | |||
268 | !------------------------------------------------------------------------ | ||
269 | ! evaluate the test point | ||
270 | !------------------------------------------------------------------------ | ||
271 | test_value = evaluate_point( distribs_container, & | ||
272 | test_vector, atom_ignore_list(1,1), basis, & | ||
273 | atom_ignore_list, radius_list & | ||
274 | 25 | ) | |
275 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 25 times.
|
25 | if(test_value.lt.1.E-6) cycle walk_loop |
276 | !------------------------------------------------------------------------ | ||
277 | ! if viability of test point is less than current point, then we | ||
278 | ! are stuck at the current point and need to try again | ||
279 | !------------------------------------------------------------------------ | ||
280 |
2/2✓ Branch 0 taken 24 times.
✓ Branch 1 taken 1 times.
|
25 | if(test_value.lt.site_value) then |
281 | 24 | nstuck = nstuck + 1 | |
282 |
2/2✓ Branch 0 taken 15 times.
✓ Branch 1 taken 9 times.
|
24 | if(nstuck.ge.10) then |
283 | 15 | nattempt = nattempt + 1 | |
284 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 15 times.
|
15 | if(crude_norm.lt.site_value) & |
285 | crude_norm = ( & | ||
286 | crude_norm + site_value/real(nattempt) & | ||
287 | ✗ | ) / 2._real32 | |
288 | |||
289 | ! if we have tried 10 times, and still no luck, then we need to | ||
290 | ! reduce the tolerance | ||
291 |
2/2✓ Branch 0 taken 6 times.
✓ Branch 1 taken 9 times.
|
15 | if(nattempt.ge.10) site_value = site_value / crude_norm |
292 | 15 | call random_number(rtmp1) | |
293 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 14 times.
|
15 | if(rtmp1.lt.site_value) exit walk_loop |
294 | end if | ||
295 | else | ||
296 | 1 | nstuck = 0 | |
297 | 1 | site_vector = test_vector | |
298 | 1 | site_value = test_value | |
299 | |||
300 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | if(nattempt.ge.10) test_value = test_value / crude_norm |
301 | 1 | call random_number(rtmp1) | |
302 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | if(rtmp1.lt.test_value) exit walk_loop |
303 | end if | ||
304 | |||
305 | end do walk_loop | ||
306 | |||
307 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | point = site_vector |
308 | 1 | viable=.true. | |
309 | |||
310 | end function place_method_walk | ||
311 | !############################################################################### | ||
312 | |||
313 | |||
314 | !############################################################################### | ||
315 | 1 | function place_method_growth( distribs_container, & | |
316 | prior_point, prior_species, & | ||
317 | bounds, & | ||
318 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | basis, atom_ignore_list, & |
319 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | radius_list, max_attempts, & |
320 | step_size_coarse, step_size_fine, & | ||
321 | viable & | ||
322 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | ) result(point) |
323 | !! Random walk placement method. | ||
324 | !! | ||
325 | !! This method places the atom using a random walk method. | ||
326 | !! An initial point is chosen at random, and then points nearby are tested | ||
327 | !! to see if they are more suitable than the current point. If they are, | ||
328 | !! the query point is moved to the new point and the process is repeated. | ||
329 | !! The process is repeated, with each point being tested against a random | ||
330 | !! number. If the random number is less than the suitability of the point, | ||
331 | !! the atom is placed at that point. | ||
332 | implicit none | ||
333 | |||
334 | ! Arguments | ||
335 | type(distribs_container_type), intent(in) :: distribs_container | ||
336 | !! Distribution function (gvector) container. | ||
337 | real(real32), dimension(3), intent(in) :: prior_point | ||
338 | !! Point to start walk from. | ||
339 | integer, intent(in) :: prior_species | ||
340 | !! Species of last atom placed. | ||
341 | real(real32), dimension(2,3), intent(in) :: bounds | ||
342 | !! Bounds of the unit cell. | ||
343 | type(extended_basis_type), intent(inout) :: basis | ||
344 | !! Structure to add atom to. | ||
345 | integer, intent(in) :: max_attempts | ||
346 | !! Limit on number of attempts. | ||
347 | real(real32), intent(in) :: step_size_coarse, step_size_fine | ||
348 | !! Step sizes for random walk. | ||
349 | logical, intent(out) :: viable | ||
350 | !! Boolean to indicate if point is viable. | ||
351 | integer, dimension(:,:), intent(in) :: atom_ignore_list | ||
352 | !! List of atoms to ignore (i.e. indices of atoms not yet placed). | ||
353 | real(real32), dimension(:), intent(in) :: radius_list | ||
354 | !! List of radii for each pair of elements. | ||
355 | real(real32), dimension(3) :: point | ||
356 | !! Point to add atom to. | ||
357 | |||
358 | ! Local variables | ||
359 | integer :: i, j, idx | ||
360 | !! Loop indices. | ||
361 | integer :: nattempt, nstuck | ||
362 | !! Number of attempts and number of times stuck at same site | ||
363 | real(real32) :: rtmp1, min_radius | ||
364 | !! Random number and minimum radius. | ||
365 | real(real32), dimension(3) :: rvec1, abc | ||
366 | !! Random vector and lattice constants. | ||
367 | real(real32) :: crude_norm | ||
368 | !! Crude normalisation. | ||
369 | real(real32) :: site_value, test_value | ||
370 | !! Viability values. | ||
371 | real(real32), dimension(3) :: site_vector, test_vector | ||
372 | !! Vectors for gridpoints. | ||
373 | real(real32), dimension(3,3) :: inverse_lattice | ||
374 | |||
375 | |||
376 | 1 | viable = .false. | |
377 | |||
378 | !--------------------------------------------------------------------------- | ||
379 | ! get the lattice constants and the inverse lattice | ||
380 | !--------------------------------------------------------------------------- | ||
381 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | do i = 1, 3 |
382 | 4 | abc(i) = modu(basis%lat(i,:)) | |
383 | end do | ||
384 | 1 | inverse_lattice = inverse_3x3(basis%lat) | |
385 | |||
386 | |||
387 | !--------------------------------------------------------------------------- | ||
388 | ! get the index of the pair of species | ||
389 | !--------------------------------------------------------------------------- | ||
390 | idx = distribs_container%get_pair_index( & | ||
391 | basis%spec(prior_species)%name, & | ||
392 | basis%spec(atom_ignore_list(1,1))%name & | ||
393 | 1 | ) | |
394 | 1 | min_radius = radius_list(idx) * distribs_container%radius_distance_tol(1) | |
395 | |||
396 | |||
397 | !--------------------------------------------------------------------------- | ||
398 | ! test a random point within a spherical shell around the prior point | ||
399 | !--------------------------------------------------------------------------- | ||
400 | 1 | i = 0 | |
401 | 436 | shell_loop: do | |
402 | 437 | i = i + 1 | |
403 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 437 times.
|
437 | if(i.gt.max_attempts) return |
404 | 437 | call random_number(rvec1) | |
405 | ! map rvec1(1) to ring between min_radius and min_radius + 1.0 | ||
406 | 437 | rvec1(1) = rvec1(1) + min_radius ! r | |
407 | 437 | rvec1(2) = rvec1(2) * 2._real32 * pi ! theta | |
408 | 437 | rvec1(3) = rvec1(3) * pi ! phi | |
409 | ! convert from spherical to cartesian | ||
410 | rvec1 = [ & | ||
411 | rvec1(1) * cos(rvec1(2)) * sin(rvec1(3)), & | ||
412 | rvec1(1) * sin(rvec1(2)) * sin(rvec1(3)), & | ||
413 | rvec1(1) * cos(rvec1(3)) & | ||
414 |
2/2✓ Branch 0 taken 1311 times.
✓ Branch 1 taken 437 times.
|
1748 | ] |
415 | ! convert from cartesian to direct | ||
416 |
2/2✓ Branch 1 taken 1311 times.
✓ Branch 2 taken 437 times.
|
1748 | rvec1 = matmul(rvec1, inverse_lattice) |
417 |
2/2✓ Branch 0 taken 1311 times.
✓ Branch 1 taken 437 times.
|
1748 | site_vector = prior_point + rvec1 |
418 |
2/2✓ Branch 0 taken 1213 times.
✓ Branch 1 taken 296 times.
|
1509 | do j = 1, 3 |
419 |
2/2✓ Branch 0 taken 141 times.
✓ Branch 1 taken 1072 times.
|
1213 | if(site_vector(j).lt.bounds(1,j) .or. site_vector(j).ge.bounds(2,j)) & |
420 | 437 | cycle shell_loop | |
421 | end do | ||
422 | ! now evaluate the point and check if it passes the initial criteria | ||
423 | site_value = evaluate_point( distribs_container, & | ||
424 | site_vector, atom_ignore_list(1,1), basis, & | ||
425 | atom_ignore_list, radius_list & | ||
426 | 296 | ) | |
427 | 296 | call random_number(rtmp1) | |
428 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 295 times.
|
296 | if(rtmp1.lt.site_value) exit shell_loop |
429 | |||
430 | end do shell_loop | ||
431 | |||
432 | |||
433 | !--------------------------------------------------------------------------- | ||
434 | ! now do a random walk to find a suitable point to place the atom | ||
435 | !--------------------------------------------------------------------------- | ||
436 | 1 | nattempt = 0 | |
437 | 1 | nstuck = 0 | |
438 | 1 | crude_norm = 0.5_real32 | |
439 | 1 | i = 0 | |
440 | 32 | walk_loop : do | |
441 | 33 | i = i + 1 | |
442 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 33 times.
|
33 | if(i.gt.max_attempts) return |
443 | !------------------------------------------------------------------------ | ||
444 | ! if we have tried 10 times, then we need to reduce the step size | ||
445 | ! get the new test point and map it back into the unit cell | ||
446 | !------------------------------------------------------------------------ | ||
447 | 33 | call random_number(rvec1) | |
448 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 29 times.
|
33 | if(nattempt.ge.10) then |
449 | test_vector = site_vector + & | ||
450 |
2/2✓ Branch 0 taken 12 times.
✓ Branch 1 taken 4 times.
|
16 | ( rvec1 * 2._real32 - 1._real32 ) * step_size_fine / abc |
451 | else | ||
452 | test_vector = site_vector + & | ||
453 |
2/2✓ Branch 0 taken 87 times.
✓ Branch 1 taken 29 times.
|
116 | ( rvec1 * 2._real32 - 1._real32 ) * step_size_coarse / abc |
454 | end if | ||
455 |
3/4✓ Branch 0 taken 99 times.
✓ Branch 1 taken 33 times.
✓ Branch 2 taken 99 times.
✗ Branch 3 not taken.
|
132 | test_vector = test_vector - floor(test_vector) |
456 |
2/2✓ Branch 0 taken 99 times.
✓ Branch 1 taken 30 times.
|
129 | do j = 1, 3 |
457 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 96 times.
|
99 | if(test_vector(j).lt.bounds(1,j) .or. test_vector(j).ge.bounds(2,j)) & |
458 | 33 | cycle walk_loop | |
459 | end do | ||
460 | |||
461 | !------------------------------------------------------------------------ | ||
462 | ! evaluate the test point | ||
463 | !------------------------------------------------------------------------ | ||
464 | test_value = evaluate_point( distribs_container, & | ||
465 | test_vector, atom_ignore_list(1,1), basis, & | ||
466 | atom_ignore_list, radius_list & | ||
467 | 30 | ) | |
468 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 30 times.
|
30 | if(test_value.lt.1.E-6) cycle walk_loop |
469 | !------------------------------------------------------------------------ | ||
470 | ! if viability of test point is less than current point, then we | ||
471 | ! are stuck at the current point and need to try again | ||
472 | !------------------------------------------------------------------------ | ||
473 |
2/2✓ Branch 0 taken 27 times.
✓ Branch 1 taken 3 times.
|
30 | if(test_value.lt.site_value) then |
474 | 27 | nstuck = nstuck + 1 | |
475 |
2/2✓ Branch 0 taken 14 times.
✓ Branch 1 taken 13 times.
|
27 | if(nstuck.ge.10) then |
476 | 14 | nattempt = nattempt + 1 | |
477 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 14 times.
|
14 | if(crude_norm.lt.site_value) & |
478 | crude_norm = ( & | ||
479 | crude_norm + site_value/real(nattempt) & | ||
480 | ✗ | ) / 2._real32 | |
481 | |||
482 | ! if we have tried 10 times, and still no luck, then we need to | ||
483 | ! reduce the tolerance | ||
484 |
2/2✓ Branch 0 taken 5 times.
✓ Branch 1 taken 9 times.
|
14 | if(nattempt.ge.10) site_value = site_value / crude_norm |
485 | 14 | call random_number(rtmp1) | |
486 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 13 times.
|
14 | if(rtmp1.lt.site_value) exit walk_loop |
487 | end if | ||
488 | else | ||
489 | 3 | nstuck = 0 | |
490 | 3 | site_vector = test_vector | |
491 | 3 | site_value = test_value | |
492 | |||
493 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
|
3 | if(nattempt.ge.10) test_value = test_value / crude_norm |
494 | 3 | call random_number(rtmp1) | |
495 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
|
3 | if(rtmp1.lt.test_value) exit walk_loop |
496 | end if | ||
497 | |||
498 | end do walk_loop | ||
499 | |||
500 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | point = site_vector |
501 | 1 | viable=.true. | |
502 | |||
503 | end function place_method_growth | ||
504 | !############################################################################### | ||
505 | |||
506 | |||
507 | !############################################################################### | ||
508 | 26 | function place_method_min( & | |
509 | 26 | points, species, & | |
510 |
2/4✓ Branch 0 taken 26 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 26 times.
✗ Branch 3 not taken.
|
26 | species_index_list, viable & |
511 |
1/2✓ Branch 0 taken 26 times.
✗ Branch 1 not taken.
|
26 | ) result(point) |
512 | !! Global minimum placement method. | ||
513 | !! | ||
514 | !! This method places the atom at the gridpoint with the highest | ||
515 | !! suitability. | ||
516 | implicit none | ||
517 | |||
518 | ! Arguments | ||
519 | logical, intent(out) :: viable | ||
520 | !! Boolean to indicate if point is viable. | ||
521 | integer, intent(in) :: species | ||
522 | !! Species index to add atom to. | ||
523 | integer, dimension(:), intent(in) :: species_index_list | ||
524 | !! List of species indices to add atoms to. | ||
525 | real(real32), dimension(:,:), intent(in) :: points | ||
526 | !! List of gridpoints to consider. | ||
527 | real(real32), dimension(3) :: point | ||
528 | !! Point to add atom to. | ||
529 | |||
530 | ! Local variables | ||
531 | integer :: species_index | ||
532 | !! Index of species in list. | ||
533 | integer :: best_gridpoint | ||
534 | !! Index of best gridpoint. | ||
535 | |||
536 | |||
537 | 26 | viable = .false. | |
538 | |||
539 | !--------------------------------------------------------------------------- | ||
540 | ! find the gridpoint with the highest viability | ||
541 | !--------------------------------------------------------------------------- | ||
542 |
2/4✓ Branch 0 taken 26 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 26 times.
✗ Branch 3 not taken.
|
26 | species_index = findloc(species_index_list, species, 1) |
543 |
6/10✓ Branch 0 taken 26 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 26 times.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 114746 times.
✓ Branch 7 taken 26 times.
✓ Branch 8 taken 273 times.
✓ Branch 9 taken 114473 times.
|
114772 | best_gridpoint = maxloc(points(4+species_index,:), dim=1) |
544 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 26 times.
|
26 | if(best_gridpoint.eq.0)then |
545 | ✗ | return | |
546 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 24 times.
|
26 | elseif(points(4+species,best_gridpoint).lt.1.E-6)then |
547 | 2 | return | |
548 | end if | ||
549 | |||
550 | !--------------------------------------------------------------------------- | ||
551 | ! return the gridpoint with the highest viability | ||
552 | !--------------------------------------------------------------------------- | ||
553 |
2/2✓ Branch 0 taken 72 times.
✓ Branch 1 taken 24 times.
|
96 | point = points(1:3,best_gridpoint) |
554 | 24 | viable = .true. | |
555 | |||
556 | end function place_method_min | ||
557 | !############################################################################### | ||
558 | |||
559 | end module raffle__place_methods | ||
560 |