GCC Code Coverage Report


Directory: src/fortran/lib/
File: mod_generator.f90
Date: 2025-04-05 12:17:58
Exec Total Coverage
Lines: 314 373 84.2%
Functions: 0 0 -%
Branches: 651 1175 55.4%

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_linalg, only: modu
12 use raffle__misc, only: strip_null, set, shuffle, sort1D, to_upper
13 use raffle__geom_rw, only: basis_type
14 use raffle__geom_extd, only: extended_basis_type
15 use raffle__distribs_container, only: distribs_container_type
16 use raffle__geom_utils, only: basis_merge
17 use raffle__place_methods, only: &
18 place_method_void, place_method_rand, &
19 place_method_growth, place_method_walk, &
20 place_method_min
21 use raffle__viability, only: &
22 get_gridpoints_and_viability, update_gridpoints_and_viability
23
24 implicit none
25
26
27 private
28 public :: raffle_generator_type, stoichiometry_type
29
30
31 type :: stoichiometry_type
32 !! Type for storing the stoichiometry of atoms to be placed in the host
33 !! structure.
34 character(len=3) :: element
35 !! Element symbol.
36 integer :: num
37 !! Number of atoms.
38 end type stoichiometry_type
39
40
41 type :: raffle_generator_type
42 !! Type for instance of raffle generator.
43 !!
44 !! This type contains the parameters and methods for generating random
45 !! structures from a host structure, using the RAFFLE method.
46 integer :: num_structures = 0
47 !! Number of structures generated. Initialised to zero.
48 type(basis_type) :: host
49 !! Host structure.
50 integer, dimension(3) :: grid = [0, 0, 0]
51 !! Grid to divide the host structure into along each axis.
52 real(real32), dimension(3) :: &
53 grid_offset = [0.5_real32, 0.5_real32, 0.5_real32]
54 !! Offset of the gridpoints.
55 real(real32) :: grid_spacing = 0.1_real32
56 !! Spacing of the gridpoints.
57 real(real32), dimension(2,3) :: bounds = reshape( &
58 (/ &
59 0.0_real32, 1.0_real32, &
60 0.0_real32, 1.0_real32, &
61 0.0_real32, 1.0_real32 &
62 /), [2,3] &
63 )
64 !! Bounds for atom placement.
65 type(distribs_container_type) :: distributions
66 !! Distribution function container for the 2-, 3-, and 4-body interactions.
67 integer :: max_attempts = 10000
68 !! Limit for the number of attempts to place an atom.
69 real(real32) :: &
70 walk_step_size_coarse = 1._real32, &
71 walk_step_size_fine = 0.1_real32
72 !! Step size for the walk and grow methods.
73 real(real32), dimension(5) :: method_ratio
74 !! Ratio of each placement method.
75 type(basis_type), dimension(:), allocatable :: structures
76 !! Generated structures.
77 contains
78 procedure, pass(this) :: set_host
79 !! Procedure to set the host structure.
80 procedure, pass(this) :: set_grid
81 !! Procedure to set the grid for the raffle generator.
82 procedure, pass(this) :: reset_grid
83 !! Procedure to reset the grid for the raffle generator.
84 procedure, pass(this) :: set_bounds
85 !! Procedure to set the bounds for the raffle generator.
86 procedure, pass(this) :: reset_bounds
87 !! Procedure to reset the bounds for the raffle generator.
88 procedure, pass(this) :: generate
89 !! Procedure to generate random structures.
90 procedure, pass(this), private :: generate_structure
91 !! Procedure to generate a single random structure.
92 procedure, pass(this) :: get_structures
93 !! Procedure to return the generated structures.
94 procedure, pass(this) :: set_structures
95 !! Procedure to set the array of generated structures.
96 procedure, pass(this) :: remove_structure
97 !! Procedure to remove a structure from the array of generated structures.
98 procedure, pass(this) :: evaluate
99 !! Procedure to evaluate the viability of a structure.
100
101 procedure, pass(this) :: print_settings => print_generator_settings
102 !! Procedure to print the raffle generator settings.
103 procedure, pass(this) :: read_settings => read_generator_settings
104 !! Procedure to read the raffle generator settings.
105 end type raffle_generator_type
106
107 interface raffle_generator_type
108 !! Constructor for the raffle generator type.
109 module function init_raffle_generator( &
110 host, &
111 width, sigma, cutoff_min, cutoff_max) result(generator)
112 type(basis_type), intent(in), optional :: host
113 real(real32), dimension(3), intent(in), optional :: width
114 real(real32), dimension(3), intent(in), optional :: sigma
115 real(real32), dimension(3), intent(in), optional :: cutoff_min
116 real(real32), dimension(3), intent(in), optional :: cutoff_max
117 type(raffle_generator_type) :: generator
118 end function init_raffle_generator
119 end interface raffle_generator_type
120
121
122 contains
123
124 !###############################################################################
125 2 module function init_raffle_generator( &
126 host, width, sigma, cutoff_min, cutoff_max &
127 ) result(generator)
128 !! Initialise an instance of the raffle generator.
129 !!
130 !! Set up run-independent parameters.
131 implicit none
132
133 ! Arguments
134 type(basis_type), intent(in), optional :: host
135 !! Basis of the host structure.
136 real(real32), dimension(3), intent(in), optional :: width
137 !! Width of the gaussians used in the 2-, 3-, and 4-body
138 !! distribution functions.
139 real(real32), dimension(3), intent(in), optional :: sigma
140 !! Width of the gaussians used in the 2-, 3-, and 4-body
141 !! distribution functions.
142 real(real32), dimension(3), intent(in), optional :: cutoff_min
143 !! Minimum cutoff for the 2-, 3-, and 4-body distribution functions.
144 real(real32), dimension(3), intent(in), optional :: cutoff_max
145 !! Maximum cutoff for the 2-, 3-, and 4-body distribution functions.
146
147 ! Local variables
148 type(raffle_generator_type) :: generator
149 !! Instance of the raffle generator.
150
151 ! Handle optional arguments
152 ! Set up the host structure
153 1 if(present(host)) call generator%set_host(host)
154
155 ! Set up the distribution function parameters
156
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 if( present(width) ) &
157 1 call generator%distributions%set_width(width)
158
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 if( present(sigma) ) &
159 1 call generator%distributions%set_sigma(sigma)
160
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 if( present(cutoff_min) ) &
161 1 call generator%distributions%set_cutoff_min(cutoff_min)
162
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 if( present(cutoff_max) ) &
163 1 call generator%distributions%set_cutoff_max(cutoff_max)
164
165
34/34
✓ 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 1 times.
✓ Branch 33 taken 1 times.
132 end function init_raffle_generator
166 !###############################################################################
167
168
169 !###############################################################################
170 5 subroutine set_host(this, host)
171 !! Set the host structure.
172 !!
173 !! This procedure sets the host structure for the raffle generator.
174 implicit none
175
176 ! Arguments
177 class(raffle_generator_type), intent(inout) :: this
178 !! Instance of the raffle generator.
179 class(basis_type), intent(in) :: host
180 !! Basis of the host structure.
181
182 ! Local variables
183 integer :: i
184 !! Loop index.
185
186
187 5 call this%host%copy(host)
188 5 call this%distributions%host_system%set(this%host)
189
190 5 call this%set_grid()
191 5 end subroutine set_host
192 !###############################################################################
193
194
195 !###############################################################################
196 15 subroutine set_grid(this, grid, grid_spacing, grid_offset)
197 !! Set the grid for the raffle generator.
198 !!
199 !! This procedure sets the grid for the raffle generator. The grid is used
200 !! to divide the host structure into bins along each axis on which
201 !! atom placement viability will be evaluated
202 implicit none
203
204 ! Arguments
205 class(raffle_generator_type), intent(inout) :: this
206 !! Instance of the raffle generator.
207 integer, dimension(3), intent(in), optional :: grid
208 !! Number of bins to divide the host structure into along each axis.
209 real(real32), intent(in), optional :: grid_spacing
210 !! Spacing of the bins.
211 real(real32), dimension(3), intent(in), optional :: grid_offset
212 !! Offset of the gridpoints.
213
214 ! Local variables
215 integer :: i
216 !! Loop index.
217
218
219
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 14 times.
15 if(present(grid).and.present(grid_spacing)) then
220 1 call this%reset_grid()
221 1 call stop_program("Cannot set grid and grid spacing simultaneously")
222 1 return
223
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 8 times.
14 elseif(present(grid_spacing)) then
224 6 this%grid_spacing = grid_spacing
225
2/2
✓ Branch 0 taken 18 times.
✓ Branch 1 taken 6 times.
24 this%grid = 0
226
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 7 times.
8 elseif(present(grid)) then
227
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 this%grid = grid
228 end if
229
230
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
231
232
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
233
1/2
✓ Branch 0 taken 12 times.
✗ Branch 1 not taken.
12 if(allocated(this%host%spec))then
234
2/2
✓ Branch 0 taken 36 times.
✓ Branch 1 taken 12 times.
48 do i = 1, 3
235 this%grid(i) = nint( &
236 ( this%bounds(2,i) - this%bounds(1,i) ) * &
237 modu(this%host%lat(i,:)) / this%grid_spacing &
238 48 )
239 end do
240 end if
241 end if
242
243 end subroutine set_grid
244 !###############################################################################
245
246
247 !###############################################################################
248 4 subroutine reset_grid(this)
249 !! Reset the grid for the raffle generator.
250 implicit none
251
252 ! Arguments
253 class(raffle_generator_type), intent(inout) :: this
254 !! Instance of the raffle generator.
255
256
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 4 times.
16 this%grid = 0
257 4 end subroutine reset_grid
258 !###############################################################################
259
260
261 !###############################################################################
262 2 subroutine set_bounds(this, bounds)
263 !! Set the bounds for the raffle generator.
264 !!
265 !! This procedure sets the bounds for the raffle generator. The bounds are
266 !! used to determine the placement of atoms in the host structure.
267 implicit none
268
269 ! Arguments
270 class(raffle_generator_type), intent(inout) :: this
271 !! Instance of the raffle generator.
272 real(real32), dimension(2,3), intent(in) :: bounds
273 !! Bounds for atom placement.
274
275
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
276 2 call this%set_grid()
277
278 2 end subroutine set_bounds
279 !###############################################################################
280
281
282 !###############################################################################
283 2 subroutine reset_bounds(this)
284 !! Reset the grid for the raffle generator.
285 implicit none
286
287 ! Arguments
288 class(raffle_generator_type), intent(inout) :: this
289 !! Instance of the raffle generator.
290
291
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
8 this%bounds(1,:) = 0.0_real32
292
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
8 this%bounds(2,:) = 1.0_real32
293 2 end subroutine reset_bounds
294 !###############################################################################
295
296
297
298 !###############################################################################
299 4 subroutine generate(this, num_structures, &
300 4 stoichiometry, method_ratio, seed, settings_out_file, &
301 verbose, exit_code &
302 )
303 !! Generate random structures.
304 !!
305 !! This procedure generates random structures from the contained host
306 !! structure and the stoichiometry argument. The number of structures to
307 !! generate is specified by the num_structures argument.
308 !! The ratio of placement methods to be sampled is defined by method_ratio.
309 implicit none
310
311 ! Arguments
312 class(raffle_generator_type), intent(inout) :: this
313 !! Instance of the raffle generator.
314 integer, intent(in) :: num_structures
315 !! Number of structures to generate.
316 type(stoichiometry_type), dimension(:), intent(in) :: stoichiometry
317 !! Stoichiometry of the structures to generate.
318 real(real32), dimension(5), intent(in), optional :: method_ratio
319 !! Ratio of each placement method.
320 integer, intent(in), optional :: seed
321 !! Seed for the random number generator.
322 character(*), intent(in), optional :: settings_out_file
323 !! File to print the settings to.
324 integer, intent(in), optional :: verbose
325 !! Verbosity level.
326 integer, intent(out), optional :: exit_code
327 !! Exit code.
328
329 ! Local variables
330 integer :: i, j, k, istructure, num_structures_old, num_structures_new
331 !! Loop counters.
332 integer :: exit_code_
333 !! Exit code.
334 integer :: num_seed
335 !! Number of seeds for the random number generator.
336 integer :: num_insert_atoms, num_insert_species
337 !! Number of atoms and species to insert (from stoichiometry).
338 real(real32) :: ratio_norm
339 !! Normalisation factor for the method ratios.
340 logical :: success
341 !! Boolean comparison of element symbols.
342 integer :: verbose_
343 !! Verbosity level.
344 logical :: suppress_warnings_store
345 !! Boolean to store the suppress_warnings value.
346
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
347 !! Basis of the structure to generate (i.e. allocated species and atoms).
348 real(real32), dimension(5) :: &
349 method_rand_limit = &
350 [1.0_real32, 0.1_real32, 0.5_real32, 0.5_real32, 1.0_real32]
351 !! Default ratio of each placement method.
352
353 4 integer, dimension(:), allocatable :: seed_arr
354 !! Array of seeds for the random number generator.
355 4 type(basis_type), dimension(:), allocatable :: tmp_structures
356 !! Temporary array of structures (for memory reallocation).
357
358 4 integer, dimension(:,:), allocatable :: placement_list
359 !! List of possible atoms to place in the structure.
360
361
362 !---------------------------------------------------------------------------
363 ! Set the verbosity level
364 !---------------------------------------------------------------------------
365 4 exit_code_ = 0
366 4 verbose_ = 0
367
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 if(present(verbose)) verbose_ = verbose
368
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 if(verbose_ .eq. 0)then
369 1 suppress_warnings_store = suppress_warnings
370 1 suppress_warnings = .true.
371 end if
372
373
374 !---------------------------------------------------------------------------
375 ! Set the placement method selection limit numbers
376 !---------------------------------------------------------------------------
377
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 if(verbose_.gt.0) write(*,*) "Setting method ratios"
378
1/2
✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
4 if(present(method_ratio))then
379 4 method_rand_limit = method_ratio
380 else
381 method_rand_limit = this%method_ratio
382 end if
383
2/2
✓ Branch 0 taken 20 times.
✓ Branch 1 taken 4 times.
24 this%method_ratio = method_rand_limit
384
2/2
✓ Branch 0 taken 20 times.
✓ Branch 1 taken 4 times.
24 ratio_norm = real(sum(method_rand_limit), real32)
385
2/2
✓ Branch 0 taken 20 times.
✓ Branch 1 taken 4 times.
24 method_rand_limit = method_rand_limit / ratio_norm
386
2/2
✓ Branch 0 taken 16 times.
✓ Branch 1 taken 4 times.
20 do i = 2, 5, 1
387 20 method_rand_limit(i) = method_rand_limit(i) + method_rand_limit(i-1)
388 end do
389
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 if(verbose_.gt.0) write(*,*) &
390 3 "Method random limits (void, rand, walk, grow, min): ", &
391 6 method_rand_limit
392
393
394 !---------------------------------------------------------------------------
395 ! Print the settings to a file
396 !---------------------------------------------------------------------------
397
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
4 if(present(settings_out_file))then
398 if(trim(settings_out_file).ne."")then
399 call this%print_settings(settings_out_file)
400 end if
401 end if
402
403 !---------------------------------------------------------------------------
404 ! Set the random seed
405 !---------------------------------------------------------------------------
406
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 if(present(seed))then
407 3 call random_seed(size=num_seed)
408
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(seed_arr(num_seed))
409
2/2
✓ Branch 0 taken 24 times.
✓ Branch 1 taken 3 times.
27 seed_arr = seed
410 3 call random_seed(put=seed_arr)
411 else
412 1 call random_seed(size=num_seed)
413
7/14
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 1 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 1 times.
1 allocate(seed_arr(num_seed))
414 1 call random_seed(get=seed_arr)
415 end if
416
417
418 !---------------------------------------------------------------------------
419 ! allocate memory for structures
420 !---------------------------------------------------------------------------
421
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 if(verbose_.gt.0) write(*,*) "Allocating memory for structures"
422
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 2 times.
4 if(.not.allocated(this%structures))then
423
19/30
✓ 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.
33 allocate(this%structures(num_structures))
424 else
425
17/30
✓ 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.
36 allocate(tmp_structures(this%num_structures + num_structures))
426 tmp_structures(:this%num_structures) = &
427
9/20
✓ 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 not taken.
✓ Branch 13 taken 1 times.
✗ Branch 14 not taken.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✗ Branch 17 not taken.
✗ Branch 18 not taken.
✗ Branch 19 not taken.
4 this%structures(:this%num_structures)
428
9/14
✓ 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 2 times.
✗ Branch 13 not taken.
6 call move_alloc(tmp_structures, this%structures)
429 end if
430
431
432 !---------------------------------------------------------------------------
433 ! set up the template basis for generated structures
434 !---------------------------------------------------------------------------
435
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 if(verbose_.gt.0) write(*,*) "Setting up basis store"
436 4 num_insert_species = size(stoichiometry)
437
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
8 num_insert_atoms = sum(stoichiometry(:)%num)
438
11/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 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.
8 allocate(basis_template%spec(num_insert_species))
439
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
8 do i = 1, size(stoichiometry)
440 8 basis_template%spec(i)%name = strip_null(stoichiometry(i)%element)
441 end do
442
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
8 basis_template%spec(:)%num = stoichiometry(:)%num
443 4 basis_template%natom = num_insert_atoms
444 4 basis_template%nspec = num_insert_species
445 4 basis_template%sysname = "inserts"
446
447
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
8 do i = 1, basis_template%nspec
448 allocate( &
449 basis_template%spec(i)%atom(basis_template%spec(i)%num,3), &
450 source = 0._real32 &
451
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 )
452 end do
453
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 3 times.
4 if(.not.allocated(this%host%spec))then
454 1 call stop_program("Host structure not set")
455 1 return
456 end if
457
5/8
✓ 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.
9 basis_template = basis_merge(this%host,basis_template)
458
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
459
460
461 !---------------------------------------------------------------------------
462 ! ensure host element map is set
463 !---------------------------------------------------------------------------
464 call this%distributions%set_element_map( &
465 [ basis_template%spec(:)%name ] &
466
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 )
467 call this%distributions%host_system%set_element_map( &
468 this%distributions%element_info &
469 3 )
470
471
472 !---------------------------------------------------------------------------
473 ! generate the placement list
474 ! placement list is the list of number of atoms of each species that can be
475 ! placed in the structure
476 ! ... the second dimension is the index of the species and atom in the
477 ! ... basis_template
478 !---------------------------------------------------------------------------
479
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 if(verbose_.gt.0) write(*,*) "Generating placement list"
480
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))
481 3 k = 0
482
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 3 times.
6 spec_loop1: do i = 1, basis_template%nspec
483 3 success = .false.
484
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 3 times.
6 do j = 1, size(stoichiometry)
485
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( &
486 trim(basis_template%spec(i)%name) .eq. &
487 trim(strip_null(stoichiometry(j)%element)) &
488 9 ) success = .true.
489 end do
490
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
3 if(.not.success) cycle
491
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
6 if(i.gt.this%host%nspec)then
492 do j = 1, basis_template%spec(i)%num
493 k = k + 1
494 placement_list(1,k) = i
495 placement_list(2,k) = j
496 end do
497 else
498
2/2
✓ Branch 0 taken 52 times.
✓ Branch 1 taken 3 times.
55 do j = 1, basis_template%spec(i)%num
499
2/2
✓ Branch 0 taken 24 times.
✓ Branch 1 taken 28 times.
52 if(j.le.this%host%spec(i)%num) cycle
500 28 k = k + 1
501 28 placement_list(1,k) = i
502 31 placement_list(2,k) = j
503 end do
504 end if
505 end do spec_loop1
506
507
508 !---------------------------------------------------------------------------
509 ! generate the structures
510 !---------------------------------------------------------------------------
511
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 if(verbose_.gt.0) write(*,*) "Entering structure generation loop"
512 3 num_structures_old = this%num_structures
513 3 num_structures_new = this%num_structures + num_structures
514
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 3 times.
6 structure_loop: do istructure = num_structures_old + 1, num_structures_new
515
516
1/2
✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
3 if(verbose_.gt.0) write(*,*) "Generating structure", istructure
517 call this%structures(istructure)%copy( basis = &
518 this%generate_structure( &
519 basis_template, &
520 placement_list, &
521 method_rand_limit, &
522 verbose_, &
523 exit_code_ &
524 ) &
525
10/16
✓ 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 taken 3 times.
✓ Branch 16 taken 3 times.
✗ Branch 17 not taken.
15 )
526 6 this%num_structures = istructure
527
528 end do structure_loop
529
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 if(verbose_ .gt. 0 .and. exit_code_ .eq. 0) &
530 1 write(*,*) "Finished generating structures"
531
532
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 if(verbose_ .eq. 0)then
533 1 suppress_warnings = suppress_warnings_store
534 end if
535
536
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
3 if(present(exit_code))then
537 exit_code = exit_code_
538
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 elseif(exit_code_ .ne. 0)then
539 1 call stop_program("Error generating structures", exit_code_)
540 end if
541
542
10/28
✓ 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 taken 4 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 3 times.
✓ Branch 19 taken 1 times.
✓ Branch 20 taken 4 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 4 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 4 times.
✓ Branch 25 taken 4 times.
✓ Branch 26 taken 4 times.
✗ Branch 27 not taken.
16 end subroutine generate
543 !###############################################################################
544
545
546 !###############################################################################
547 3 function generate_structure( &
548 this, &
549 basis_initial, &
550 3 placement_list, method_rand_limit, verbose, &
551 exit_code &
552 ) result(basis)
553 !! Generate a single random structure.
554 !!
555 !! This function generates a single random structure from a host structure
556 !! by placing atoms according to the ratio of placement methods.
557 !! The input host structure will already have all host and insert species
558 !! and atoms allocated. The placement list specifies the atoms in the
559 !! host structure to be replaced by insert atoms.
560 implicit none
561
562 ! Arguments
563 class(raffle_generator_type), intent(in) :: this
564 !! Instance of the raffle generator.
565 type(basis_type), intent(in) :: basis_initial
566 !! Initial basis to build upon.
567 integer, dimension(:,:), intent(in) :: placement_list
568 !! List of possible placements.
569 real(real32), dimension(5) :: method_rand_limit
570 !! Upper limit of the random number to call each placement method.
571 type(extended_basis_type) :: basis
572 !! Generated basis.
573 integer, intent(in) :: verbose
574 !! Verbosity level.
575 integer, intent(inout) :: exit_code
576 !! Exit code.
577
578 ! Local variables
579 integer :: iplaced, void_ticker
580 !! Loop counters.
581 integer :: num_insert_atoms
582 !! Number of atoms to insert.
583 real(real32) :: rtmp1
584 !! Random number.
585 logical :: skip_min
586 !! Boolean for skipping the minimum method.
587 logical :: viable
588 !! Boolean for viable placement.
589 logical :: placement_aborted
590 !! Boolean for aborted placement.
591 integer, dimension(size(placement_list,1),size(placement_list,2)) :: &
592 6 placement_list_shuffled
593 !! Shuffled placement list.
594 real(real32), dimension(3) :: point
595 !! Coordinate of the atom to place.
596 real(real32), dimension(5) :: method_rand_limit_, method_rand_limit_store
597 !! Temporary random limit of each placement method.
598 !! This is used to update the contribution of the global minimum method if
599 !! no viable gridpoints are found.
600 3 integer, dimension(:), allocatable :: species_index_list
601 !! List of species indices to add.
602 3 real(real32), dimension(:,:), allocatable :: gridpoint_viability
603 !! Viable gridpoints for placing atoms.
604 character(len=256) :: stop_msg, warn_msg
605 !! Error message.
606
607
608 !---------------------------------------------------------------------------
609 ! initialise the basis
610 !---------------------------------------------------------------------------
611 3 call basis%copy(basis_initial)
612 call basis%create_images( &
613 max_bondlength = this%distributions%cutoff_max(1), &
614 atom_ignore_list = placement_list &
615 3 )
616 3 num_insert_atoms = basis%natom - this%host%natom
617
618
619 !---------------------------------------------------------------------------
620 ! shuffle the placement list
621 !---------------------------------------------------------------------------
622
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
623 3 call shuffle(placement_list_shuffled,2)
624
625
626 !---------------------------------------------------------------------------
627 ! generate species index list to add
628 !---------------------------------------------------------------------------
629
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,:)
630 3 call set(species_index_list)
631
632
633 !---------------------------------------------------------------------------
634 ! check for viable gridpoints
635 !---------------------------------------------------------------------------
636 3 method_rand_limit_ = method_rand_limit
637 gridpoint_viability = get_gridpoints_and_viability( &
638 this%distributions, &
639 this%grid, &
640 this%bounds, &
641 basis, &
642 species_index_list, &
643 [ this%distributions%bond_info(:)%radius_covalent ], &
644 placement_list_shuffled, &
645 this%grid_offset &
646
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 19656 times.
✓ Branch 21 taken 3 times.
✓ Branch 22 taken 98280 times.
✓ Branch 23 taken 19656 times.
117945 )
647
648
649 !---------------------------------------------------------------------------
650 ! place the atoms according to the method ratios
651 !---------------------------------------------------------------------------
652 3 iplaced = 0
653 3 void_ticker = 0
654 3 viable = .false.
655 3 skip_min = .false.
656 3 placement_aborted = .false.
657
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 26 times.
27 placement_loop: do while (iplaced.lt.num_insert_atoms)
658 !------------------------------------------------------------------------
659 ! check if there are any viable gridpoints remaining
660 !------------------------------------------------------------------------
661
2/2
✓ Branch 0 taken 23 times.
✓ Branch 1 taken 3 times.
26 if(viable)then
662
1/2
✓ Branch 0 taken 23 times.
✗ Branch 1 not taken.
23 if(allocated(gridpoint_viability)) &
663 call update_gridpoints_and_viability( &
664 gridpoint_viability, &
665 this%distributions, &
666 basis, &
667 species_index_list, &
668 [ placement_list_shuffled(:,iplaced) ], &
669 [ this%distributions%bond_info(:)%radius_covalent ], &
670 placement_list_shuffled(:,iplaced+1:) &
671
12/16
✗ Branch 0 not taken.
✓ Branch 1 taken 23 times.
✓ Branch 3 taken 46 times.
✓ Branch 4 taken 23 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 23 times.
✓ Branch 7 taken 46 times.
✓ Branch 8 taken 23 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 23 times.
✓ Branch 12 taken 23 times.
✓ Branch 13 taken 23 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 23 times.
✓ Branch 16 taken 23 times.
✓ Branch 17 taken 23 times.
161 )
672 end if
673
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 26 times.
26 if(.not.allocated(gridpoint_viability))then
674 write(warn_msg, '("No more viable gridpoints")')
675 warn_msg = trim(warn_msg) // &
676 achar(13) // achar(10) // &
677 "Stopping atom placement for this structure"
678 call print_warning(warn_msg)
679 placement_aborted = .true.
680 exit placement_loop
681 end if
682 26 viable = .false.
683 !------------------------------------------------------------------------
684 ! Choose a placement method
685 ! call a random number and query the method ratios
686 !------------------------------------------------------------------------
687 26 call random_number(rtmp1)
688
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 26 times.
26 if(rtmp1.le.method_rand_limit_(1)) then
689 if(verbose.gt.0) write(*,*) "Add Atom Void"
690 point = place_method_void( &
691 gridpoint_viability, &
692 basis, &
693 placement_list_shuffled(:,iplaced+1:), viable &
694 )
695
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 26 times.
26 elseif(rtmp1.le.method_rand_limit_(2)) then
696 if(verbose.gt.0) write(*,*) "Add Atom Random"
697 point = place_method_rand( &
698 this%distributions, &
699 this%bounds, &
700 basis, &
701 placement_list_shuffled(:,iplaced+1:), &
702 [ this%distributions%bond_info(:)%radius_covalent ], &
703 this%max_attempts, &
704 viable &
705 )
706
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 26 times.
26 elseif(rtmp1.le.method_rand_limit_(3)) then
707 if(verbose.gt.0) write(*,*) "Add Atom Walk"
708 point = place_method_walk( &
709 this%distributions, &
710 this%bounds, &
711 basis, &
712 placement_list_shuffled(:,iplaced+1:), &
713 [ this%distributions%bond_info(:)%radius_covalent ], &
714 this%max_attempts, &
715 this%walk_step_size_coarse, this%walk_step_size_fine, &
716 viable &
717 )
718
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 26 times.
26 elseif(rtmp1.le.method_rand_limit_(4)) then
719 if(iplaced.eq.0)then
720 if(verbose.gt.0) write(*,*) "Add Atom Random (growth seed)"
721 point = place_method_rand( &
722 this%distributions, &
723 this%bounds, &
724 basis, &
725 placement_list_shuffled(:,iplaced+1:), &
726 [ this%distributions%bond_info(:)%radius_covalent ], &
727 this%max_attempts, &
728 viable &
729 )
730 else
731 if(verbose.gt.0) write(*,*) "Add Atom Growth"
732 point = place_method_growth( &
733 this%distributions, &
734 basis%spec(placement_list_shuffled(1,iplaced))%atom( &
735 placement_list_shuffled(2,iplaced),:3 &
736 ), &
737 placement_list_shuffled(1,iplaced), &
738 this%bounds, &
739 basis, &
740 placement_list_shuffled(:,iplaced+1:), &
741 [ this%distributions%bond_info(:)%radius_covalent ], &
742 this%max_attempts, &
743 this%walk_step_size_coarse, this%walk_step_size_fine, &
744 viable &
745 )
746 end if
747
1/2
✓ Branch 0 taken 26 times.
✗ Branch 1 not taken.
26 elseif(rtmp1.le.method_rand_limit_(5)) then
748
1/2
✓ Branch 0 taken 26 times.
✗ Branch 1 not taken.
26 if(verbose.gt.0) write(*,*) "Add Atom Minimum"
749 point = place_method_min( gridpoint_viability, &
750 placement_list_shuffled(1,iplaced+1), &
751 species_index_list, &
752 viable &
753 26 )
754
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 24 times.
26 if(.not. viable .and. abs(method_rand_limit_(4)).lt.1.E-6)then
755 write(warn_msg, &
756 '("Minimum method failed, no other methods available")' &
757 2 )
758 warn_msg = trim(warn_msg) // &
759 achar(13) // achar(10) // &
760
2/4
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 6 taken 2 times.
✗ Branch 7 not taken.
2 "Stopping atom placement for this structure"
761 2 call print_warning(warn_msg)
762 2 placement_aborted = .true.
763 2 exit placement_loop
764
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 24 times.
24 elseif(.not.viable)then
765 skip_min = .true.
766 method_rand_limit_store = method_rand_limit_
767 method_rand_limit_ = method_rand_limit_ / method_rand_limit_(4)
768 method_rand_limit_(5) = method_rand_limit_(4)
769 end if
770 end if
771 !------------------------------------------------------------------------
772 ! check if the placement method returned a viable point
773 ! if not, cycle the loop
774 !------------------------------------------------------------------------
775
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 24 times.
24 if(.not. viable)then
776 void_ticker = void_ticker + 1
777 if(void_ticker.gt.10.and..not.allocated(gridpoint_viability))then
778 write(warn_msg, '("No more viable gridpoints")')
779 warn_msg = trim(warn_msg) // &
780 achar(13) // achar(10) // &
781 "Stopping atom placement for this structure"
782 call print_warning(warn_msg)
783 placement_aborted = .true.
784 exit placement_loop
785 elseif(void_ticker.gt.10)then
786 point = place_method_void( &
787 gridpoint_viability, basis, &
788 placement_list_shuffled(:,iplaced+1:), viable &
789 )
790 void_ticker = 0
791 end if
792 if(.not.viable) cycle placement_loop
793 end if
794 !------------------------------------------------------------------------
795 ! place the atom and update the image atoms in the basis
796 !------------------------------------------------------------------------
797
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 24 times.
24 if(skip_min)then
798 method_rand_limit_ = method_rand_limit_store
799 skip_min = .false.
800 end if
801 24 iplaced = iplaced + 1
802 basis%spec(placement_list_shuffled(1,iplaced))%atom( &
803
2/2
✓ Branch 0 taken 72 times.
✓ Branch 1 taken 24 times.
96 placement_list_shuffled(2,iplaced),:3) = point(:3)
804 call basis%update_images( &
805 max_bondlength = this%distributions%cutoff_max(1), &
806 is = placement_list_shuffled(1,iplaced), &
807 ia = placement_list_shuffled(2,iplaced) &
808 24 )
809
1/2
✓ Branch 0 taken 24 times.
✗ Branch 1 not taken.
24 if(verbose.gt.0)then
810 24 write(*,'(A)',ADVANCE='NO') achar(13)
811 write(*,'(2X,"placed atom ",I0," [",I0,",",I0,"] at",3(1X,F6.3))') &
812 24 iplaced, placement_list_shuffled(1:2,iplaced), point(:3)
813 24 write(*,*)
814 end if
815
816 end do placement_loop
817
818
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 if(placement_aborted)then
819 call stop_program( &
820 "Placement routine aborted, not all atoms placed", &
821 block_stop = .true. &
822 2 )
823 2 exit_code = 1
824 2 call basis%remove_atoms(placement_list_shuffled(:,iplaced+1:))
825 end if
826
827
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)
828
829
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
830 !###############################################################################
831
832
833 !###############################################################################
834 3 function get_structures(this) result(structures)
835 !! Get the generated structures.
836 implicit none
837 ! Arguments
838 class(raffle_generator_type), intent(in) :: this
839 !! Instance of the raffle generator.
840 type(basis_type), dimension(:), allocatable :: structures
841 !! Generated structures.
842
843
17/52
✓ 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 taken 8 times.
✓ Branch 33 taken 3 times.
✓ Branch 34 taken 8 times.
✗ Branch 35 not taken.
✓ Branch 36 taken 8 times.
✗ Branch 37 not taken.
✓ Branch 38 taken 8 times.
✓ Branch 39 taken 8 times.
✓ Branch 40 taken 8 times.
✗ Branch 41 not taken.
✓ Branch 42 taken 8 times.
✗ Branch 43 not taken.
✗ Branch 44 not taken.
✓ Branch 45 taken 8 times.
✗ Branch 46 not taken.
✗ Branch 47 not taken.
✗ Branch 48 not taken.
✗ Branch 49 not taken.
✗ Branch 50 not taken.
✗ Branch 51 not taken.
30 structures = this%structures
844 3 end function get_structures
845 !###############################################################################
846
847
848 !###############################################################################
849 1 subroutine set_structures(this, structures)
850 !! Set the generated structures.
851 !!
852 !! This procedure overwrites the array of generated structures with the
853 !! input array.
854 !! This can be useful for removing structures that are not viable from the
855 !! array.
856 implicit none
857 ! Arguments
858 class(raffle_generator_type), intent(inout) :: this
859 !! Instance of the raffle generator.
860 type(basis_type), dimension(..), allocatable, intent(in) :: structures
861 !! Array of structures to set.
862
863 select rank(structures)
864 rank(0)
865 this%structures = [ structures ]
866 rank(1)
867
25/50
✓ 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 1 times.
✗ Branch 27 not taken.
✓ Branch 28 taken 3 times.
✓ Branch 29 taken 1 times.
✓ Branch 30 taken 3 times.
✓ Branch 31 taken 1 times.
✓ Branch 32 taken 3 times.
✗ Branch 33 not taken.
✓ Branch 34 taken 3 times.
✗ Branch 35 not taken.
✓ Branch 36 taken 3 times.
✓ Branch 37 taken 3 times.
✓ Branch 38 taken 3 times.
✗ Branch 39 not taken.
✓ Branch 40 taken 3 times.
✗ Branch 41 not taken.
✗ Branch 42 not taken.
✓ Branch 43 taken 3 times.
✗ Branch 44 not taken.
✗ Branch 45 not taken.
✗ Branch 46 not taken.
✗ Branch 47 not taken.
✗ Branch 48 not taken.
✗ Branch 49 not taken.
16 this%structures = structures
868 rank default
869 call stop_program("Invalid rank for structures")
870 end select
871 1 this%num_structures = size(this%structures)
872 1 end subroutine set_structures
873 !###############################################################################
874
875
876 !###############################################################################
877 1 subroutine remove_structure(this, index)
878 !! Remove structures from the generated structures.
879 !!
880 !! This procedure removes structures from the array of generated structures
881 !! at the specified indices.
882 implicit none
883 ! Arguments
884 class(raffle_generator_type), intent(inout) :: this
885 !! Instance of the raffle generator.
886 integer, dimension(..), intent(in) :: index
887 !! Indices of the structures to remove.
888
889 ! Local variables
890 integer :: i
891 !! Loop index.
892 1 integer, dimension(:), allocatable :: index_
893 !! Indices of the structures to keep.
894
895 select rank(index)
896 rank(0)
897
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 ]
898 rank(1)
899 index_ = index
900 rank default
901 call stop_program("Invalid rank for index")
902 end select
903
904
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
905 call stop_program("Invalid index")
906 return
907 end if
908
909 1 call sort1D(index_, reverse=.true.)
910
911
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 do i = 1, size(index_)
912 this%structures = [ &
913 this%structures(:index_(i)-1:1), &
914 this%structures(index_(i)+1:this%num_structures:1) &
915
30/56
✗ 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 1 times.
✗ Branch 23 not taken.
✗ Branch 24 not taken.
✓ Branch 25 taken 1 times.
✗ Branch 26 not taken.
✓ Branch 27 taken 1 times.
✗ Branch 28 not taken.
✗ Branch 29 not taken.
✗ Branch 30 not taken.
✗ Branch 31 not taken.
✓ Branch 32 taken 1 times.
✗ Branch 33 not taken.
✓ 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 1 times.
✗ Branch 45 not taken.
✓ Branch 46 taken 2 times.
✓ Branch 47 taken 1 times.
✓ Branch 48 taken 2 times.
✓ Branch 49 taken 1 times.
✗ Branch 50 not taken.
✓ Branch 51 taken 2 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.
19 ]
916 2 this%num_structures = this%num_structures - 1
917 end do
918
919
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 end subroutine remove_structure
920 !###############################################################################
921
922
923 !###############################################################################
924 subroutine allocate_structures(this, num_structures)
925 !! Allocate memory for the generated structures.
926 implicit none
927 ! Arguments
928 class(raffle_generator_type), intent(inout) :: this
929 !! Instance of the raffle generator.
930 integer, intent(in) :: num_structures
931 !! Number of structures to allocate memory for.
932
933 if(allocated(this%structures)) deallocate(this%structures)
934 allocate(this%structures(num_structures))
935 this%num_structures = num_structures
936 end subroutine allocate_structures
937 !###############################################################################
938
939
940 !###############################################################################
941 1 function evaluate(this, basis) result(viability)
942 !! Evaluate the viability of the generated structures.
943 use raffle__evaluator, only: evaluate_point
944 implicit none
945 ! Arguments
946 class(raffle_generator_type), intent(inout) :: this
947 !! Instance of the raffle generator.
948 type(basis_type), intent(in) :: basis
949 !! Basis of the structure to evaluate.
950 real(real32) :: viability
951 !! Viability of the generated structures.
952
953 ! Local variables
954 integer :: is, ia, species
955 !! Loop indices.
956 integer, dimension(2,1) :: atom_ignore
957 !! Atom to ignore.
958
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
959 !! Extended basis for the structure to evaluate.
960
961
962 1 call basis_extd%copy(basis)
963 call basis_extd%create_images( &
964 max_bondlength = this%distributions%cutoff_max(1) &
965 1 )
966 1 viability = 0.0_real32
967 call this%distributions%set_element_map( &
968 [ basis_extd%spec(:)%name ] &
969
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 )
970
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 do is = 1, basis%nspec
971 species = this%distributions%get_element_index( &
972 basis_extd%spec(is)%name &
973 1 )
974
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if(species.eq.0)then
975 call stop_program( &
976 "Species "//&
977 trim(basis_extd%spec(is)%name)//&
978 " not found in distribution functions" &
979 )
980 return
981 end if
982
2/2
✓ Branch 0 taken 16 times.
✓ Branch 1 taken 1 times.
18 do ia = 1, basis%spec(is)%num
983
2/2
✓ Branch 0 taken 32 times.
✓ Branch 1 taken 16 times.
48 atom_ignore(:,1) = [is,ia]
984 viability = viability + &
985 evaluate_point( this%distributions, &
986 [ basis%spec(is)%atom(ia,1:3) ], &
987 species, basis_extd, &
988 atom_ignore, &
989 [ this%distributions%bond_info(:)%radius_covalent ] &
990
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.
145 )
991 end do
992 end do
993
994 1 viability = viability / real(basis%natom, real32)
995
10/16
✓ 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 taken 1 times.
✓ Branch 14 taken 1 times.
✗ Branch 15 not taken.
3 end function evaluate
996 !###############################################################################
997
998
999 !###############################################################################
1000 1 subroutine print_generator_settings(this, file)
1001 !! Print the raffle generator settings.
1002 implicit none
1003
1004 ! Arguments
1005 class(raffle_generator_type), intent(in) :: this
1006 !! Instance of the raffle generator.
1007 character(*), intent(in) :: file
1008 !! Filename to write the settings to.
1009
1010 ! Local variables
1011 integer :: i
1012 !! Loop index.
1013 integer :: unit
1014 !! Unit number for the file.
1015
1016 ! Open the file
1017 1 open(newunit=unit, file=file)
1018
1019 1 write(unit,'("# RAFFLE Generator Settings")')
1020 1 write(unit,'("# GENERATOR SETTINGS")')
1021 1 write(unit,'("HOST_LATTICE # not a setting, just for reference")')
1022 1 write(unit,'(" ",3(1X,F5.2))') this%host%lat(1,:)
1023 1 write(unit,'(" ",3(1X,F5.2))') this%host%lat(2,:)
1024 1 write(unit,'(" ",3(1X,F5.2))') this%host%lat(3,:)
1025 1 write(unit,'("END HOST_LATTICE")')
1026
1027 1 write(unit,'("GRID =",3(1X,I0))') this%grid
1028 1 write(unit,'("GRID_OFFSET =",3(1X,F15.9))') this%grid_offset
1029 1 write(unit,'("GRID_SPACING = ",F15.9)') this%grid_spacing
1030 1 write(unit,'("BOUNDS_LW =",3(1X,F15.9))') this%bounds(1,:)
1031 1 write(unit,'("BOUNDS_UP =",3(1X,F15.9))') this%bounds(2,:)
1032
1033 1 write(unit,'("MAX_ATTEMPTS =",I0)') this%max_attempts
1034 1 write(unit,'("WALK_STEP_SIZE_COARSE = ",F15.9)') this%walk_step_size_coarse
1035 1 write(unit,'("WALK_STEP_SIZE_FINE = ",F15.9)') this%walk_step_size_fine
1036 1 write(unit,'("METHOD_VOID = ",F15.9)') this%method_ratio(1)
1037 1 write(unit,'("METHOD_RANDOM = ",F15.9)') this%method_ratio(2)
1038 1 write(unit,'("METHOD_WALK = ",F15.9)') this%method_ratio(3)
1039 1 write(unit,'("METHOD_GROW = ",F15.9)') this%method_ratio(4)
1040 1 write(unit,'("METHOD_MIN = ",F15.9)') this%method_ratio(5)
1041
1042 1 write(unit,'("# DISTRIBUTION SETTINGS")')
1043 1 write(unit,'("KBT = ",F5.2)') this%distributions%kbt
1044 1 write(unit,'("SIGMA =",3(1X,F15.9))') this%distributions%sigma
1045 1 write(unit,'("WIDTH =",3(1X,F15.9))') this%distributions%width
1046 1 write(unit,'("CUTOFF_MIN =",3(1X,F15.9))') this%distributions%cutoff_min
1047 1 write(unit,'("CUTOFF_MAX =",3(1X,F15.9))') this%distributions%cutoff_max
1048 write(unit,'("RADIUS_DISTANCE_TOLERANCE =",4(1X,F15.9))') &
1049 1 this%distributions%radius_distance_tol
1050 1 write(unit,'("ELEMENT_INFO # element : energy")')
1051
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 do i = 1, size(this%distributions%element_info)
1052 write(unit,'(" ",A," : ",F15.9)') &
1053 1 this%distributions%element_info(i)%name, &
1054 3 this%distributions%element_info(i)%energy
1055 end do
1056 1 write(unit,'("END ELEMENT_INFO")')
1057 1 write(unit,'("BOND_INFO # element1 element2 : radius")')
1058
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 do i = 1, size(this%distributions%bond_info)
1059 write(unit,'(" ",A," ",A," : ",F15.9)') &
1060 1 this%distributions%bond_info(i)%element(1), &
1061 1 this%distributions%bond_info(i)%element(2), &
1062 3 this%distributions%bond_info(i)%radius_covalent
1063 end do
1064 1 write(unit,'("END BOND_INFO")')
1065
1066 1 close(unit)
1067
1068 1 end subroutine print_generator_settings
1069 !###############################################################################
1070
1071
1072 !###############################################################################
1073 1 subroutine read_generator_settings(this, file)
1074 !! Read the raffle generator settings.
1075 implicit none
1076
1077 ! Arguments
1078 class(raffle_generator_type), intent(inout) :: this
1079 !! Instance of the raffle generator.
1080 character(*), intent(in) :: file
1081 !! Filename to read the settings from.
1082
1083 ! Local variables
1084 integer :: i
1085 !! Loop index.
1086 integer :: itmp1, status
1087 !! Temporary integer.
1088 integer :: unit
1089 !! Unit number for the file.
1090 logical :: exist
1091 !! Boolean for file existence.
1092 character(len=256) :: line, buffer, tag
1093 !! Line from the file.
1094 character(3), dimension(2) :: elements
1095 !! Element symbols.
1096 real(real32) :: rtmp1
1097 !! Temporary real number.
1098
1099 ! Check if the file exists
1100 1 inquire(file=file, exist=exist)
1101
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if(.not.exist)then
1102 call stop_program("File does not exist")
1103 return
1104 end if
1105
1106 ! Open the file
1107 1 open(newunit=unit, file=file)
1108
1109
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if(allocated(this%distributions%element_info)) &
1110 deallocate(this%distributions%element_info)
1111
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 if(allocated(this%distributions%bond_info)) &
1112 deallocate(this%distributions%bond_info)
1113 1 itmp1 = 0
1114 25 do
1115 26 read(unit, '(A)', iostat = status) line
1116 ! encounter end of line
1117
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 25 times.
26 if(status.ne.0) exit
1118
1119
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)
1120
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)))
1121
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
1122
1123
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))
1124
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))
1125
1126 44 select case(trim(adjustl(tag)))
1127 case("HOST_LATTICE")
1128
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 1 times.
6 do i = 1, 4
1129 5 read(unit,*)
1130 end do
1131 case("GRID")
1132 1 call assign_vec(line, this%grid, itmp1)
1133 case("GRID_OFFSET")
1134 1 call assign_vec(line, this%grid_offset, itmp1)
1135 case("GRID_SPACING")
1136 1 call assign_val(line, this%grid_spacing, itmp1)
1137 case("BOUNDS_LW")
1138 1 call assign_vec(line, this%bounds(1,:), itmp1)
1139 case("BOUNDS_UP")
1140 1 call assign_vec(line, this%bounds(2,:), itmp1)
1141 case("MAX_ATTEMPTS")
1142 1 call assign_val(line, this%max_attempts, itmp1)
1143 case("WALK_STEP_SIZE_COARSE")
1144 1 call assign_val(line, this%walk_step_size_coarse, itmp1)
1145 case("WALK_STEP_SIZE_FINE")
1146 1 call assign_val(line, this%walk_step_size_fine, itmp1)
1147 case("METHOD_VOID")
1148 1 call assign_val(line, this%method_ratio(1), itmp1)
1149 case("METHOD_RANDOM")
1150 1 call assign_val(line, this%method_ratio(2), itmp1)
1151 case("METHOD_WALK")
1152 1 call assign_val(line, this%method_ratio(3), itmp1)
1153 case("METHOD_GROW")
1154 1 call assign_val(line, this%method_ratio(4), itmp1)
1155 case("METHOD_MIN")
1156 1 call assign_val(line, this%method_ratio(5), itmp1)
1157 case("KBT")
1158 1 call assign_val(line, this%distributions%kbt, itmp1)
1159 case("SIGMA")
1160 1 call assign_vec(line, this%distributions%sigma, itmp1)
1161 case("WIDTH")
1162 1 call assign_vec(line, this%distributions%width, itmp1)
1163 case("CUTOFF_MIN")
1164 1 call assign_vec(line, this%distributions%cutoff_min, itmp1)
1165 case("CUTOFF_MAX")
1166 1 call assign_vec(line, this%distributions%cutoff_max, itmp1)
1167 case("RADIUS_DISTANCE_TOLERANCE")
1168 1 call assign_vec(line, this%distributions%radius_distance_tol, itmp1)
1169 case("ELEMENT_INFO")
1170 2 do
1171 2 read(unit,'(A)') line
1172
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)
1173
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)))
1174
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
1175
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 if(index(line,'END').gt.0) exit
1176 1 read(line(:scan(line,":")-1),*) elements(1)
1177 1 read(line(scan(line,":")+1:),*) rtmp1
1178 1 call this%distributions%set_element_energy(elements(1), rtmp1)
1179 end do
1180 case("BOND_INFO")
1181
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
1182 2 read(unit,'(A)') line
1183
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)
1184
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)))
1185
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
1186
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 if(index(line,'END').gt.0) exit
1187 1 read(line(:scan(line,":")-1),*) elements(1), elements(2)
1188 1 read(line(scan(line,":")+1:),*) rtmp1
1189 1 call this%distributions%set_bond_radius(elements, rtmp1)
1190 end do
1191 end select
1192 end do
1193
1194 1 close(unit)
1195
1196 1 end subroutine read_generator_settings
1197 !###############################################################################
1198
1199
113/172
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 3 times.
✓ Branch 2 taken 2 times.
✓ Branch 3 taken 1 times.
✓ Branch 4 taken 1 times.
✓ Branch 5 taken 2 times.
✓ Branch 6 taken 3 times.
✓ Branch 7 taken 2 times.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 4 times.
✓ Branch 10 taken 2 times.
✓ Branch 11 taken 2 times.
✓ Branch 12 taken 1 times.
✓ Branch 13 taken 3 times.
✓ Branch 14 taken 1 times.
✓ Branch 15 taken 3 times.
✓ Branch 16 taken 1 times.
✓ Branch 17 taken 2 times.
✓ Branch 18 taken 1 times.
✓ Branch 19 taken 3 times.
✓ Branch 20 taken 2 times.
✓ Branch 21 taken 2 times.
✓ Branch 22 taken 2 times.
✓ Branch 23 taken 2 times.
✓ Branch 24 taken 2 times.
✓ Branch 25 taken 2 times.
✓ Branch 26 taken 2 times.
✓ Branch 27 taken 2 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 3 times.
✓ Branch 51 taken 1 times.
✓ Branch 52 taken 3 times.
✓ Branch 53 taken 1 times.
✓ Branch 54 taken 3 times.
✗ Branch 55 not taken.
✓ Branch 56 taken 3 times.
✓ Branch 57 taken 1 times.
✓ Branch 58 taken 2 times.
✓ Branch 59 taken 2 times.
✓ Branch 60 taken 2 times.
✓ Branch 61 taken 2 times.
✓ Branch 62 taken 2 times.
✗ Branch 63 not taken.
✓ Branch 64 taken 2 times.
✗ Branch 65 not taken.
✓ Branch 66 taken 2 times.
✗ Branch 67 not taken.
✓ Branch 68 taken 2 times.
✗ Branch 69 not taken.
✓ Branch 70 taken 2 times.
✗ Branch 71 not taken.
✓ Branch 72 taken 2 times.
✗ Branch 73 not taken.
✓ 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 taken 2 times.
✓ Branch 84 taken 2 times.
✓ Branch 85 taken 2 times.
✓ Branch 86 taken 2 times.
✓ Branch 87 taken 2 times.
✓ 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 not taken.
✓ Branch 96 taken 2 times.
✗ Branch 97 not taken.
✓ Branch 98 taken 2 times.
✗ Branch 99 not taken.
✓ 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 1 times.
✓ Branch 107 taken 1 times.
✓ Branch 108 taken 1 times.
✓ Branch 109 taken 1 times.
✓ Branch 110 taken 1 times.
✗ Branch 111 not taken.
✓ Branch 112 taken 1 times.
✓ Branch 113 taken 1 times.
✓ Branch 114 taken 2 times.
✗ Branch 115 not taken.
✓ Branch 116 taken 1 times.
✓ Branch 117 taken 1 times.
✓ Branch 118 taken 2 times.
✗ Branch 119 not taken.
✓ Branch 120 taken 2 times.
✗ Branch 121 not taken.
✓ Branch 122 taken 2 times.
✗ Branch 123 not taken.
✗ Branch 124 not taken.
✓ Branch 125 taken 2 times.
✗ Branch 126 not taken.
✗ Branch 127 not taken.
✗ Branch 128 not taken.
✗ Branch 129 not taken.
✗ Branch 130 not taken.
✗ Branch 131 not taken.
✗ Branch 132 not taken.
✗ Branch 133 not taken.
✗ Branch 134 not taken.
✗ Branch 135 not taken.
✗ Branch 136 not taken.
✗ Branch 137 not taken.
✗ Branch 138 not taken.
✗ Branch 139 not taken.
✗ Branch 140 not taken.
✗ Branch 141 not taken.
✗ Branch 142 not taken.
✗ Branch 143 not taken.
✗ Branch 144 not taken.
✗ Branch 145 not taken.
✓ Branch 146 taken 2 times.
✗ Branch 147 not taken.
✓ Branch 148 taken 2 times.
✗ Branch 149 not taken.
✓ Branch 150 taken 2 times.
✗ Branch 151 not taken.
✓ Branch 152 taken 2 times.
✗ Branch 153 not taken.
✓ Branch 154 taken 2 times.
✗ Branch 155 not taken.
✓ Branch 156 taken 2 times.
✗ Branch 157 not taken.
✓ Branch 158 taken 1 times.
✓ Branch 159 taken 1 times.
✓ Branch 160 taken 1 times.
✓ Branch 161 taken 1 times.
✗ Branch 162 not taken.
✓ Branch 163 taken 1 times.
✗ Branch 164 not taken.
✗ Branch 165 not taken.
✗ Branch 166 not taken.
✗ Branch 167 not taken.
✗ Branch 168 not taken.
✗ Branch 169 not taken.
✓ Branch 170 taken 1 times.
✓ Branch 171 taken 1 times.
32 end module raffle__generator
1200