Line | Branch | Exec | Source |
---|---|---|---|
1 | module raffle__generator | ||
2 | !! Module for generating random structures from host structures. | ||
3 | !! | ||
4 | !! This module contains the raffle generator type, which is used to generate | ||
5 | !! random structures from a host structure. The raffle generator uses | ||
6 | !! distribution functions to determine the placement of atoms in the | ||
7 | !! provided host structure. | ||
8 | use raffle__io_utils, only: stop_program, print_warning, suppress_warnings | ||
9 | use raffle__constants, only: real32 | ||
10 | use raffle__tools_infile, only: assign_val, assign_vec | ||
11 | use raffle__misc, only: strip_null, set, shuffle, sort1D, sort2D, to_upper | ||
12 | use raffle__geom_rw, only: basis_type | ||
13 | use raffle__geom_extd, only: extended_basis_type | ||
14 | use raffle__distribs_container, only: distribs_container_type | ||
15 | use raffle__geom_utils, only: basis_merge | ||
16 | use raffle__place_methods, only: & | ||
17 | place_method_void, place_method_rand, & | ||
18 | place_method_growth, place_method_walk, & | ||
19 | place_method_min | ||
20 | use raffle__viability, only: & | ||
21 | get_gridpoints_and_viability, update_gridpoints_and_viability | ||
22 | |||
23 | implicit none | ||
24 | |||
25 | |||
26 | private | ||
27 | public :: raffle_generator_type, stoichiometry_type | ||
28 | |||
29 | |||
30 | type :: stoichiometry_type | ||
31 | !! Type for storing the stoichiometry of atoms to be placed in the host | ||
32 | !! structure. | ||
33 | character(len=3) :: element | ||
34 | !! Element symbol. | ||
35 | integer :: num | ||
36 | !! Number of atoms. | ||
37 | end type stoichiometry_type | ||
38 | |||
39 | |||
40 | type :: raffle_generator_type | ||
41 | !! Type for instance of raffle generator. | ||
42 | !! | ||
43 | !! This type contains the parameters and methods for generating random | ||
44 | !! structures from a host structure, using the RAFFLE method. | ||
45 | integer :: num_structures = 0 | ||
46 | !! Number of structures generated. Initialised to zero. | ||
47 | |||
48 | integer, dimension(:), allocatable :: seed | ||
49 | !! Seed for random number generator | ||
50 | |||
51 | type(basis_type) :: host | ||
52 | !! Host structure. | ||
53 | integer, dimension(3) :: grid = [0, 0, 0] | ||
54 | !! Grid to divide the host structure into along each axis. | ||
55 | real(real32), dimension(3) :: & | ||
56 | grid_offset = [0.5_real32, 0.5_real32, 0.5_real32] | ||
57 | !! Offset of the gridpoints. | ||
58 | real(real32) :: grid_spacing = 0.1_real32 | ||
59 | !! Spacing of the gridpoints. | ||
60 | real(real32), dimension(2,3) :: bounds = reshape( & | ||
61 | (/ & | ||
62 | 0.0_real32, 1.0_real32, & | ||
63 | 0.0_real32, 1.0_real32, & | ||
64 | 0.0_real32, 1.0_real32 & | ||
65 | /), [2,3] & | ||
66 | ) | ||
67 | !! Bounds for atom placement. | ||
68 | type(distribs_container_type) :: distributions | ||
69 | !! Distribution function container for the 2-, 3-, and 4-body interactions. | ||
70 | integer :: max_attempts = 10000 | ||
71 | !! Limit for the number of attempts to place an atom. | ||
72 | real(real32) :: & | ||
73 | walk_step_size_coarse = 1._real32, & | ||
74 | walk_step_size_fine = 0.1_real32 | ||
75 | !! Step size for the walk and grow methods. | ||
76 | real(real32), dimension(5) :: method_ratio_default = & | ||
77 | [0.1_real32, 0.01_real32, 0.25_real32, 0.25_real32, 1.0_real32] | ||
78 | !! Default ratio of each placement method. | ||
79 | real(real32), dimension(5) :: method_ratio | ||
80 | !! Last used ratio of each placement method. | ||
81 | type(basis_type), dimension(:), allocatable :: structures | ||
82 | !! Generated structures. | ||
83 | contains | ||
84 | procedure, pass(this) :: init_seed | ||
85 | !! Procedure to set the seed for the random number generator. | ||
86 | procedure, pass(this) :: set_method_ratio_default | ||
87 | !! Procedure to set the ratio of each placement method. | ||
88 | |||
89 | procedure, pass(this) :: set_host | ||
90 | !! Procedure to set the host structure. | ||
91 | procedure, pass(this) :: get_host | ||
92 | !! Procedure to get the host structure. | ||
93 | procedure, pass(this) :: prepare_host | ||
94 | !! Procedure to prepare the host structure. | ||
95 | procedure, pass(this) :: set_grid | ||
96 | !! Procedure to set the grid for the raffle generator. | ||
97 | procedure, pass(this) :: reset_grid | ||
98 | !! Procedure to reset the grid for the raffle generator. | ||
99 | procedure, pass(this) :: set_bounds | ||
100 | !! Procedure to set the bounds for the raffle generator. | ||
101 | procedure, pass(this) :: reset_bounds | ||
102 | !! Procedure to reset the bounds for the raffle generator. | ||
103 | procedure, pass(this) :: generate | ||
104 | !! Procedure to generate random structures. | ||
105 | procedure, pass(this), private :: generate_structure | ||
106 | !! Procedure to generate a single random structure. | ||
107 | procedure, pass(this) :: get_structures | ||
108 | !! Procedure to return the generated structures. | ||
109 | procedure, pass(this) :: set_structures | ||
110 | !! Procedure to set the array of generated structures. | ||
111 | procedure, pass(this) :: remove_structure | ||
112 | !! Procedure to remove a structure from the array of generated structures. | ||
113 | procedure, pass(this) :: evaluate | ||
114 | !! Procedure to evaluate the viability of a structure. | ||
115 | procedure, pass(this) :: get_probability_density | ||
116 | !! Procedure to get the probability density of a structure. | ||
117 | |||
118 | procedure, pass(this) :: print_settings => print_generator_settings | ||
119 | !! Procedure to print the raffle generator settings. | ||
120 | procedure, pass(this) :: read_settings => read_generator_settings | ||
121 | !! Procedure to read the raffle generator settings. | ||
122 | end type raffle_generator_type | ||
123 | |||
124 | interface raffle_generator_type | ||
125 | !! Constructor for the raffle generator type. | ||
126 | module function init_raffle_generator( & | ||
127 | host, & | ||
128 | width, sigma, cutoff_min, cutoff_max, & | ||
129 | history_len & | ||
130 | ) result(generator) | ||
131 | type(basis_type), intent(in), optional :: host | ||
132 | real(real32), dimension(3), intent(in), optional :: width | ||
133 | real(real32), dimension(3), intent(in), optional :: sigma | ||
134 | real(real32), dimension(3), intent(in), optional :: cutoff_min | ||
135 | real(real32), dimension(3), intent(in), optional :: cutoff_max | ||
136 | integer, intent(in), optional :: history_len | ||
137 | type(raffle_generator_type) :: generator | ||
138 | end function init_raffle_generator | ||
139 | end interface raffle_generator_type | ||
140 | |||
141 | |||
142 | contains | ||
143 | |||
144 | !############################################################################### | ||
145 | 2 | module function init_raffle_generator( & | |
146 | host, width, sigma, cutoff_min, cutoff_max, & | ||
147 | history_len & | ||
148 | ) result(generator) | ||
149 | !! Initialise an instance of the raffle generator. | ||
150 | !! | ||
151 | !! Set up run-independent parameters. | ||
152 | implicit none | ||
153 | |||
154 | ! Arguments | ||
155 | type(basis_type), intent(in), optional :: host | ||
156 | !! Basis of the host structure. | ||
157 | real(real32), dimension(3), intent(in), optional :: width | ||
158 | !! Width of the gaussians used in the 2-, 3-, and 4-body | ||
159 | !! distribution functions. | ||
160 | real(real32), dimension(3), intent(in), optional :: sigma | ||
161 | !! Width of the gaussians used in the 2-, 3-, and 4-body | ||
162 | !! distribution functions. | ||
163 | real(real32), dimension(3), intent(in), optional :: cutoff_min | ||
164 | !! Minimum cutoff for the 2-, 3-, and 4-body distribution functions. | ||
165 | real(real32), dimension(3), intent(in), optional :: cutoff_max | ||
166 | !! Maximum cutoff for the 2-, 3-, and 4-body distribution functions. | ||
167 | integer, intent(in), optional :: history_len | ||
168 | !! Length of the history for the 2-, 3-, and 4-body distribution functions. | ||
169 | |||
170 | ! Local variables | ||
171 | type(raffle_generator_type) :: generator | ||
172 | !! Instance of the raffle generator. | ||
173 | |||
174 | ! Handle optional arguments | ||
175 | ! Set up the host structure | ||
176 | 1 | if(present(host)) call generator%set_host(host) | |
177 | |||
178 | ! Set up the distribution function parameters | ||
179 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | if(present(width)) & |
180 | 1 | call generator%distributions%set_width(width) | |
181 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | if(present(sigma)) & |
182 | 1 | call generator%distributions%set_sigma(sigma) | |
183 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | if(present(cutoff_min)) & |
184 | 1 | call generator%distributions%set_cutoff_min(cutoff_min) | |
185 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | if(present(cutoff_max)) & |
186 | 1 | call generator%distributions%set_cutoff_max(cutoff_max) | |
187 | |||
188 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
|
2 | if(present(history_len)) & |
189 | ✗ | call generator%distributions%set_history_len(history_len) | |
190 | |||
191 |
36/36✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
✓ Branch 2 taken 18 times.
✓ Branch 3 taken 6 times.
✓ Branch 4 taken 6 times.
✓ Branch 5 taken 2 times.
✓ Branch 6 taken 6 times.
✓ Branch 7 taken 2 times.
✓ Branch 8 taken 6 times.
✓ Branch 9 taken 2 times.
✓ Branch 10 taken 6 times.
✓ Branch 11 taken 2 times.
✓ Branch 12 taken 12 times.
✓ Branch 13 taken 6 times.
✓ Branch 14 taken 6 times.
✓ Branch 15 taken 2 times.
✓ Branch 16 taken 6 times.
✓ Branch 17 taken 2 times.
✓ Branch 18 taken 6 times.
✓ Branch 19 taken 2 times.
✓ Branch 20 taken 6 times.
✓ Branch 21 taken 2 times.
✓ Branch 22 taken 6 times.
✓ Branch 23 taken 2 times.
✓ Branch 24 taken 8 times.
✓ Branch 25 taken 2 times.
✓ Branch 26 taken 6 times.
✓ Branch 27 taken 2 times.
✓ Branch 28 taken 18 times.
✓ Branch 29 taken 6 times.
✓ Branch 30 taken 6 times.
✓ Branch 31 taken 2 times.
✓ Branch 32 taken 10 times.
✓ Branch 33 taken 2 times.
✓ Branch 34 taken 1 times.
✓ Branch 35 taken 1 times.
|
142 | end function init_raffle_generator |
192 | !############################################################################### | ||
193 | |||
194 | |||
195 | !############################################################################### | ||
196 |
1/6✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
|
4 | subroutine init_seed(this, put, get, num_threads) |
197 | !! Set the seed for the random number generator. | ||
198 | implicit none | ||
199 | |||
200 | ! Arguments | ||
201 | class(raffle_generator_type), intent(inout) :: this | ||
202 | !! Instance of the raffle generator. | ||
203 | integer, dimension(..), intent(in), optional :: put | ||
204 | !! Seed for the random number generator. | ||
205 | integer, dimension(:), intent(out), optional :: get | ||
206 | !! Seed for the random number generator. | ||
207 | integer, intent(out), optional :: num_threads | ||
208 | !! Size of the seed array. | ||
209 | |||
210 | ! Local variables | ||
211 | integer :: num_threads_ | ||
212 | !! Number of threads for the random number generator. | ||
213 | 4 | integer, dimension(:), allocatable :: seed_arr | |
214 | !! Array of seeds for the random number generator. | ||
215 | |||
216 | 4 | call random_seed( size = num_threads_ ) | |
217 |
7/14✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 4 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 4 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 4 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 4 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 4 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 4 times.
|
4 | allocate(seed_arr(num_threads_)) |
218 |
3/4✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 3 times.
✗ Branch 3 not taken.
|
4 | if(present(put))then |
219 | select rank(put) | ||
220 | rank(0) | ||
221 |
2/2✓ Branch 0 taken 24 times.
✓ Branch 1 taken 3 times.
|
27 | seed_arr(1:num_threads_) = put |
222 | rank(1) | ||
223 | ✗ | if(size(put).eq.1)then | |
224 | ✗ | seed_arr(1:num_threads_) = put(1) | |
225 | ✗ | elseif(size(put).eq.num_threads_)then | |
226 | ✗ | seed_arr = put | |
227 | else | ||
228 | ✗ | call stop_program("Invalid seed array size") | |
229 | ✗ | return | |
230 | end if | ||
231 | rank default | ||
232 | ✗ | call stop_program("Invalid seed array") | |
233 | ✗ | return | |
234 | end select | ||
235 | 3 | call random_seed( put = seed_arr ) | |
236 | end if | ||
237 | |||
238 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
|
4 | if(present(get))then |
239 | ✗ | call random_seed( get = seed_arr ) | |
240 | ✗ | get = seed_arr | |
241 | end if | ||
242 | |||
243 |
8/12✓ Branch 0 taken 2 times.
✓ Branch 1 taken 2 times.
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 2 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 2 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 32 times.
✓ Branch 11 taken 4 times.
|
38 | this%seed = seed_arr |
244 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
|
4 | if(present(num_threads)) num_threads = num_threads_ |
245 | |||
246 |
1/2✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
|
4 | end subroutine init_seed |
247 | !############################################################################### | ||
248 | |||
249 | |||
250 | !############################################################################### | ||
251 | ✗ | subroutine set_method_ratio_default(this, method_ratio) | |
252 | !! Set the ratio of each placement method. | ||
253 | implicit none | ||
254 | |||
255 | ! Arguments | ||
256 | class(raffle_generator_type), intent(inout) :: this | ||
257 | !! Instance of the raffle generator. | ||
258 | real(real32), dimension(5), intent(in) :: method_ratio | ||
259 | !! Ratio of each placement method. | ||
260 | |||
261 | ✗ | this%method_ratio_default = method_ratio | |
262 | |||
263 | ✗ | end subroutine set_method_ratio_default | |
264 | !############################################################################### | ||
265 | |||
266 | |||
267 | !############################################################################### | ||
268 | 5 | subroutine set_host(this, host) | |
269 | !! Set the host structure. | ||
270 | !! | ||
271 | !! This procedure sets the host structure for the raffle generator. | ||
272 | implicit none | ||
273 | |||
274 | ! Arguments | ||
275 | class(raffle_generator_type), intent(inout) :: this | ||
276 | !! Instance of the raffle generator. | ||
277 | class(basis_type), intent(in) :: host | ||
278 | !! Basis of the host structure. | ||
279 | |||
280 | 5 | call this%host%copy(host) | |
281 | 5 | call this%distributions%host_system%set(this%host) | |
282 | |||
283 | 5 | call this%set_grid() | |
284 | 5 | end subroutine set_host | |
285 | !############################################################################### | ||
286 | |||
287 | |||
288 | !############################################################################### | ||
289 | ✗ | function get_host(this) result(output) | |
290 | !! Get the host structure. | ||
291 | !! | ||
292 | !! This procedure returns the host structure from the raffle generator. | ||
293 | implicit none | ||
294 | |||
295 | ! Arguments | ||
296 | class(raffle_generator_type), intent(in) :: this | ||
297 | !! Instance of the raffle generator. | ||
298 | |||
299 | type(basis_type) :: output | ||
300 | !! Basis of the host structure. | ||
301 | |||
302 | ✗ | call output%copy(this%host) | |
303 | |||
304 | ✗ | end function get_host | |
305 | !############################################################################### | ||
306 | |||
307 | |||
308 | !############################################################################### | ||
309 | ✗ | function prepare_host( & | |
310 | ✗ | this, interface_location, interface_axis, depth, & | |
311 | location_as_fractional & | ||
312 | ) result(stoichiometry) | ||
313 | !! Prepare the host structure for the raffle generator. | ||
314 | !! | ||
315 | !! This procedure prepares the host structure for the raffle generator. | ||
316 | implicit none | ||
317 | |||
318 | ! Arguments | ||
319 | class(raffle_generator_type), intent(inout) :: this | ||
320 | !! Instance of the raffle generator. | ||
321 | real(real32), dimension(:), intent(in) :: interface_location | ||
322 | !! Location of the interface in the host structure. | ||
323 | integer, intent(in), optional :: interface_axis | ||
324 | !! Axis of the interface in the host structure. | ||
325 | real(real32), intent(in), optional :: depth | ||
326 | !! Depth of the interface. | ||
327 | logical, intent(in), optional :: location_as_fractional | ||
328 | !! Boolean whether interface location is given in fractional coordinates. | ||
329 | |||
330 | type(stoichiometry_type), dimension(:), allocatable :: stoichiometry | ||
331 | !! Stoichiometry of the atoms removed from the host structure. | ||
332 | |||
333 | ! Local variables | ||
334 | integer :: i, is, ia | ||
335 | !! Loop indices. | ||
336 | integer :: num_remove | ||
337 | !! Number of atoms removed from the host structure. | ||
338 | integer :: axis | ||
339 | !! Axis of the interface in the host structure. | ||
340 | real(real32) :: dist, depth_ | ||
341 | !! Distance to the interface and depth of the interface. | ||
342 | real(real32) :: lattice_const | ||
343 | !! Lattice constant of the host structure along the interface axis. | ||
344 | ✗ | type(basis_type) :: host | |
345 | !! Host structure. | ||
346 | logical :: location_as_fractional_ | ||
347 | !! Boolean whether interface location is given in fractional coordinates. | ||
348 | ✗ | real(real32), dimension(size(interface_location)) :: intf_loc_ | |
349 | ✗ | integer, dimension(:), allocatable :: species_index_list | |
350 | !! List of species indices to remove. | ||
351 | ✗ | integer, dimension(:,:), allocatable :: remove_atom_list | |
352 | !! List of atoms to be removed from the host structure. | ||
353 | |||
354 | |||
355 | !--------------------------------------------------------------------------- | ||
356 | ! Handle optional arguments | ||
357 | !--------------------------------------------------------------------------- | ||
358 | ✗ | axis = 3 | |
359 | ✗ | if(present(interface_axis)) axis = interface_axis | |
360 | ✗ | depth_ = 3._real32 | |
361 | ✗ | if(present(depth)) depth_ = depth | |
362 | ✗ | call host%copy(this%host) | |
363 | ✗ | lattice_const = norm2(host%lat(axis,:)) | |
364 | ✗ | location_as_fractional_ = .false. | |
365 | ✗ | if(present(location_as_fractional)) & | |
366 | ✗ | location_as_fractional_ = location_as_fractional | |
367 | ✗ | if(location_as_fractional_)then | |
368 | ✗ | intf_loc_ = interface_location | |
369 | else | ||
370 | ✗ | intf_loc_ = interface_location / lattice_const | |
371 | end if | ||
372 | |||
373 | |||
374 | !--------------------------------------------------------------------------- | ||
375 | ! Identify atoms to be removed from the host structure | ||
376 | !--------------------------------------------------------------------------- | ||
377 | ✗ | num_remove = 0 | |
378 | ✗ | allocate(remove_atom_list(2,host%natom)) | |
379 | ✗ | do is = 1, host%nspec | |
380 | ✗ | atom_loop: do ia = 1, host%spec(is)%num | |
381 | ✗ | do i = 1, size(intf_loc_) | |
382 | ✗ | dist = host%spec(is)%atom(ia,axis) - intf_loc_(i) | |
383 | ✗ | dist = dist - ceiling(dist - 0.5_real32) | |
384 | ✗ | if( abs(dist * lattice_const) .le. depth_ )then | |
385 | ✗ | num_remove = num_remove + 1 | |
386 | ✗ | remove_atom_list(:,num_remove) = [ is, ia ] | |
387 | ✗ | cycle atom_loop | |
388 | end if | ||
389 | end do | ||
390 | end do atom_loop | ||
391 | end do | ||
392 | |||
393 | |||
394 | !--------------------------------------------------------------------------- | ||
395 | ! Create the dictionary of atoms to be removed | ||
396 | !--------------------------------------------------------------------------- | ||
397 | ✗ | if(num_remove.gt.0)then | |
398 | ✗ | remove_atom_list = remove_atom_list(1:2,1:num_remove) | |
399 | ✗ | call host%remove_atoms(remove_atom_list) | |
400 | ✗ | species_index_list = remove_atom_list(1,:) | |
401 | ✗ | call set(species_index_list) | |
402 | ✗ | call sort2D(remove_atom_list, 1) | |
403 | ✗ | allocate(stoichiometry(size(species_index_list))) | |
404 | ✗ | do i = 1, size(species_index_list) | |
405 | ✗ | stoichiometry(i)%element = host%spec(species_index_list(i))%name | |
406 | stoichiometry(i)%num = & | ||
407 | ✗ | count(remove_atom_list(1,:).eq.species_index_list(i)) | |
408 | end do | ||
409 | end if | ||
410 | |||
411 | |||
412 | !--------------------------------------------------------------------------- | ||
413 | ! Reset the host structure | ||
414 | !--------------------------------------------------------------------------- | ||
415 | ✗ | if(host%natom.eq.0)then | |
416 | ✗ | call stop_program("No atoms remaining in host structure") | |
417 | ✗ | return | |
418 | end if | ||
419 | ✗ | call this%set_host(host) | |
420 | |||
421 | ✗ | end function prepare_host | |
422 | !############################################################################### | ||
423 | |||
424 | |||
425 | !############################################################################### | ||
426 | 15 | subroutine set_grid(this, grid, grid_spacing, grid_offset) | |
427 | !! Set the grid for the raffle generator. | ||
428 | !! | ||
429 | !! This procedure sets the grid for the raffle generator. The grid is used | ||
430 | !! to divide the host structure into bins along each axis on which | ||
431 | !! atom placement viability will be evaluated | ||
432 | implicit none | ||
433 | |||
434 | ! Arguments | ||
435 | class(raffle_generator_type), intent(inout) :: this | ||
436 | !! Instance of the raffle generator. | ||
437 | integer, dimension(3), intent(in), optional :: grid | ||
438 | !! Number of bins to divide the host structure into along each axis. | ||
439 | real(real32), intent(in), optional :: grid_spacing | ||
440 | !! Spacing of the bins. | ||
441 | real(real32), dimension(3), intent(in), optional :: grid_offset | ||
442 | !! Offset of the gridpoints. | ||
443 | |||
444 | ! Local variables | ||
445 | integer :: i | ||
446 | !! Loop index. | ||
447 | |||
448 | |||
449 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 14 times.
|
15 | if(present(grid).and.present(grid_spacing)) then |
450 | 1 | call this%reset_grid() | |
451 | 1 | call stop_program("Cannot set grid and grid spacing simultaneously") | |
452 | 1 | return | |
453 |
2/2✓ Branch 0 taken 6 times.
✓ Branch 1 taken 8 times.
|
14 | elseif(present(grid_spacing)) then |
454 | 6 | this%grid_spacing = grid_spacing | |
455 |
2/2✓ Branch 0 taken 18 times.
✓ Branch 1 taken 6 times.
|
24 | this%grid = 0 |
456 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 7 times.
|
8 | elseif(present(grid)) then |
457 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | this%grid = grid |
458 | end if | ||
459 | |||
460 |
4/4✓ Branch 0 taken 4 times.
✓ Branch 1 taken 10 times.
✓ Branch 2 taken 12 times.
✓ Branch 3 taken 4 times.
|
26 | if(present(grid_offset)) this%grid_offset = grid_offset |
461 | |||
462 |
6/6✓ Branch 0 taken 38 times.
✓ Branch 1 taken 12 times.
✓ Branch 2 taken 2 times.
✓ Branch 3 taken 36 times.
✓ Branch 4 taken 12 times.
✓ Branch 5 taken 2 times.
|
50 | if(all(this%grid.eq.0))then |
463 |
1/2✓ Branch 0 taken 12 times.
✗ Branch 1 not taken.
|
12 | if(allocated(this%host%spec))then |
464 |
2/2✓ Branch 0 taken 36 times.
✓ Branch 1 taken 12 times.
|
48 | do i = 1, 3 |
465 | this%grid(i) = nint( & | ||
466 | ( this%bounds(2,i) - this%bounds(1,i) ) * & | ||
467 | norm2(this%host%lat(i,:)) / this%grid_spacing & | ||
468 |
5/6✓ Branch 0 taken 108 times.
✓ Branch 1 taken 36 times.
✓ Branch 2 taken 36 times.
✓ Branch 3 taken 72 times.
✓ Branch 4 taken 36 times.
✗ Branch 5 not taken.
|
156 | ) |
469 | end do | ||
470 | end if | ||
471 | end if | ||
472 | |||
473 | end subroutine set_grid | ||
474 | !############################################################################### | ||
475 | |||
476 | |||
477 | !############################################################################### | ||
478 | 4 | subroutine reset_grid(this) | |
479 | !! Reset the grid for the raffle generator. | ||
480 | implicit none | ||
481 | |||
482 | ! Arguments | ||
483 | class(raffle_generator_type), intent(inout) :: this | ||
484 | !! Instance of the raffle generator. | ||
485 | |||
486 |
2/2✓ Branch 0 taken 12 times.
✓ Branch 1 taken 4 times.
|
16 | this%grid = 0 |
487 | 4 | end subroutine reset_grid | |
488 | !############################################################################### | ||
489 | |||
490 | |||
491 | !############################################################################### | ||
492 | 2 | subroutine set_bounds(this, bounds) | |
493 | !! Set the bounds for the raffle generator. | ||
494 | !! | ||
495 | !! This procedure sets the bounds for the raffle generator. The bounds are | ||
496 | !! used to determine the placement of atoms in the host structure. | ||
497 | implicit none | ||
498 | |||
499 | ! Arguments | ||
500 | class(raffle_generator_type), intent(inout) :: this | ||
501 | !! Instance of the raffle generator. | ||
502 | real(real32), dimension(2,3), intent(in) :: bounds | ||
503 | !! Bounds for atom placement. | ||
504 | |||
505 | ! check if bounds has zero volume, if so, return | ||
506 |
4/6✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 6 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2 times.
|
8 | if( any(bounds(2,:) .le. bounds(1,:)) ) then |
507 | ✗ | call stop_program("Bounds have zero volume") | |
508 | ✗ | return | |
509 | end if | ||
510 | |||
511 |
4/4✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
✓ Branch 2 taken 12 times.
✓ Branch 3 taken 6 times.
|
20 | this%bounds = bounds |
512 | 2 | call this%set_grid() | |
513 | |||
514 | end subroutine set_bounds | ||
515 | !############################################################################### | ||
516 | |||
517 | |||
518 | !############################################################################### | ||
519 | 2 | subroutine reset_bounds(this) | |
520 | !! Reset the grid for the raffle generator. | ||
521 | implicit none | ||
522 | |||
523 | ! Arguments | ||
524 | class(raffle_generator_type), intent(inout) :: this | ||
525 | !! Instance of the raffle generator. | ||
526 | |||
527 |
2/2✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
|
8 | this%bounds(1,:) = 0.0_real32 |
528 |
2/2✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
|
8 | this%bounds(2,:) = 1.0_real32 |
529 | 2 | end subroutine reset_bounds | |
530 | !############################################################################### | ||
531 | |||
532 | |||
533 | !############################################################################### | ||
534 | 4 | subroutine generate(this, num_structures, & | |
535 | 4 | stoichiometry, method_ratio, seed, settings_out_file, & | |
536 | verbose, exit_code & | ||
537 | ) | ||
538 | !! Generate random structures. | ||
539 | !! | ||
540 | !! This procedure generates random structures from the contained host | ||
541 | !! structure and the stoichiometry argument. The number of structures to | ||
542 | !! generate is specified by the num_structures argument. | ||
543 | !! The ratio of placement methods to be sampled is defined by method_ratio. | ||
544 | implicit none | ||
545 | |||
546 | ! Arguments | ||
547 | class(raffle_generator_type), intent(inout) :: this | ||
548 | !! Instance of the raffle generator. | ||
549 | integer, intent(in) :: num_structures | ||
550 | !! Number of structures to generate. | ||
551 | type(stoichiometry_type), dimension(:), intent(in) :: stoichiometry | ||
552 | !! Stoichiometry of the structures to generate. | ||
553 | real(real32), dimension(5), intent(in), optional :: method_ratio | ||
554 | !! Ratio of each placement method. | ||
555 | integer, intent(in), optional :: seed | ||
556 | !! Seed for the random number generator. | ||
557 | character(*), intent(in), optional :: settings_out_file | ||
558 | !! File to print the settings to. | ||
559 | integer, intent(in), optional :: verbose | ||
560 | !! Verbosity level. | ||
561 | integer, intent(out), optional :: exit_code | ||
562 | !! Exit code. | ||
563 | |||
564 | ! Local variables | ||
565 | integer :: i, j, k, istructure, num_structures_old, num_structures_new | ||
566 | !! Loop counters. | ||
567 | integer :: exit_code_ | ||
568 | !! Exit code. | ||
569 | integer :: num_seed | ||
570 | !! Number of seeds for the random number generator. | ||
571 | integer :: num_insert_atoms, num_insert_species | ||
572 | !! Number of atoms and species to insert (from stoichiometry). | ||
573 | real(real32) :: ratio_norm | ||
574 | !! Normalisation factor for the method ratios. | ||
575 | logical :: success | ||
576 | !! Boolean comparison of element symbols. | ||
577 | integer :: verbose_ | ||
578 | !! Verbosity level. | ||
579 | logical :: suppress_warnings_store | ||
580 | !! Boolean to store the suppress_warnings value. | ||
581 |
6/6✓ Branch 0 taken 12 times.
✓ Branch 1 taken 4 times.
✓ Branch 2 taken 36 times.
✓ Branch 3 taken 12 times.
✓ Branch 4 taken 12 times.
✓ Branch 5 taken 4 times.
|
64 | type(basis_type) :: basis_template |
582 | !! Basis of the structure to generate (i.e. allocated species and atoms). | ||
583 | real(real32), dimension(5) :: method_rand_limit | ||
584 | !! Default ratio of each placement method. | ||
585 | |||
586 | integer, dimension(:), allocatable :: seed_arr | ||
587 | !! Array of seeds for the random number generator. | ||
588 | 4 | type(basis_type), dimension(:), allocatable :: tmp_structures | |
589 | !! Temporary array of structures (for memory reallocation). | ||
590 | |||
591 | 4 | integer, dimension(:,:), allocatable :: placement_list | |
592 | !! List of possible atoms to place in the structure. | ||
593 | |||
594 | |||
595 | !--------------------------------------------------------------------------- | ||
596 | ! Set the verbosity level | ||
597 | !--------------------------------------------------------------------------- | ||
598 | 4 | exit_code_ = 0 | |
599 | 4 | verbose_ = 0 | |
600 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | if(present(verbose)) verbose_ = verbose |
601 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
|
4 | if(verbose_ .eq. 0)then |
602 | 1 | suppress_warnings_store = suppress_warnings | |
603 | 1 | suppress_warnings = .true. | |
604 | end if | ||
605 | |||
606 | |||
607 | !--------------------------------------------------------------------------- | ||
608 | ! Handle placement method optional argument | ||
609 | !--------------------------------------------------------------------------- | ||
610 |
1/2✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
|
4 | if(present(method_ratio))then |
611 | 4 | method_rand_limit = method_ratio | |
612 | else | ||
613 | ✗ | method_rand_limit = this%method_ratio_default | |
614 | end if | ||
615 |
2/2✓ Branch 0 taken 20 times.
✓ Branch 1 taken 4 times.
|
24 | this%method_ratio = method_rand_limit |
616 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | if(verbose_.gt.0) write(*,*) & |
617 | 3 | "Method ratio (void, rand, walk, grow, min): ", this%method_ratio | |
618 | |||
619 | |||
620 | !--------------------------------------------------------------------------- | ||
621 | ! Print the settings to a file | ||
622 | !--------------------------------------------------------------------------- | ||
623 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
|
4 | if(present(settings_out_file))then |
624 | ✗ | if(trim(settings_out_file).ne."")then | |
625 | ✗ | call this%print_settings(settings_out_file) | |
626 | end if | ||
627 | end if | ||
628 | |||
629 | |||
630 | !--------------------------------------------------------------------------- | ||
631 | ! Set the placement method selection limit numbers | ||
632 | !--------------------------------------------------------------------------- | ||
633 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | if(verbose_.gt.0) write(*,*) "Setting method ratio limits" |
634 |
2/2✓ Branch 0 taken 20 times.
✓ Branch 1 taken 4 times.
|
24 | ratio_norm = real(sum(method_rand_limit), real32) |
635 |
2/2✓ Branch 0 taken 20 times.
✓ Branch 1 taken 4 times.
|
24 | method_rand_limit = method_rand_limit / ratio_norm |
636 |
2/2✓ Branch 0 taken 16 times.
✓ Branch 1 taken 4 times.
|
20 | do i = 2, 5, 1 |
637 | 20 | method_rand_limit(i) = method_rand_limit(i) + method_rand_limit(i-1) | |
638 | end do | ||
639 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | if(verbose_.gt.0) write(*,*) & |
640 | 3 | "Method random limits (void, rand, walk, grow, min): ", & | |
641 | 6 | method_rand_limit | |
642 | |||
643 | |||
644 | !--------------------------------------------------------------------------- | ||
645 | ! Set the random seed | ||
646 | !--------------------------------------------------------------------------- | ||
647 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | if(present(seed))then |
648 | 3 | call this%init_seed( put = seed ) | |
649 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | elseif(.not.allocated(this%seed))then |
650 | 1 | call this%init_seed() | |
651 | end if | ||
652 | |||
653 | |||
654 | !--------------------------------------------------------------------------- | ||
655 | ! allocate memory for structures | ||
656 | !--------------------------------------------------------------------------- | ||
657 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | if(verbose_.gt.0) write(*,*) "Allocating memory for structures" |
658 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 2 times.
|
4 | if(.not.allocated(this%structures))then |
659 |
19/34✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2 times.
✓ Branch 6 taken 1 times.
✓ Branch 7 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 2 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 2 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 2 times.
✓ Branch 17 taken 6 times.
✓ Branch 18 taken 2 times.
✓ Branch 19 taken 18 times.
✓ Branch 20 taken 6 times.
✓ Branch 21 taken 6 times.
✓ Branch 22 taken 2 times.
✓ Branch 23 taken 1 times.
✓ Branch 24 taken 2 times.
✓ Branch 25 taken 1 times.
✗ Branch 26 not taken.
✗ Branch 27 not taken.
✓ Branch 28 taken 1 times.
✗ Branch 29 not taken.
✗ Branch 30 not taken.
✗ Branch 31 not taken.
✗ Branch 32 not taken.
✗ Branch 33 not taken.
✗ Branch 34 not taken.
✗ Branch 35 not taken.
✗ Branch 36 not taken.
|
33 | allocate(this%structures(num_structures)) |
660 | else | ||
661 |
17/34✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 2 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 2 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 2 times.
✓ Branch 17 taken 6 times.
✓ Branch 18 taken 2 times.
✓ Branch 19 taken 18 times.
✓ Branch 20 taken 6 times.
✓ Branch 21 taken 6 times.
✓ Branch 22 taken 2 times.
✓ Branch 23 taken 4 times.
✓ Branch 24 taken 2 times.
✓ Branch 25 taken 4 times.
✗ Branch 26 not taken.
✗ Branch 27 not taken.
✓ Branch 28 taken 4 times.
✗ Branch 29 not taken.
✗ Branch 30 not taken.
✗ Branch 31 not taken.
✗ Branch 32 not taken.
✗ Branch 33 not taken.
✗ Branch 34 not taken.
✗ Branch 35 not taken.
✗ Branch 36 not taken.
|
36 | allocate(tmp_structures(this%num_structures + num_structures)) |
662 | tmp_structures(:this%num_structures) = & | ||
663 |
11/28✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✓ Branch 7 taken 1 times.
✓ Branch 8 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 1 times.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✓ Branch 17 taken 1 times.
✗ Branch 18 not taken.
✗ Branch 19 not taken.
✗ Branch 20 not taken.
✗ Branch 21 not taken.
✗ Branch 22 not taken.
✗ Branch 23 not taken.
✗ Branch 24 not taken.
✗ Branch 25 not taken.
✗ Branch 26 not taken.
✗ Branch 27 not taken.
|
4 | this%structures(:this%num_structures) |
664 |
11/18✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 1 times.
✓ Branch 10 taken 1 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 1 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 2 times.
✗ Branch 17 not taken.
|
6 | call move_alloc(tmp_structures, this%structures) |
665 | end if | ||
666 | |||
667 | |||
668 | !--------------------------------------------------------------------------- | ||
669 | ! set up the template basis for generated structures | ||
670 | !--------------------------------------------------------------------------- | ||
671 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
|
4 | if(verbose_.gt.0) write(*,*) "Setting up basis store" |
672 | 4 | num_insert_species = size(stoichiometry) | |
673 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
|
8 | num_insert_atoms = sum(stoichiometry(:)%num) |
674 |
13/24✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 4 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 4 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 4 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 4 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 4 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 4 times.
✓ Branch 17 taken 4 times.
✓ Branch 18 taken 4 times.
✓ Branch 19 taken 4 times.
✗ Branch 20 not taken.
✗ Branch 21 not taken.
✓ Branch 22 taken 4 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 4 times.
✗ Branch 25 not taken.
✓ Branch 26 taken 4 times.
|
8 | allocate(basis_template%spec(num_insert_species)) |
675 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
|
8 | do i = 1, size(stoichiometry) |
676 | 8 | basis_template%spec(i)%name = strip_null(stoichiometry(i)%element) | |
677 | end do | ||
678 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
|
8 | basis_template%spec(:)%num = stoichiometry(:)%num |
679 | 4 | basis_template%natom = num_insert_atoms | |
680 | 4 | basis_template%nspec = num_insert_species | |
681 | 4 | basis_template%sysname = "inserts" | |
682 | |||
683 | 4 | j = 0 | |
684 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
|
8 | do i = 1, basis_template%nspec |
685 | basis_template%spec(i)%atom_mask = & | ||
686 |
10/16✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
✓ Branch 3 taken 36 times.
✓ Branch 4 taken 4 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 4 times.
✓ Branch 7 taken 36 times.
✓ Branch 8 taken 4 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 4 times.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
✓ Branch 13 taken 4 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 36 times.
✓ Branch 16 taken 4 times.
|
112 | [ ( .false., k = 1, basis_template%spec(i)%num, 1 ) ] |
687 | basis_template%spec(i)%atom_idx = & | ||
688 |
10/16✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
✓ Branch 3 taken 36 times.
✓ Branch 4 taken 4 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 4 times.
✓ Branch 7 taken 36 times.
✓ Branch 8 taken 4 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 4 times.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
✓ Branch 13 taken 4 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 36 times.
✓ Branch 16 taken 4 times.
|
112 | [ ( k, k = j + 1, j + basis_template%spec(i)%num, 1 ) ] |
689 | 4 | j = j + basis_template%spec(i)%num | |
690 | allocate( & | ||
691 | ✗ | basis_template%spec(i)%atom(basis_template%spec(i)%num,3), & | |
692 | source = 0._real32 & | ||
693 |
12/20✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 4 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 4 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 4 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 4 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 4 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 4 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 4 times.
✓ Branch 18 taken 12 times.
✓ Branch 19 taken 4 times.
✓ Branch 20 taken 108 times.
✓ Branch 21 taken 12 times.
|
128 | ) |
694 | end do | ||
695 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
|
4 | if(.not.allocated(this%host%spec))then |
696 | 1 | call stop_program("Host structure not set") | |
697 | 1 | return | |
698 | end if | ||
699 | basis_template = basis_merge( & | ||
700 | this%host, basis_template, & | ||
701 | mask1 = .true., mask2 = .false. & | ||
702 |
7/12✓ Branch 1 taken 3 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 3 times.
✓ Branch 6 taken 3 times.
✓ Branch 7 taken 3 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 3 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 3 times.
✗ Branch 12 not taken.
|
9 | ) |
703 |
4/4✓ Branch 0 taken 9 times.
✓ Branch 1 taken 3 times.
✓ Branch 2 taken 27 times.
✓ Branch 3 taken 9 times.
|
39 | basis_template%lat = this%host%lat |
704 | |||
705 | |||
706 | !--------------------------------------------------------------------------- | ||
707 | ! ensure host element map is set | ||
708 | !--------------------------------------------------------------------------- | ||
709 | call this%distributions%set_element_map( & | ||
710 | [ basis_template%spec(:)%name ] & | ||
711 |
6/8✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
✓ Branch 3 taken 3 times.
✓ Branch 4 taken 3 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 3 times.
✓ Branch 7 taken 3 times.
✓ Branch 8 taken 3 times.
|
9 | ) |
712 | call this%distributions%host_system%set_element_map( & | ||
713 | this%distributions%element_info & | ||
714 | 3 | ) | |
715 | |||
716 | |||
717 | !--------------------------------------------------------------------------- | ||
718 | ! generate the placement list | ||
719 | ! placement list is the list of number of atoms of each species that can be | ||
720 | ! placed in the structure | ||
721 | ! ... the second dimension is the index of the species and atom in the | ||
722 | ! ... basis_template | ||
723 | !--------------------------------------------------------------------------- | ||
724 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | if(verbose_.gt.0) write(*,*) "Generating placement list" |
725 |
7/14✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 3 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 3 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 3 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 3 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 3 times.
|
3 | allocate(placement_list(2, num_insert_atoms)) |
726 | 3 | k = 0 | |
727 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 3 times.
|
6 | spec_loop1: do i = 1, basis_template%nspec |
728 | 3 | success = .false. | |
729 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 3 times.
|
6 | do j = 1, size(stoichiometry) |
730 |
3/6✓ Branch 2 taken 3 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 3 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 3 times.
✗ Branch 7 not taken.
|
6 | if( & |
731 | trim(basis_template%spec(i)%name) .eq. & | ||
732 | trim(strip_null(stoichiometry(j)%element)) & | ||
733 | 9 | ) success = .true. | |
734 | end do | ||
735 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
|
3 | if(.not.success) cycle |
736 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
|
6 | if(i.gt.this%host%nspec)then |
737 | ✗ | do j = 1, basis_template%spec(i)%num | |
738 | ✗ | k = k + 1 | |
739 | ✗ | placement_list(1,k) = i | |
740 | ✗ | placement_list(2,k) = j | |
741 | end do | ||
742 | else | ||
743 |
2/2✓ Branch 0 taken 52 times.
✓ Branch 1 taken 3 times.
|
55 | do j = 1, basis_template%spec(i)%num |
744 |
2/2✓ Branch 0 taken 24 times.
✓ Branch 1 taken 28 times.
|
52 | if(j.le.this%host%spec(i)%num) cycle |
745 | 28 | k = k + 1 | |
746 | 28 | placement_list(1,k) = i | |
747 | 31 | placement_list(2,k) = j | |
748 | end do | ||
749 | end if | ||
750 | end do spec_loop1 | ||
751 | |||
752 | |||
753 | !--------------------------------------------------------------------------- | ||
754 | ! generate the structures | ||
755 | !--------------------------------------------------------------------------- | ||
756 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | if(verbose_.gt.0) write(*,*) "Entering structure generation loop" |
757 | 3 | num_structures_old = this%num_structures | |
758 | 3 | num_structures_new = this%num_structures + num_structures | |
759 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 3 times.
|
6 | structure_loop: do istructure = num_structures_old + 1, num_structures_new |
760 | |||
761 |
1/2✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
|
3 | if(verbose_.gt.0) write(*,*) "Generating structure", istructure |
762 | call this%structures(istructure)%copy( basis = & | ||
763 | this%generate_structure( & | ||
764 | basis_template, & | ||
765 | placement_list, & | ||
766 | method_rand_limit, & | ||
767 | verbose_, & | ||
768 | exit_code_ & | ||
769 | ) & | ||
770 |
14/24✓ Branch 2 taken 3 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 3 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 3 times.
✓ Branch 7 taken 3 times.
✓ Branch 8 taken 3 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 3 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 3 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 3 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 3 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 3 times.
✓ Branch 19 taken 3 times.
✗ Branch 20 not taken.
✓ Branch 21 taken 3 times.
✗ Branch 22 not taken.
✓ Branch 23 taken 3 times.
✓ Branch 24 taken 3 times.
✗ Branch 25 not taken.
|
15 | ) |
771 | 6 | this%num_structures = istructure | |
772 | |||
773 | end do structure_loop | ||
774 |
2/2✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
|
3 | if(verbose_ .gt. 0 .and. exit_code_ .eq. 0) & |
775 | 2 | write(*,*) "Finished generating structures" | |
776 | |||
777 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
|
3 | if(verbose_ .eq. 0)then |
778 | 1 | suppress_warnings = suppress_warnings_store | |
779 | end if | ||
780 | |||
781 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
|
3 | if(present(exit_code))then |
782 | ✗ | exit_code = exit_code_ | |
783 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
|
3 | elseif(exit_code_ .ne. 0)then |
784 | ✗ | call stop_program("Error generating structures", exit_code_) | |
785 | end if | ||
786 | |||
787 |
11/34✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 4 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✗ Branch 8 not taken.
✗ Branch 9 not taken.
✗ Branch 10 not taken.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
✗ Branch 13 not taken.
✗ Branch 14 not taken.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✗ Branch 17 not taken.
✗ Branch 18 not taken.
✗ Branch 19 not taken.
✓ Branch 20 taken 3 times.
✓ Branch 21 taken 1 times.
✓ Branch 22 taken 4 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 4 times.
✗ Branch 25 not taken.
✓ Branch 26 taken 4 times.
✓ Branch 27 taken 4 times.
✓ Branch 28 taken 4 times.
✗ Branch 29 not taken.
✓ Branch 30 taken 4 times.
✗ Branch 31 not taken.
✓ Branch 32 taken 4 times.
✗ Branch 33 not taken.
|
16 | end subroutine generate |
788 | !############################################################################### | ||
789 | |||
790 | |||
791 | !############################################################################### | ||
792 | 3 | function generate_structure( & | |
793 | this, & | ||
794 | basis_initial, & | ||
795 | 3 | placement_list, method_rand_limit, verbose, & | |
796 | exit_code & | ||
797 | ) result(basis) | ||
798 | !! Generate a single random structure. | ||
799 | !! | ||
800 | !! This function generates a single random structure from a host structure | ||
801 | !! by placing atoms according to the ratio of placement methods. | ||
802 | !! The input host structure will already have all host and insert species | ||
803 | !! and atoms allocated. The placement list specifies the atoms in the | ||
804 | !! host structure to be replaced by insert atoms. | ||
805 | implicit none | ||
806 | |||
807 | ! Arguments | ||
808 | class(raffle_generator_type), intent(in) :: this | ||
809 | !! Instance of the raffle generator. | ||
810 | type(basis_type), intent(in) :: basis_initial | ||
811 | !! Initial basis to build upon. | ||
812 | integer, dimension(:,:), intent(in) :: placement_list | ||
813 | !! List of possible placements. | ||
814 | real(real32), dimension(5), intent(in) :: method_rand_limit | ||
815 | !! Upper limit of the random number to call each placement method. | ||
816 | type(extended_basis_type) :: basis | ||
817 | !! Generated basis. | ||
818 | integer, intent(in) :: verbose | ||
819 | !! Verbosity level. | ||
820 | integer, intent(inout) :: exit_code | ||
821 | !! Exit code. | ||
822 | |||
823 | ! Local variables | ||
824 | integer :: iplaced, void_ticker, i | ||
825 | !! Loop counters. | ||
826 | integer :: num_insert_atoms | ||
827 | !! Number of atoms to insert. | ||
828 | real(real32) :: rtmp1 | ||
829 | !! Random number. | ||
830 | logical :: skip_min | ||
831 | !! Boolean for skipping the minimum method. | ||
832 | logical :: viable | ||
833 | !! Boolean for viable placement. | ||
834 | logical :: placement_aborted | ||
835 | !! Boolean for aborted placement. | ||
836 | integer, dimension(size(placement_list,1),size(placement_list,2)) :: & | ||
837 | 6 | placement_list_shuffled | |
838 | !! Shuffled placement list. | ||
839 | real(real32), dimension(3) :: point | ||
840 | !! Coordinate of the atom to place. | ||
841 | real(real32), dimension(5) :: method_rand_limit_, method_rand_limit_store | ||
842 | !! Temporary random limit of each placement method. | ||
843 | !! This is used to update the contribution of the global minimum method if | ||
844 | !! no viable gridpoints are found. | ||
845 | 3 | integer, dimension(:), allocatable :: species_index_list | |
846 | !! List of species indices to add. | ||
847 | 3 | real(real32), dimension(:,:), allocatable :: gridpoint_viability | |
848 | !! Viable gridpoints for placing atoms. | ||
849 | character(len=256) :: stop_msg, warn_msg | ||
850 | !! Error message. | ||
851 | |||
852 | |||
853 | !--------------------------------------------------------------------------- | ||
854 | ! initialise the basis | ||
855 | !--------------------------------------------------------------------------- | ||
856 | 3 | call basis%copy(basis_initial) | |
857 | call basis%create_images( & | ||
858 | max_bondlength = this%distributions%cutoff_max(1) & | ||
859 | 3 | ) | |
860 | 3 | num_insert_atoms = basis%natom - this%host%natom | |
861 | |||
862 | |||
863 | !--------------------------------------------------------------------------- | ||
864 | ! shuffle the placement list | ||
865 | !--------------------------------------------------------------------------- | ||
866 |
4/4✓ Branch 0 taken 32 times.
✓ Branch 1 taken 3 times.
✓ Branch 2 taken 64 times.
✓ Branch 3 taken 32 times.
|
99 | placement_list_shuffled = placement_list |
867 | 3 | call shuffle(placement_list_shuffled,2) | |
868 | |||
869 | |||
870 | !--------------------------------------------------------------------------- | ||
871 | ! generate species index list to add | ||
872 | !--------------------------------------------------------------------------- | ||
873 |
5/10✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 3 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 32 times.
✓ Branch 9 taken 3 times.
|
35 | species_index_list = placement_list_shuffled(1,:) |
874 | 3 | call set(species_index_list) | |
875 | |||
876 | |||
877 | !--------------------------------------------------------------------------- | ||
878 | ! check for viable gridpoints | ||
879 | !--------------------------------------------------------------------------- | ||
880 | 3 | method_rand_limit_ = method_rand_limit | |
881 | gridpoint_viability = get_gridpoints_and_viability( & | ||
882 | this%distributions, & | ||
883 | this%grid, & | ||
884 | this%bounds, & | ||
885 | basis, & | ||
886 | species_index_list, & | ||
887 | [ this%distributions%bond_info(:)%radius_covalent ], & | ||
888 | this%grid_offset & | ||
889 |
13/22✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
✓ Branch 5 taken 3 times.
✓ Branch 6 taken 3 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 3 times.
✓ Branch 9 taken 3 times.
✓ Branch 10 taken 3 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 3 times.
✗ Branch 14 not taken.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✗ Branch 17 not taken.
✓ Branch 18 taken 3 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 45852 times.
✓ Branch 21 taken 3 times.
✓ Branch 22 taken 229260 times.
✓ Branch 23 taken 45852 times.
|
275121 | ) |
890 | |||
891 | |||
892 | !--------------------------------------------------------------------------- | ||
893 | ! place the atoms according to the method ratios | ||
894 | !--------------------------------------------------------------------------- | ||
895 | 3 | iplaced = 0 | |
896 | 3 | void_ticker = 0 | |
897 | 3 | viable = .false. | |
898 | 3 | skip_min = .false. | |
899 | 3 | placement_aborted = .false. | |
900 |
2/2✓ Branch 0 taken 3 times.
✓ Branch 1 taken 32 times.
|
35 | placement_loop: do while (iplaced.lt.num_insert_atoms) |
901 | !------------------------------------------------------------------------ | ||
902 | ! check if there are any viable gridpoints remaining | ||
903 | !------------------------------------------------------------------------ | ||
904 |
2/2✓ Branch 0 taken 29 times.
✓ Branch 1 taken 3 times.
|
32 | if(viable)then |
905 |
1/2✓ Branch 0 taken 29 times.
✗ Branch 1 not taken.
|
29 | if(allocated(gridpoint_viability)) & |
906 | call update_gridpoints_and_viability( & | ||
907 | gridpoint_viability, & | ||
908 | this%distributions, & | ||
909 | basis, & | ||
910 | species_index_list, & | ||
911 | [ placement_list_shuffled(:,iplaced) ], & | ||
912 | [ this%distributions%bond_info(:)%radius_covalent ] & | ||
913 |
12/16✗ Branch 0 not taken.
✓ Branch 1 taken 29 times.
✓ Branch 3 taken 58 times.
✓ Branch 4 taken 29 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 29 times.
✓ Branch 7 taken 58 times.
✓ Branch 8 taken 29 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 29 times.
✓ Branch 12 taken 29 times.
✓ Branch 13 taken 29 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 29 times.
✓ Branch 16 taken 29 times.
✓ Branch 17 taken 29 times.
|
203 | ) |
914 | end if | ||
915 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 32 times.
|
32 | if(.not.allocated(gridpoint_viability))then |
916 | ✗ | write(warn_msg, '("No more viable gridpoints")') | |
917 | warn_msg = trim(warn_msg) // & | ||
918 | achar(13) // achar(10) // & | ||
919 | ✗ | "Stopping atom placement for this structure" | |
920 | ✗ | call print_warning(warn_msg) | |
921 | ✗ | placement_aborted = .true. | |
922 | ✗ | exit placement_loop | |
923 | end if | ||
924 | 32 | viable = .false. | |
925 | !------------------------------------------------------------------------ | ||
926 | ! Choose a placement method | ||
927 | ! call a random number and query the method ratios | ||
928 | !------------------------------------------------------------------------ | ||
929 | 32 | call random_number(rtmp1) | |
930 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 32 times.
|
32 | if(rtmp1.le.method_rand_limit_(1)) then |
931 | ✗ | if(verbose.gt.0) write(*,*) "Add Atom Void" | |
932 | ✗ | point = place_method_void( gridpoint_viability, basis, viable ) | |
933 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 32 times.
|
32 | elseif(rtmp1.le.method_rand_limit_(2)) then |
934 | ✗ | if(verbose.gt.0) write(*,*) "Add Atom Random" | |
935 | point = place_method_rand( & | ||
936 | this%distributions, & | ||
937 | this%bounds, & | ||
938 | basis, & | ||
939 | placement_list_shuffled(1,iplaced+1), & | ||
940 | [ this%distributions%bond_info(:)%radius_covalent ], & | ||
941 | this%max_attempts, & | ||
942 | viable & | ||
943 | ✗ | ) | |
944 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 32 times.
|
32 | elseif(rtmp1.le.method_rand_limit_(3)) then |
945 | ✗ | if(verbose.gt.0) write(*,*) "Add Atom Walk" | |
946 | point = place_method_walk( & | ||
947 | this%distributions, & | ||
948 | this%bounds, & | ||
949 | basis, & | ||
950 | placement_list_shuffled(1,iplaced+1), & | ||
951 | [ this%distributions%bond_info(:)%radius_covalent ], & | ||
952 | this%max_attempts, & | ||
953 | this%walk_step_size_coarse, this%walk_step_size_fine, & | ||
954 | viable & | ||
955 | ✗ | ) | |
956 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 32 times.
|
32 | elseif(rtmp1.le.method_rand_limit_(4)) then |
957 | ✗ | if(iplaced.eq.0)then | |
958 | ✗ | if(verbose.gt.0) write(*,*) "Add Atom Random (growth seed)" | |
959 | point = place_method_rand( & | ||
960 | this%distributions, & | ||
961 | this%bounds, & | ||
962 | basis, & | ||
963 | placement_list_shuffled(1,iplaced+1), & | ||
964 | [ this%distributions%bond_info(:)%radius_covalent ], & | ||
965 | this%max_attempts, & | ||
966 | viable & | ||
967 | ✗ | ) | |
968 | else | ||
969 | ✗ | if(verbose.gt.0) write(*,*) "Add Atom Growth" | |
970 | point = place_method_growth( & | ||
971 | this%distributions, & | ||
972 | basis%spec(placement_list_shuffled(1,iplaced))%atom( & | ||
973 | placement_list_shuffled(2,iplaced),:3 & | ||
974 | ), & | ||
975 | placement_list_shuffled(1,iplaced), & | ||
976 | this%bounds, & | ||
977 | basis, & | ||
978 | placement_list_shuffled(1,iplaced+1), & | ||
979 | [ this%distributions%bond_info(:)%radius_covalent ], & | ||
980 | this%max_attempts, & | ||
981 | this%walk_step_size_coarse, this%walk_step_size_fine, & | ||
982 | viable & | ||
983 | ✗ | ) | |
984 | end if | ||
985 |
1/2✓ Branch 0 taken 32 times.
✗ Branch 1 not taken.
|
32 | elseif(rtmp1.le.method_rand_limit_(5)) then |
986 |
1/2✓ Branch 0 taken 32 times.
✗ Branch 1 not taken.
|
32 | if(verbose.gt.0) write(*,*) "Add Atom Minimum" |
987 | point = place_method_min( gridpoint_viability, & | ||
988 | placement_list_shuffled(1,iplaced+1), & | ||
989 | species_index_list, & | ||
990 | viable & | ||
991 | 32 | ) | |
992 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 32 times.
|
32 | if(.not. viable .and. abs(method_rand_limit_(4)).lt.1.E-6)then |
993 | write(warn_msg, & | ||
994 | '("Minimum method failed, no other methods available")' & | ||
995 | ✗ | ) | |
996 | warn_msg = trim(warn_msg) // & | ||
997 | achar(13) // achar(10) // & | ||
998 | ✗ | "Stopping atom placement for this structure" | |
999 | ✗ | call print_warning(warn_msg) | |
1000 | ✗ | placement_aborted = .true. | |
1001 | ✗ | exit placement_loop | |
1002 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 32 times.
|
32 | elseif(.not.viable)then |
1003 | ✗ | skip_min = .true. | |
1004 | ✗ | method_rand_limit_store = method_rand_limit_ | |
1005 | ✗ | method_rand_limit_ = method_rand_limit_ / method_rand_limit_(4) | |
1006 | ✗ | method_rand_limit_(5) = method_rand_limit_(4) | |
1007 | end if | ||
1008 | end if | ||
1009 | !------------------------------------------------------------------------ | ||
1010 | ! check if the placement method returned a viable point | ||
1011 | ! if not, cycle the loop | ||
1012 | !------------------------------------------------------------------------ | ||
1013 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 32 times.
|
32 | if(.not. viable)then |
1014 | ✗ | void_ticker = void_ticker + 1 | |
1015 | ✗ | if(void_ticker.gt.10.and..not.allocated(gridpoint_viability))then | |
1016 | ✗ | write(warn_msg, '("No more viable gridpoints")') | |
1017 | warn_msg = trim(warn_msg) // & | ||
1018 | achar(13) // achar(10) // & | ||
1019 | ✗ | "Stopping atom placement for this structure" | |
1020 | ✗ | call print_warning(warn_msg) | |
1021 | ✗ | placement_aborted = .true. | |
1022 | ✗ | exit placement_loop | |
1023 | ✗ | elseif(void_ticker.gt.10)then | |
1024 | ✗ | point = place_method_void( gridpoint_viability, basis, viable ) | |
1025 | ✗ | void_ticker = 0 | |
1026 | end if | ||
1027 | ✗ | if(.not.viable) cycle placement_loop | |
1028 | end if | ||
1029 | !------------------------------------------------------------------------ | ||
1030 | ! place the atom and update the image atoms in the basis | ||
1031 | !------------------------------------------------------------------------ | ||
1032 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 32 times.
|
32 | if(skip_min)then |
1033 | ✗ | method_rand_limit_ = method_rand_limit_store | |
1034 | ✗ | skip_min = .false. | |
1035 | end if | ||
1036 | 32 | iplaced = iplaced + 1 | |
1037 | basis%spec(placement_list_shuffled(1,iplaced))%atom( & | ||
1038 |
2/2✓ Branch 0 taken 96 times.
✓ Branch 1 taken 32 times.
|
128 | placement_list_shuffled(2,iplaced),:3) = point(:3) |
1039 | basis%spec(placement_list_shuffled(1,iplaced))%atom_mask( & | ||
1040 | 32 | placement_list_shuffled(2,iplaced)) = .true. | |
1041 | call basis%update_images( & | ||
1042 | max_bondlength = this%distributions%cutoff_max(1), & | ||
1043 | is = placement_list_shuffled(1,iplaced), & | ||
1044 | ia = placement_list_shuffled(2,iplaced) & | ||
1045 | 32 | ) | |
1046 |
1/2✓ Branch 0 taken 32 times.
✗ Branch 1 not taken.
|
32 | if(verbose.gt.0)then |
1047 | 32 | write(*,'(A)',ADVANCE='NO') achar(13) | |
1048 | write(*,'(2X,"placed atom ",I0," [",I0,",",I0,"] at",3(1X,F6.3))') & | ||
1049 | 32 | iplaced, placement_list_shuffled(1:2,iplaced), point(:3) | |
1050 | 32 | write(*,*) | |
1051 | end if | ||
1052 | |||
1053 | end do placement_loop | ||
1054 | |||
1055 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
|
3 | if(placement_aborted)then |
1056 | call stop_program( & | ||
1057 | "Placement routine aborted, not all atoms placed", & | ||
1058 | block_stop = .true. & | ||
1059 | ✗ | ) | |
1060 | ✗ | exit_code = 1 | |
1061 | ✗ | call basis%remove_atoms(placement_list_shuffled(:,iplaced+1:)) | |
1062 | end if | ||
1063 | |||
1064 |
2/4✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
|
3 | if(allocated(gridpoint_viability)) deallocate(gridpoint_viability) |
1065 | |||
1066 |
9/12✓ Branch 0 taken 9 times.
✓ Branch 1 taken 3 times.
✓ Branch 2 taken 27 times.
✓ Branch 3 taken 9 times.
✓ Branch 4 taken 9 times.
✓ Branch 5 taken 3 times.
✓ Branch 6 taken 3 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 3 times.
✗ Branch 9 not taken.
✗ Branch 10 not taken.
✓ Branch 11 taken 3 times.
|
51 | end function generate_structure |
1067 | !############################################################################### | ||
1068 | |||
1069 | |||
1070 | !############################################################################### | ||
1071 | 3 | function get_structures(this) result(structures) | |
1072 | !! Get the generated structures. | ||
1073 | implicit none | ||
1074 | ! Arguments | ||
1075 | class(raffle_generator_type), intent(in) :: this | ||
1076 | !! Instance of the raffle generator. | ||
1077 | type(basis_type), dimension(:), allocatable :: structures | ||
1078 | !! Generated structures. | ||
1079 | |||
1080 |
19/64✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 3 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 3 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 3 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 3 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 8 times.
✓ Branch 15 taken 3 times.
✗ Branch 16 not taken.
✗ Branch 17 not taken.
✗ Branch 18 not taken.
✗ Branch 19 not taken.
✗ Branch 20 not taken.
✗ Branch 21 not taken.
✗ Branch 22 not taken.
✗ Branch 23 not taken.
✗ Branch 24 not taken.
✗ Branch 25 not taken.
✗ Branch 26 not taken.
✗ Branch 27 not taken.
✗ Branch 28 not taken.
✗ Branch 29 not taken.
✗ Branch 30 not taken.
✗ Branch 31 not taken.
✗ Branch 32 not taken.
✗ Branch 33 not taken.
✗ Branch 34 not taken.
✗ Branch 35 not taken.
✓ Branch 36 taken 8 times.
✓ Branch 37 taken 3 times.
✓ Branch 38 taken 8 times.
✗ Branch 39 not taken.
✓ Branch 40 taken 8 times.
✗ Branch 41 not taken.
✓ Branch 42 taken 8 times.
✓ Branch 43 taken 8 times.
✓ Branch 44 taken 8 times.
✗ Branch 45 not taken.
✓ Branch 46 taken 8 times.
✗ Branch 47 not taken.
✓ Branch 48 taken 8 times.
✗ Branch 49 not taken.
✓ Branch 50 taken 8 times.
✗ Branch 51 not taken.
✗ Branch 52 not taken.
✓ Branch 53 taken 8 times.
✗ Branch 54 not taken.
✗ Branch 55 not taken.
✗ Branch 56 not taken.
✗ Branch 57 not taken.
✗ Branch 58 not taken.
✗ Branch 59 not taken.
✗ Branch 60 not taken.
✗ Branch 61 not taken.
✗ Branch 62 not taken.
✗ Branch 63 not taken.
|
30 | structures = this%structures |
1081 | 3 | end function get_structures | |
1082 | !############################################################################### | ||
1083 | |||
1084 | |||
1085 | !############################################################################### | ||
1086 | 1 | subroutine set_structures(this, structures) | |
1087 | !! Set the generated structures. | ||
1088 | !! | ||
1089 | !! This procedure overwrites the array of generated structures with the | ||
1090 | !! input array. | ||
1091 | !! This can be useful for removing structures that are not viable from the | ||
1092 | !! array. | ||
1093 | implicit none | ||
1094 | ! Arguments | ||
1095 | class(raffle_generator_type), intent(inout) :: this | ||
1096 | !! Instance of the raffle generator. | ||
1097 | type(basis_type), dimension(..), allocatable, intent(in) :: structures | ||
1098 | !! Array of structures to set. | ||
1099 | |||
1100 | select rank(structures) | ||
1101 | rank(0) | ||
1102 | ✗ | this%structures = [ structures ] | |
1103 | rank(1) | ||
1104 |
29/62✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
✗ Branch 13 not taken.
✓ Branch 14 taken 1 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 2 times.
✓ Branch 17 taken 1 times.
✓ Branch 18 taken 2 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 2 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 2 times.
✓ Branch 23 taken 2 times.
✓ Branch 24 taken 2 times.
✗ Branch 25 not taken.
✓ Branch 26 taken 2 times.
✗ Branch 27 not taken.
✓ Branch 28 taken 2 times.
✗ Branch 29 not taken.
✓ Branch 30 taken 1 times.
✗ Branch 31 not taken.
✓ Branch 32 taken 3 times.
✓ Branch 33 taken 1 times.
✓ Branch 34 taken 3 times.
✓ Branch 35 taken 1 times.
✓ Branch 36 taken 3 times.
✗ Branch 37 not taken.
✓ Branch 38 taken 3 times.
✗ Branch 39 not taken.
✓ Branch 40 taken 3 times.
✓ Branch 41 taken 3 times.
✓ Branch 42 taken 3 times.
✗ Branch 43 not taken.
✓ Branch 44 taken 3 times.
✗ Branch 45 not taken.
✓ Branch 46 taken 3 times.
✗ Branch 47 not taken.
✓ Branch 48 taken 3 times.
✗ Branch 49 not taken.
✗ Branch 50 not taken.
✓ Branch 51 taken 3 times.
✗ Branch 52 not taken.
✗ Branch 53 not taken.
✗ Branch 54 not taken.
✗ Branch 55 not taken.
✗ Branch 56 not taken.
✗ Branch 57 not taken.
✗ Branch 58 not taken.
✗ Branch 59 not taken.
✗ Branch 60 not taken.
✗ Branch 61 not taken.
|
16 | this%structures = structures |
1105 | rank default | ||
1106 | ✗ | call stop_program("Invalid rank for structures") | |
1107 | end select | ||
1108 | 1 | this%num_structures = size(this%structures) | |
1109 | 1 | end subroutine set_structures | |
1110 | !############################################################################### | ||
1111 | |||
1112 | |||
1113 | !############################################################################### | ||
1114 | 1 | subroutine remove_structure(this, index) | |
1115 | !! Remove structures from the generated structures. | ||
1116 | !! | ||
1117 | !! This procedure removes structures from the array of generated structures | ||
1118 | !! at the specified indices. | ||
1119 | implicit none | ||
1120 | ! Arguments | ||
1121 | class(raffle_generator_type), intent(inout) :: this | ||
1122 | !! Instance of the raffle generator. | ||
1123 | integer, dimension(..), intent(in) :: index | ||
1124 | !! Indices of the structures to remove. | ||
1125 | |||
1126 | ! Local variables | ||
1127 | integer :: i | ||
1128 | !! Loop index. | ||
1129 | 1 | integer, dimension(:), allocatable :: index_ | |
1130 | !! Indices of the structures to keep. | ||
1131 | |||
1132 | select rank(index) | ||
1133 | rank(0) | ||
1134 |
5/10✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 1 times.
|
2 | index_ = [ index ] |
1135 | rank(1) | ||
1136 | ✗ | index_ = index | |
1137 | rank default | ||
1138 | ✗ | call stop_program("Invalid rank for index") | |
1139 | end select | ||
1140 | |||
1141 |
7/10✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✓ Branch 4 taken 1 times.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
|
3 | if(any(index_.lt.1) .or. any(index_.gt.this%num_structures))then |
1142 | ✗ | call stop_program("Invalid index") | |
1143 | ✗ | return | |
1144 | end if | ||
1145 | |||
1146 | 1 | call sort1D(index_, reverse=.true.) | |
1147 | |||
1148 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | do i = 1, size(index_) |
1149 | this%structures = [ & | ||
1150 | this%structures(:index_(i)-1:1), & | ||
1151 | this%structures(index_(i)+1:this%num_structures:1) & | ||
1152 |
34/68✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✓ Branch 8 taken 2 times.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 1 times.
✓ Branch 12 taken 2 times.
✓ Branch 13 taken 1 times.
✓ Branch 14 taken 2 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 2 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 2 times.
✓ Branch 19 taken 2 times.
✓ Branch 20 taken 2 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 2 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 2 times.
✗ Branch 25 not taken.
✓ Branch 26 taken 1 times.
✗ Branch 27 not taken.
✗ Branch 28 not taken.
✓ Branch 29 taken 1 times.
✗ Branch 30 not taken.
✓ Branch 31 taken 1 times.
✗ Branch 32 not taken.
✗ Branch 33 not taken.
✗ Branch 34 not taken.
✗ Branch 35 not taken.
✓ Branch 36 taken 1 times.
✗ Branch 37 not taken.
✓ Branch 38 taken 3 times.
✓ Branch 39 taken 1 times.
✓ Branch 40 taken 3 times.
✗ Branch 41 not taken.
✓ Branch 42 taken 3 times.
✗ Branch 43 not taken.
✓ Branch 44 taken 3 times.
✓ Branch 45 taken 3 times.
✓ Branch 46 taken 3 times.
✗ Branch 47 not taken.
✓ Branch 48 taken 3 times.
✗ Branch 49 not taken.
✓ Branch 50 taken 3 times.
✗ Branch 51 not taken.
✓ Branch 52 taken 1 times.
✗ Branch 53 not taken.
✓ Branch 54 taken 2 times.
✓ Branch 55 taken 1 times.
✓ Branch 56 taken 2 times.
✓ Branch 57 taken 1 times.
✗ Branch 58 not taken.
✓ Branch 59 taken 2 times.
✗ Branch 60 not taken.
✗ Branch 61 not taken.
✗ Branch 62 not taken.
✗ Branch 63 not taken.
✗ Branch 64 not taken.
✗ Branch 65 not taken.
✗ Branch 66 not taken.
✗ Branch 67 not taken.
✗ Branch 68 not taken.
✗ Branch 69 not taken.
|
19 | ] |
1153 | 2 | this%num_structures = this%num_structures - 1 | |
1154 | end do | ||
1155 | |||
1156 |
1/2✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
|
1 | end subroutine remove_structure |
1157 | !############################################################################### | ||
1158 | |||
1159 | |||
1160 | !############################################################################### | ||
1161 | ✗ | subroutine allocate_structures(this, num_structures) | |
1162 | !! Allocate memory for the generated structures. | ||
1163 | implicit none | ||
1164 | ! Arguments | ||
1165 | class(raffle_generator_type), intent(inout) :: this | ||
1166 | !! Instance of the raffle generator. | ||
1167 | integer, intent(in) :: num_structures | ||
1168 | !! Number of structures to allocate memory for. | ||
1169 | |||
1170 | ✗ | if(allocated(this%structures)) deallocate(this%structures) | |
1171 | ✗ | allocate(this%structures(num_structures)) | |
1172 | ✗ | this%num_structures = num_structures | |
1173 | ✗ | end subroutine allocate_structures | |
1174 | !############################################################################### | ||
1175 | |||
1176 | |||
1177 | !############################################################################### | ||
1178 | 1 | function evaluate(this, basis) result(viability) | |
1179 | !! Evaluate the viability of the generated structures. | ||
1180 | use raffle__evaluator, only: evaluate_point | ||
1181 | implicit none | ||
1182 | ! Arguments | ||
1183 | class(raffle_generator_type), intent(inout) :: this | ||
1184 | !! Instance of the raffle generator. | ||
1185 | type(basis_type), intent(in) :: basis | ||
1186 | !! Basis of the structure to evaluate. | ||
1187 | real(real32) :: viability | ||
1188 | !! Viability of the generated structures. | ||
1189 | |||
1190 | ! Local variables | ||
1191 | integer :: is, ia, idx | ||
1192 | !! Loop indices. | ||
1193 |
6/6✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 9 times.
✓ Branch 3 taken 3 times.
✓ Branch 4 taken 3 times.
✓ Branch 5 taken 1 times.
|
16 | type(extended_basis_type) :: basis_extd |
1194 | !! Extended basis for the structure to evaluate. | ||
1195 | |||
1196 | |||
1197 | 1 | call basis_extd%copy(basis) | |
1198 | call basis_extd%create_images( & | ||
1199 | max_bondlength = this%distributions%cutoff_max(1) & | ||
1200 | 1 | ) | |
1201 | 1 | viability = 0.0_real32 | |
1202 | call this%distributions%set_element_map( & | ||
1203 | [ basis_extd%spec(:)%name ] & | ||
1204 |
6/8✗ 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 1 times.
✓ Branch 8 taken 1 times.
|
3 | ) |
1205 | 1 | call this%distributions%set_num_bins() | |
1206 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | do is = 1, basis%nspec |
1207 | idx = this%distributions%get_element_index( & | ||
1208 | basis_extd%spec(is)%name & | ||
1209 | 1 | ) | |
1210 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | if(idx.eq.0)then |
1211 | call stop_program( & | ||
1212 | "Species "//& | ||
1213 | trim(basis_extd%spec(is)%name)//& | ||
1214 | " not found in distribution functions" & | ||
1215 | ✗ | ) | |
1216 | ✗ | return | |
1217 | end if | ||
1218 |
2/2✓ Branch 0 taken 16 times.
✓ Branch 1 taken 1 times.
|
18 | do ia = 1, basis%spec(is)%num |
1219 | 16 | basis_extd%spec(is)%atom_mask(ia) = .false. | |
1220 | viability = viability + & | ||
1221 | evaluate_point( this%distributions, & | ||
1222 | [ basis%spec(is)%atom(ia,1:3) ], & | ||
1223 | is, basis_extd, & | ||
1224 | [ this%distributions%bond_info(:)%radius_covalent ] & | ||
1225 |
10/12✓ Branch 0 taken 48 times.
✓ Branch 1 taken 16 times.
✓ Branch 2 taken 48 times.
✓ Branch 3 taken 16 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 16 times.
✓ Branch 7 taken 16 times.
✓ Branch 8 taken 16 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 16 times.
✓ Branch 11 taken 16 times.
✓ Branch 12 taken 16 times.
|
144 | ) |
1226 | 17 | basis_extd%spec(is)%atom_mask(ia) = .true. | |
1227 | end do | ||
1228 | end do | ||
1229 | |||
1230 | 1 | viability = viability / real(basis%natom, real32) | |
1231 |
14/24✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 1 times.
✓ Branch 5 taken 1 times.
✓ Branch 6 taken 1 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 1 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 1 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 1 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 1 times.
✓ Branch 17 taken 1 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 1 times.
✗ Branch 20 not taken.
✓ Branch 21 taken 1 times.
✓ Branch 22 taken 1 times.
✗ Branch 23 not taken.
|
3 | end function evaluate |
1232 | !############################################################################### | ||
1233 | |||
1234 | |||
1235 | !############################################################################### | ||
1236 | ✗ | function get_probability_density(this, basis, species_list, & | |
1237 | grid, grid_offset, grid_spacing, bounds, & | ||
1238 | grid_output & | ||
1239 | ) result(probability) | ||
1240 | !! Get the probability density of the generated structures. | ||
1241 | implicit none | ||
1242 | |||
1243 | ! Arguments | ||
1244 | class(raffle_generator_type), intent(inout) :: this | ||
1245 | !! Instance of the raffle generator. | ||
1246 | type(basis_type), intent(in) :: basis | ||
1247 | !! Structure to evaluate. | ||
1248 | character(len=3), dimension(:), intent(in) :: species_list | ||
1249 | !! List of species to evaluate. | ||
1250 | integer, dimension(3), intent(in), optional :: grid | ||
1251 | !! Number of bins to divide the host structure into along each axis. | ||
1252 | real(real32), dimension(3), intent(in), optional :: grid_offset | ||
1253 | !! Offset of the gridpoints. | ||
1254 | real(real32), intent(in), optional :: grid_spacing | ||
1255 | !! Spacing of the bins. | ||
1256 | real(real32), dimension(2,3), intent(in), optional :: bounds | ||
1257 | !! Bounds for atom placement. | ||
1258 | integer, dimension(3), intent(out), optional :: grid_output | ||
1259 | |||
1260 | real(real32), dimension(:,:), allocatable :: probability | ||
1261 | |||
1262 | ! Local variables | ||
1263 | integer :: i, is, ia, idx | ||
1264 | !! Loop indices. | ||
1265 | real(real32) :: grid_spacing_ | ||
1266 | !! Spacing of the bins. | ||
1267 | integer, dimension(3) :: grid_ | ||
1268 | !! Number of bins to divide the host structure into along each axis. | ||
1269 | ✗ | integer, dimension(size(species_list,1)) :: species_idx_list | |
1270 | real(real32), dimension(3) :: grid_offset_ | ||
1271 | !! Offset of the gridpoints. | ||
1272 | real(real32), dimension(2,3) :: bounds_ | ||
1273 | !! Bounds for atom placement. | ||
1274 | ✗ | type(extended_basis_type) :: basis_extd | |
1275 | !! Extended basis for the structure to evaluate. | ||
1276 | |||
1277 | |||
1278 | !--------------------------------------------------------------------------- | ||
1279 | ! Set the grid and bounds | ||
1280 | !--------------------------------------------------------------------------- | ||
1281 | ✗ | grid_ = -1 | |
1282 | ✗ | grid_spacing_ = -1._real32 | |
1283 | ✗ | grid_offset_ = 0._real32 | |
1284 | ✗ | bounds_(1,:) = 0._real32 | |
1285 | ✗ | bounds_(2,:) = 1._real32 | |
1286 | ✗ | if(present(grid)) grid_ = grid | |
1287 | ✗ | if(present(grid_offset)) grid_offset_ = grid_offset | |
1288 | ✗ | if(present(grid_spacing)) grid_spacing_ = grid_spacing | |
1289 | ✗ | if(present(bounds)) bounds_ = bounds | |
1290 | |||
1291 | ✗ | if(any(grid_.eq.-1))then | |
1292 | ✗ | if(grid_spacing_.lt.0._real32)then | |
1293 | ✗ | call stop_program("Grid or grid spacing not set. One must be set") | |
1294 | ✗ | return | |
1295 | end if | ||
1296 | ✗ | do i = 1, 3 | |
1297 | grid_(i) = nint( & | ||
1298 | ( bounds_(2,i) - bounds_(1,i) ) * & | ||
1299 | norm2(basis%lat(i,:)) / grid_spacing_ & | ||
1300 | ✗ | ) | |
1301 | end do | ||
1302 | end if | ||
1303 | ✗ | if(present(grid_output)) grid_output = grid_ | |
1304 | ✗ | call this%distributions%set_num_bins() | |
1305 | |||
1306 | |||
1307 | ✗ | call basis_extd%copy(basis) | |
1308 | ✗ | do i = 1, size(species_list) | |
1309 | call basis_extd%add_atom( & | ||
1310 | species_list(i), & | ||
1311 | position = [0._real32, 0._real32, 0._real32], & | ||
1312 | mask = .false. & | ||
1313 | ✗ | ) | |
1314 | species_idx_list(i) = & | ||
1315 | ✗ | findloc(basis_extd%spec(:)%name, strip_null(species_list(i)), dim=1) | |
1316 | end do | ||
1317 | ✗ | do is = 1, basis_extd%nspec | |
1318 | idx = this%distributions%get_element_index( & | ||
1319 | basis_extd%spec(is)%name & | ||
1320 | ✗ | ) | |
1321 | ✗ | if(idx.eq.0)then | |
1322 | call stop_program( & | ||
1323 | "Species "//& | ||
1324 | trim(basis_extd%spec(is)%name)//& | ||
1325 | " not found in distribution functions" & | ||
1326 | ✗ | ) | |
1327 | ✗ | return | |
1328 | end if | ||
1329 | end do | ||
1330 | call basis_extd%create_images( & | ||
1331 | max_bondlength = this%distributions%cutoff_max(1) & | ||
1332 | ✗ | ) | |
1333 | |||
1334 | |||
1335 | call this%distributions%set_element_map( & | ||
1336 | [ basis_extd%spec(:)%name ] & | ||
1337 | ✗ | ) | |
1338 | probability = get_gridpoints_and_viability( & | ||
1339 | this%distributions, & | ||
1340 | grid_, & | ||
1341 | bounds_, & | ||
1342 | basis_extd, & | ||
1343 | species_idx_list, & | ||
1344 | [ this%distributions%bond_info(:)%radius_covalent ], & | ||
1345 | grid_offset = grid_offset_ & | ||
1346 | ✗ | ) | |
1347 | |||
1348 | ✗ | end function get_probability_density | |
1349 | !############################################################################### | ||
1350 | |||
1351 | |||
1352 | !############################################################################### | ||
1353 | 1 | subroutine print_generator_settings(this, file) | |
1354 | !! Print the raffle generator settings. | ||
1355 | implicit none | ||
1356 | |||
1357 | ! Arguments | ||
1358 | class(raffle_generator_type), intent(in) :: this | ||
1359 | !! Instance of the raffle generator. | ||
1360 | character(*), intent(in) :: file | ||
1361 | !! Filename to write the settings to. | ||
1362 | |||
1363 | ! Local variables | ||
1364 | integer :: i | ||
1365 | !! Loop index. | ||
1366 | integer :: unit | ||
1367 | !! Unit number for the file. | ||
1368 | |||
1369 | ! Open the file | ||
1370 | 1 | open(newunit=unit, file=file) | |
1371 | |||
1372 | 1 | write(unit,'("# RAFFLE Generator Settings")') | |
1373 | 1 | write(unit,'("# GENERATOR SETTINGS")') | |
1374 | 1 | write(unit,'("HOST_LATTICE # not a setting, just for reference")') | |
1375 | 1 | write(unit,'(" ",3(1X,F5.2))') this%host%lat(1,:) | |
1376 | 1 | write(unit,'(" ",3(1X,F5.2))') this%host%lat(2,:) | |
1377 | 1 | write(unit,'(" ",3(1X,F5.2))') this%host%lat(3,:) | |
1378 | 1 | write(unit,'("END HOST_LATTICE")') | |
1379 | |||
1380 | 1 | write(unit,'("GRID =",3(1X,I0))') this%grid | |
1381 | 1 | write(unit,'("GRID_OFFSET =",3(1X,F15.9))') this%grid_offset | |
1382 | 1 | write(unit,'("GRID_SPACING = ",F15.9)') this%grid_spacing | |
1383 | 1 | write(unit,'("BOUNDS_LW =",3(1X,F15.9))') this%bounds(1,:) | |
1384 | 1 | write(unit,'("BOUNDS_UP =",3(1X,F15.9))') this%bounds(2,:) | |
1385 | |||
1386 | 1 | write(unit,'("MAX_ATTEMPTS =",I0)') this%max_attempts | |
1387 | 1 | write(unit,'("WALK_STEP_SIZE_COARSE = ",F15.9)') this%walk_step_size_coarse | |
1388 | 1 | write(unit,'("WALK_STEP_SIZE_FINE = ",F15.9)') this%walk_step_size_fine | |
1389 | 1 | write(unit,'("METHOD_VOID = ",F15.9)') this%method_ratio(1) | |
1390 | 1 | write(unit,'("METHOD_RANDOM = ",F15.9)') this%method_ratio(2) | |
1391 | 1 | write(unit,'("METHOD_WALK = ",F15.9)') this%method_ratio(3) | |
1392 | 1 | write(unit,'("METHOD_GROW = ",F15.9)') this%method_ratio(4) | |
1393 | 1 | write(unit,'("METHOD_MIN = ",F15.9)') this%method_ratio(5) | |
1394 | |||
1395 | 1 | write(unit,'("# DISTRIBUTION SETTINGS")') | |
1396 | 1 | write(unit,'("KBT = ",F5.2)') this%distributions%kbt | |
1397 | 1 | write(unit,'("SIGMA =",3(1X,F15.9))') this%distributions%sigma | |
1398 | 1 | write(unit,'("WIDTH =",3(1X,F15.9))') this%distributions%width | |
1399 | 1 | write(unit,'("CUTOFF_MIN =",3(1X,F15.9))') this%distributions%cutoff_min | |
1400 | 1 | write(unit,'("CUTOFF_MAX =",3(1X,F15.9))') this%distributions%cutoff_max | |
1401 | write(unit,'("RADIUS_DISTANCE_TOLERANCE =",4(1X,F15.9))') & | ||
1402 | 1 | this%distributions%radius_distance_tol | |
1403 | 1 | write(unit,'("ELEMENT_INFO # element : energy")') | |
1404 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | do i = 1, size(this%distributions%element_info) |
1405 | write(unit,'(" ",A," : ",F15.9)') & | ||
1406 | 1 | this%distributions%element_info(i)%name, & | |
1407 | 3 | this%distributions%element_info(i)%energy | |
1408 | end do | ||
1409 | 1 | write(unit,'("END ELEMENT_INFO")') | |
1410 | 1 | write(unit,'("BOND_INFO # element1 element2 : radius")') | |
1411 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | do i = 1, size(this%distributions%bond_info) |
1412 | write(unit,'(" ",A," ",A," : ",F15.9)') & | ||
1413 | 1 | this%distributions%bond_info(i)%element(1), & | |
1414 | 1 | this%distributions%bond_info(i)%element(2), & | |
1415 | 3 | this%distributions%bond_info(i)%radius_covalent | |
1416 | end do | ||
1417 | 1 | write(unit,'("END BOND_INFO")') | |
1418 | |||
1419 | 1 | close(unit) | |
1420 | |||
1421 | 1 | end subroutine print_generator_settings | |
1422 | !############################################################################### | ||
1423 | |||
1424 | |||
1425 | !############################################################################### | ||
1426 | 1 | subroutine read_generator_settings(this, file) | |
1427 | !! Read the raffle generator settings. | ||
1428 | implicit none | ||
1429 | |||
1430 | ! Arguments | ||
1431 | class(raffle_generator_type), intent(inout) :: this | ||
1432 | !! Instance of the raffle generator. | ||
1433 | character(*), intent(in) :: file | ||
1434 | !! Filename to read the settings from. | ||
1435 | |||
1436 | ! Local variables | ||
1437 | integer :: i | ||
1438 | !! Loop index. | ||
1439 | integer :: itmp1, status | ||
1440 | !! Temporary integer. | ||
1441 | integer :: unit | ||
1442 | !! Unit number for the file. | ||
1443 | logical :: exist | ||
1444 | !! Boolean for file existence. | ||
1445 | character(len=256) :: line, buffer, tag | ||
1446 | !! Line from the file. | ||
1447 | character(3), dimension(2) :: elements | ||
1448 | !! Element symbols. | ||
1449 | real(real32) :: rtmp1 | ||
1450 | !! Temporary real number. | ||
1451 | |||
1452 | ! Check if the file exists | ||
1453 | 1 | inquire(file=file, exist=exist) | |
1454 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | if(.not.exist)then |
1455 | ✗ | call stop_program("File does not exist") | |
1456 | ✗ | return | |
1457 | end if | ||
1458 | |||
1459 | ! Open the file | ||
1460 | 1 | open(newunit=unit, file=file) | |
1461 | |||
1462 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | if(allocated(this%distributions%element_info)) & |
1463 | ✗ | deallocate(this%distributions%element_info) | |
1464 |
1/2✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
|
1 | if(allocated(this%distributions%bond_info)) & |
1465 | ✗ | deallocate(this%distributions%bond_info) | |
1466 | 1 | itmp1 = 0 | |
1467 | 25 | do | |
1468 | 26 | read(unit, '(A)', iostat = status) line | |
1469 | ! encounter end of line | ||
1470 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 25 times.
|
26 | if(status.ne.0) exit |
1471 | |||
1472 |
3/4✓ Branch 0 taken 6 times.
✓ Branch 1 taken 19 times.
✓ Branch 2 taken 6 times.
✗ Branch 3 not taken.
|
25 | if(index(line,'#').gt.0) line = line(1:index(line,'#')-1) |
1473 |
3/4✓ Branch 3 taken 22 times.
✓ Branch 4 taken 3 times.
✓ Branch 5 taken 25 times.
✗ Branch 6 not taken.
|
25 | line = to_upper(trim(adjustl(line))) |
1474 |
4/4✓ Branch 1 taken 22 times.
✓ Branch 2 taken 3 times.
✓ Branch 3 taken 3 times.
✓ Branch 4 taken 22 times.
|
25 | if(len(trim(line)).eq.0) cycle |
1475 | |||
1476 |
2/4✓ Branch 2 taken 22 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 22 times.
✗ Branch 5 not taken.
|
22 | tag=trim(adjustl(line)) |
1477 |
4/6✓ Branch 0 taken 19 times.
✓ Branch 1 taken 3 times.
✓ Branch 3 taken 19 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 19 times.
✗ Branch 6 not taken.
|
22 | if(scan(line,"=").ne.0) tag=trim(tag(:scan(tag,"=")-1)) |
1478 | |||
1479 | 44 | select case(trim(adjustl(tag))) | |
1480 | case("HOST_LATTICE") | ||
1481 |
2/2✓ Branch 0 taken 4 times.
✓ Branch 1 taken 1 times.
|
6 | do i = 1, 4 |
1482 | 5 | read(unit,*) | |
1483 | end do | ||
1484 | case("GRID") | ||
1485 | 1 | call assign_vec(line, this%grid, itmp1) | |
1486 | case("GRID_OFFSET") | ||
1487 | 1 | call assign_vec(line, this%grid_offset, itmp1) | |
1488 | case("GRID_SPACING") | ||
1489 | 1 | call assign_val(line, this%grid_spacing, itmp1) | |
1490 | case("BOUNDS_LW") | ||
1491 | 1 | call assign_vec(line, this%bounds(1,:), itmp1) | |
1492 | case("BOUNDS_UP") | ||
1493 | 1 | call assign_vec(line, this%bounds(2,:), itmp1) | |
1494 | case("MAX_ATTEMPTS") | ||
1495 | 1 | call assign_val(line, this%max_attempts, itmp1) | |
1496 | case("WALK_STEP_SIZE_COARSE") | ||
1497 | 1 | call assign_val(line, this%walk_step_size_coarse, itmp1) | |
1498 | case("WALK_STEP_SIZE_FINE") | ||
1499 | 1 | call assign_val(line, this%walk_step_size_fine, itmp1) | |
1500 | case("METHOD_VOID") | ||
1501 | 1 | call assign_val(line, this%method_ratio(1), itmp1) | |
1502 | case("METHOD_RANDOM") | ||
1503 | 1 | call assign_val(line, this%method_ratio(2), itmp1) | |
1504 | case("METHOD_WALK") | ||
1505 | 1 | call assign_val(line, this%method_ratio(3), itmp1) | |
1506 | case("METHOD_GROW") | ||
1507 | 1 | call assign_val(line, this%method_ratio(4), itmp1) | |
1508 | case("METHOD_MIN") | ||
1509 | 1 | call assign_val(line, this%method_ratio(5), itmp1) | |
1510 | case("KBT") | ||
1511 | 1 | call assign_val(line, this%distributions%kbt, itmp1) | |
1512 | case("SIGMA") | ||
1513 | 1 | call assign_vec(line, this%distributions%sigma, itmp1) | |
1514 | case("WIDTH") | ||
1515 | 1 | call assign_vec(line, this%distributions%width, itmp1) | |
1516 | case("CUTOFF_MIN") | ||
1517 | 1 | call assign_vec(line, this%distributions%cutoff_min, itmp1) | |
1518 | case("CUTOFF_MAX") | ||
1519 | 1 | call assign_vec(line, this%distributions%cutoff_max, itmp1) | |
1520 | case("RADIUS_DISTANCE_TOLERANCE") | ||
1521 | 1 | call assign_vec(line, this%distributions%radius_distance_tol, itmp1) | |
1522 | case("ELEMENT_INFO") | ||
1523 | 2 | do | |
1524 | 2 | read(unit,'(A)') line | |
1525 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
2 | if(index(line,'#').gt.0) line = line(1:index(line,'#')-1) |
1526 |
2/4✓ Branch 3 taken 2 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2 times.
✗ Branch 6 not taken.
|
2 | line = to_upper(trim(adjustl(line))) |
1527 |
2/4✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
|
2 | if(len(trim(line)).eq.0) exit |
1528 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | if(index(line,'END').gt.0) exit |
1529 | 1 | read(line(:scan(line,":")-1),*) elements(1) | |
1530 | 1 | read(line(scan(line,":")+1:),*) rtmp1 | |
1531 | 1 | call this%distributions%set_element_energy(elements(1), rtmp1) | |
1532 | end do | ||
1533 | case("BOND_INFO") | ||
1534 |
23/25✓ Branch 0 taken 22 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 1 times.
✓ Branch 3 taken 1 times.
✓ Branch 4 taken 1 times.
✓ Branch 5 taken 1 times.
✓ Branch 6 taken 1 times.
✓ Branch 7 taken 1 times.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 1 times.
✓ Branch 10 taken 1 times.
✓ Branch 11 taken 1 times.
✓ Branch 12 taken 1 times.
✓ Branch 13 taken 1 times.
✓ Branch 14 taken 1 times.
✓ Branch 15 taken 1 times.
✓ Branch 16 taken 1 times.
✓ Branch 17 taken 1 times.
✓ Branch 18 taken 1 times.
✓ Branch 19 taken 1 times.
✓ Branch 20 taken 1 times.
✓ Branch 21 taken 1 times.
✓ Branch 22 taken 1 times.
✓ Branch 23 taken 1 times.
✗ Branch 24 not taken.
|
44 | do |
1535 | 2 | read(unit,'(A)') line | |
1536 |
1/4✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
|
2 | if(index(line,'#').gt.0) line = line(1:index(line,'#')-1) |
1537 |
2/4✓ Branch 3 taken 2 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 2 times.
✗ Branch 6 not taken.
|
2 | line = to_upper(trim(adjustl(line))) |
1538 |
2/4✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
|
2 | if(len(trim(line)).eq.0) exit |
1539 |
2/2✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
|
2 | if(index(line,'END').gt.0) exit |
1540 | 1 | read(line(:scan(line,":")-1),*) elements(1), elements(2) | |
1541 | 1 | read(line(scan(line,":")+1:),*) rtmp1 | |
1542 | 1 | call this%distributions%set_bond_radius(elements, rtmp1) | |
1543 | end do | ||
1544 | end select | ||
1545 | end do | ||
1546 | |||
1547 | 1 | close(unit) | |
1548 | |||
1549 | 1 | end subroutine read_generator_settings | |
1550 | !############################################################################### | ||
1551 | |||
1552 |
123/192✓ Branch 0 taken 2 times.
✓ Branch 1 taken 5 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 4 times.
✓ Branch 5 taken 1 times.
✓ Branch 6 taken 3 times.
✓ Branch 7 taken 3 times.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 3 times.
✓ Branch 10 taken 4 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 2 times.
✓ Branch 13 taken 2 times.
✓ Branch 14 taken 2 times.
✓ Branch 15 taken 2 times.
✓ Branch 16 taken 2 times.
✓ Branch 17 taken 3 times.
✓ Branch 18 taken 1 times.
✓ Branch 19 taken 3 times.
✓ Branch 20 taken 1 times.
✓ Branch 21 taken 2 times.
✓ Branch 22 taken 1 times.
✓ Branch 23 taken 2 times.
✓ Branch 24 taken 1 times.
✓ Branch 25 taken 2 times.
✓ Branch 26 taken 1 times.
✓ Branch 27 taken 3 times.
✓ Branch 28 taken 2 times.
✓ Branch 29 taken 2 times.
✓ Branch 30 taken 2 times.
✓ Branch 31 taken 2 times.
✓ Branch 32 taken 2 times.
✓ Branch 33 taken 2 times.
✓ Branch 34 taken 2 times.
✓ Branch 35 taken 2 times.
✓ Branch 36 taken 2 times.
✓ Branch 37 taken 2 times.
✓ Branch 38 taken 2 times.
✓ Branch 39 taken 2 times.
✓ Branch 40 taken 2 times.
✓ Branch 41 taken 2 times.
✓ Branch 42 taken 2 times.
✓ Branch 43 taken 2 times.
✓ Branch 44 taken 2 times.
✓ Branch 45 taken 2 times.
✓ Branch 46 taken 2 times.
✓ Branch 47 taken 2 times.
✓ Branch 48 taken 2 times.
✓ Branch 49 taken 2 times.
✓ Branch 50 taken 2 times.
✓ Branch 51 taken 2 times.
✓ Branch 52 taken 2 times.
✓ Branch 53 taken 2 times.
✓ Branch 54 taken 2 times.
✓ Branch 55 taken 2 times.
✓ Branch 56 taken 2 times.
✓ Branch 57 taken 2 times.
✓ Branch 58 taken 3 times.
✓ Branch 59 taken 1 times.
✓ Branch 60 taken 3 times.
✓ Branch 61 taken 1 times.
✓ Branch 62 taken 3 times.
✗ Branch 63 not taken.
✓ Branch 64 taken 3 times.
✗ Branch 65 not taken.
✓ Branch 66 taken 3 times.
✗ Branch 67 not taken.
✓ Branch 68 taken 3 times.
✓ Branch 69 taken 1 times.
✓ Branch 70 taken 2 times.
✓ Branch 71 taken 2 times.
✓ Branch 72 taken 2 times.
✓ Branch 73 taken 2 times.
✓ Branch 74 taken 2 times.
✗ Branch 75 not taken.
✓ Branch 76 taken 2 times.
✗ Branch 77 not taken.
✓ Branch 78 taken 2 times.
✗ Branch 79 not taken.
✓ Branch 80 taken 2 times.
✗ Branch 81 not taken.
✓ Branch 82 taken 2 times.
✗ Branch 83 not taken.
✓ Branch 84 taken 2 times.
✗ Branch 85 not taken.
✓ Branch 86 taken 2 times.
✗ Branch 87 not taken.
✓ Branch 88 taken 2 times.
✗ Branch 89 not taken.
✓ Branch 90 taken 2 times.
✗ Branch 91 not taken.
✓ Branch 92 taken 2 times.
✗ Branch 93 not taken.
✓ Branch 94 taken 2 times.
✓ Branch 95 taken 2 times.
✓ Branch 96 taken 2 times.
✓ Branch 97 taken 2 times.
✓ Branch 98 taken 2 times.
✓ Branch 99 taken 2 times.
✓ Branch 100 taken 2 times.
✗ Branch 101 not taken.
✓ Branch 102 taken 2 times.
✗ Branch 103 not taken.
✓ Branch 104 taken 2 times.
✗ Branch 105 not taken.
✓ Branch 106 taken 2 times.
✗ Branch 107 not taken.
✓ Branch 108 taken 2 times.
✗ Branch 109 not taken.
✓ Branch 110 taken 2 times.
✗ Branch 111 not taken.
✓ Branch 112 taken 2 times.
✗ Branch 113 not taken.
✓ Branch 114 taken 2 times.
✗ Branch 115 not taken.
✓ Branch 116 taken 2 times.
✗ Branch 117 not taken.
✓ Branch 118 taken 1 times.
✓ Branch 119 taken 1 times.
✓ Branch 120 taken 1 times.
✓ Branch 121 taken 1 times.
✓ Branch 122 taken 1 times.
✗ Branch 123 not taken.
✓ Branch 124 taken 1 times.
✗ Branch 125 not taken.
✓ Branch 126 taken 1 times.
✗ Branch 127 not taken.
✓ Branch 128 taken 1 times.
✓ Branch 129 taken 1 times.
✓ Branch 130 taken 2 times.
✗ Branch 131 not taken.
✓ Branch 132 taken 1 times.
✓ Branch 133 taken 1 times.
✓ Branch 134 taken 2 times.
✗ Branch 135 not taken.
✓ Branch 136 taken 2 times.
✗ Branch 137 not taken.
✓ Branch 138 taken 2 times.
✗ Branch 139 not taken.
✗ Branch 140 not taken.
✓ Branch 141 taken 2 times.
✗ Branch 142 not taken.
✗ Branch 143 not taken.
✗ Branch 144 not taken.
✗ Branch 145 not taken.
✗ Branch 146 not taken.
✗ Branch 147 not taken.
✗ Branch 148 not taken.
✗ Branch 149 not taken.
✗ Branch 150 not taken.
✗ Branch 151 not taken.
✗ Branch 152 not taken.
✗ Branch 153 not taken.
✗ Branch 154 not taken.
✗ Branch 155 not taken.
✗ Branch 156 not taken.
✗ Branch 157 not taken.
✗ Branch 158 not taken.
✗ Branch 159 not taken.
✗ Branch 160 not taken.
✗ Branch 161 not taken.
✓ Branch 162 taken 2 times.
✗ Branch 163 not taken.
✓ Branch 164 taken 2 times.
✗ Branch 165 not taken.
✓ Branch 166 taken 2 times.
✗ Branch 167 not taken.
✓ Branch 168 taken 2 times.
✗ Branch 169 not taken.
✓ Branch 170 taken 2 times.
✗ Branch 171 not taken.
✓ Branch 172 taken 2 times.
✗ Branch 173 not taken.
✓ Branch 174 taken 1 times.
✓ Branch 175 taken 1 times.
✓ Branch 176 taken 1 times.
✓ Branch 177 taken 1 times.
✗ Branch 178 not taken.
✓ Branch 179 taken 1 times.
✗ Branch 180 not taken.
✗ Branch 181 not taken.
✗ Branch 182 not taken.
✗ Branch 183 not taken.
✗ Branch 184 not taken.
✗ Branch 185 not taken.
✗ Branch 186 not taken.
✗ Branch 187 not taken.
✗ Branch 188 not taken.
✗ Branch 189 not taken.
✓ Branch 190 taken 1 times.
✓ Branch 191 taken 1 times.
|
35 | end module raffle__generator |
1553 |