GCC Code Coverage Report


Directory: src/fortran/lib/
File: mod_distribs_container.f90
Date: 2025-06-15 07:27:34
Exec Total Coverage
Lines: 734 958 76.6%
Functions: 0 0 -%
Branches: 1703 3204 53.2%

Line Branch Exec Source
1 module raffle__distribs_container
2 !! Module for handling the distribution function container.
3 !!
4 !! This module defines the distribution function container and associated
5 !! procedures.
6 !! The container holds the distribution functions for a set of atomic
7 !! structures, alongside parameters for initialising the distributions.
8 !! The container also holds the generalised distribution functions, built
9 !! from the distribution functions of the individual systems.
10 !! The generalised distribution functions are used to evaluate the viability
11 !! of a new structure.
12 use raffle__constants, only: real32, pi
13 use raffle__io_utils, only: stop_program, print_warning, suppress_warnings
14 use raffle__misc, only: set, icount, strip_null, sort_str
15 use raffle__misc_maths, only: triangular_number, set_difference
16 use raffle__geom_rw, only: basis_type, get_element_properties
17 use raffle__element_utils, only: &
18 element_type, element_bond_type, &
19 element_database, element_bond_database
20 use raffle__distribs, only: distribs_base_type, distribs_type, get_distrib
21 use raffle__distribs_host, only: distribs_host_type
22 implicit none
23
24
25 private
26
27 public :: distribs_container_type
28
29
30 type :: distribs_container_type
31 !! Container for distribution functions.
32 !!
33 !! This type contains the distribution functions for a set of atomic
34 !! structures, alongside parameters for initialising the distributions.
35 integer :: iteration = -1
36 !! Iteration number for the update of the distribution functions.
37 integer :: num_evaluated = 0
38 !! Number of evaluated systems.
39 integer :: num_evaluated_allocated = 0
40 !! Number of evaluated systems still allocated.
41 real(real32) :: kBT = 0.2_real32
42 !! Boltzmann constant times temperature.
43 integer :: history_len = 0
44 !! Length of the history for the distribution functions.
45 real(real32), dimension(:), allocatable :: history_deltas
46 !! History of the changes in the distribution functions.
47 logical :: weight_by_hull = .false.
48 !! Boolean whether to weight the distribution functions by the energy
49 !! above the hull. If false, the formation energy from the element
50 !! reference energies is used.
51 real(real32) :: &
52 viability_2body_default = 0.1_real32, &
53 viability_3body_default = 0.1_real32, &
54 viability_4body_default = 0.1_real32
55 !! Default viability for the 2-, 3-, and 4-body distribution functions.
56 logical :: smooth_viability = .true.
57 !! DEV FEATURE. Boolean whether to smooth the viability evaluation.
58 logical, dimension(:), allocatable :: &
59 in_dataset_2body, in_dataset_3body, in_dataset_4body
60 !! Whether the 2-, 3-, and 4-body distribution functions are in
61 !! the dataset.
62 real(real32), dimension(:), allocatable :: &
63 best_energy_pair, &
64 best_energy_per_species
65 !! Best energy for the 2-body and species distribution functions.
66 integer, dimension(3) :: nbins = -1
67 !! Number of bins for the 2-, 3-, and 4-body distribution functions.
68 real(real32), dimension(3) :: &
69 sigma = [ 0.1_real32, 0.1_real32, 0.1_real32 ]
70 !! Sigma of the gaussians used in the 2-, 3-, and 4-body
71 !! distribution functions.
72 real(real32), dimension(3) :: &
73 width = [ 0.025_real32, pi/64._real32, pi/64._real32 ]
74 !! Width of the bins used in the 2-, 3-, and 4-body distribution functions.
75 real(real32), dimension(3) :: width_inv
76 !! Inverse of the width of the bins used in the 2-, 3-, and 4-body
77 real(real32), dimension(3) :: &
78 cutoff_min = [ 0.5_real32, 0._real32, 0._real32 ]
79 !! Minimum cutoff for the 2-, 3-, and 4-body distribution functions.
80 real(real32), dimension(3) :: &
81 cutoff_max = [ 6._real32, pi, pi ]
82 !! Maximum cutoff for the 2-, 3-, and 4-body distribution functions.
83 real(real32), dimension(4) :: &
84 radius_distance_tol = [ 1.5_real32, 2.5_real32, 3._real32, 6._real32 ]
85 !! Tolerance for the distance between atoms for 3- and 4-body.
86 !! index 1 = lower bound for 3-body
87 !! index 2 = upper bound for 3-body
88 !! index 3 = lower bound for 4-body
89 !! index 4 = upper bound for 4-body
90 real(real32), dimension(:), allocatable :: &
91 norm_2body, norm_3body, norm_4body
92 !! Normalisation factors for the 2-, 3-, and 4-body distribution functions.
93 type(distribs_base_type) :: gdf
94 !! Generalised distribution functions for all systems.
95 !! Generated from combining the energy-weighted distribution functions
96 !! of all systems
97 integer, dimension(:), allocatable :: element_map
98 !! Mapping of host elements to distribution function elements.
99 type(distribs_host_type) :: host_system
100 !! Host structure for the distribution functions.
101 type(distribs_type), dimension(:), allocatable :: system
102 !! Distribution functions for each system.
103 type(element_type), dimension(:), allocatable :: element_info
104 !! Information about the elements in the container.
105 type(element_bond_type), dimension(:), allocatable :: bond_info
106 !! Information about the 2-body bonds in the container.
107 contains
108 procedure, pass(this) :: set_width
109 !! Set the width of the bins used in the 2-, 3-, and 4-body.
110 procedure, pass(this) :: set_sigma
111 !! Set the sigma of the gaussians used in the 2-, 3-, and 4-body.
112 procedure, pass(this) :: set_cutoff_min
113 !! Set the minimum cutoff for the 2-, 3-, and 4-body.
114 procedure, pass(this) :: set_cutoff_max
115 !! Set the maximum cutoff for the 2-, 3-, and 4-body.
116 procedure, pass(this) :: set_radius_distance_tol
117 !! Set the tolerance for the distance between atoms for 3- and 4-body.
118 procedure, pass(this) :: set_history_len
119 !! Set the length of the history for the distribution functions.
120
121 procedure, pass(this) :: create
122 !! Create the distribution functions for all systems, and the learned one.
123 procedure, pass(this) :: update
124 !! Update the distribution functions for all systems, and the learned one.
125
126 procedure, pass(this) :: deallocate_systems
127 !! Deallocate the systems in the container.
128
129 procedure, pass(this) :: add, add_basis
130 !! Add a system to the container.
131
132 procedure, pass(this), private :: set_element_info
133 !! Set the list of elements for the container.
134 procedure, pass(this), private :: update_element_info
135 !! Update the element information in the container.
136 procedure, pass(this) :: add_to_element_info
137 !! Add an element to the container.
138 procedure, pass(this) :: set_element_energy
139 !! Set the energy of an element in the container.
140 procedure, pass(this) :: set_element_energies
141 !! Set the energies of elements in the container.
142 procedure, pass(this) :: get_element_energies
143 !! Return the energies of elements in the container.
144 procedure, pass(this) :: get_element_energies_staticmem
145 !! Return the energies of elements in the container.
146 !! Used in Python interface.
147
148 procedure, pass(this) :: set_element_map
149 !! Set the mapping of elements to distribution function elements.
150 procedure, pass(this), private :: set_bond_info
151 !! Set the 2-body bond information for the container.
152 procedure, pass(this), private :: update_bond_info
153 !! Update the bond information in the container.
154 procedure, pass(this) :: set_bond_radius
155 !! Set the radius of a bond in the container.
156 procedure, pass(this) :: set_bond_radii
157 !! Set the radii of multiple bonds in the container.
158 procedure, pass(this) :: get_bond_radii
159 !! Return the radii of all bonds in the container.
160 procedure, pass(this) :: get_bond_radii_staticmem
161 !! Return the radii of all bonds in the container.
162 !! Used in Python interface.
163
164 procedure, pass(this) :: set_best_energy
165 !! Set the best energy and system in the container.
166 procedure, pass(this) :: initialise_gdfs
167 !! Initialise the distribution functions in the container.
168 procedure, pass(this) :: set_gdfs_to_default
169 !! Set the generalised distribution function to the default value.
170 procedure, pass(this) :: evolve
171 !! Evolve the learned distribution function.
172 procedure, pass(this) :: is_converged
173 !! Check if the learned distribution function has converged.
174
175 procedure, pass(this) :: write_gdfs
176 !! Write the generalised distribution functions to a file.
177 procedure, pass(this) :: read_gdfs
178 !! Read the generalised distribution functions from a file.
179 procedure, pass(this) :: write_dfs
180 !! Write all distribution functions to a file.
181 procedure, pass(this) :: read_dfs
182 !! Read all distribution functions from a file.
183 procedure, pass(this) :: write_2body
184 !! Write the learned 2-body distribution function to a file.
185 procedure, pass(this) :: write_3body
186 !! Write the learned 3-body distribution function to a file.
187 procedure, pass(this) :: write_4body
188 !! Write the learned 4-body distribution function to a file.
189 procedure, pass(this) :: get_pair_index
190 !! Return the index for bond_info given two elements.
191 procedure, pass(this) :: get_element_index
192 !! Return the index for element_info given one element.
193 procedure, pass(this) :: set_num_bins
194 !! Set the number of bins for the n-body distribution functions.
195 procedure, pass(this) :: get_bin
196 !! Return the bin index for a given distance.
197 procedure, pass(this) :: get_2body
198 !! Return the 2-body distribution function.
199 procedure, pass(this) :: get_3body
200 !! Return the 3-body distribution function.
201 procedure, pass(this) :: get_4body
202 !! Return the 4-body distribution function.
203
204 procedure, pass(this) :: generate_fingerprint
205 !! Calculate the distribution functions for a given system.
206 procedure, pass(this) :: generate_fingerprint_python
207 !! Calculate the distribution functions for a given system.
208 end type distribs_container_type
209
210 interface distribs_container_type
211 !! Interface for the distribution functions container.
212 module function init_distribs_container( &
213 nbins, width, sigma, cutoff_min, cutoff_max, &
214 history_len &
215 ) result(distribs_container)
216 !! Initialise the distribution functions container.
217 integer, dimension(3), intent(in), optional :: nbins
218 !! Optional. Number of bins for the 2-, 3-, and 4-body distribution
219 !! functions.
220 real(real32), dimension(3), intent(in), optional :: width, sigma
221 !! Optional. Width and sigma of the gaussians used in the 2-, 3-, and
222 !! 4-body.
223 real(real32), dimension(3), intent(in), optional :: &
224 cutoff_min, cutoff_max
225 !! Optional. Minimum and maximum cutoff for the 2-, 3-, and 4-body.
226 integer, intent(in), optional :: history_len
227 !! Optional. Length of the history for the distribution functions.
228 type(distribs_container_type) :: distribs_container
229 !! Instance of the distribution functions container.
230 end function init_distribs_container
231 end interface distribs_container_type
232
233
234 contains
235
236 !###############################################################################
237 3 module function init_distribs_container( &
238 nbins, width, sigma, &
239 cutoff_min, cutoff_max, &
240 history_len &
241 ) result(distribs_container)
242 !! Initialise the distribution functions container.
243 implicit none
244
245 ! Arguments
246 integer, dimension(3), intent(in), optional :: nbins
247 !! Optional. Number of bins for the 2-, 3-, and 4-body distribution
248 !! functions.
249 real(real32), dimension(3), intent(in), optional :: width, sigma
250 !! Optional. Width and sigma of the gaussians used in the 2-, 3-, and
251 !! 4-body.
252 real(real32), dimension(3), intent(in), optional :: cutoff_min, cutoff_max
253 !! Optional. Minimum and maximum cutoff for the 2-, 3-, and 4-body.
254 integer, intent(in), optional :: history_len
255 !! Optional. Length of the history for the distribution functions.
256 type(distribs_container_type) :: distribs_container
257 !! Instance of the distribution functions container.
258
259 ! Local variables
260 character(256) :: stop_msg
261 !! Error message.
262
263
264 3 if(present(nbins))then
265
6/8
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 3 times.
✓ Branch 7 taken 1 times.
7 if(all(nbins .gt. 0)) distribs_container%nbins = nbins
266 end if
267
268
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 if(present(width))then
269
6/8
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 3 times.
✓ Branch 7 taken 1 times.
7 if(all(width.ge.0._real32)) distribs_container%width = width
270 end if
271
272
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 if(present(sigma))then
273
6/8
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 3 times.
✓ Branch 7 taken 1 times.
7 if(all(sigma.ge.0._real32)) distribs_container%sigma = sigma
274 end if
275
276
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 if(present(cutoff_min))then
277
3/6
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
2 if(any(cutoff_min.ge.0._real32)) &
278
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
8 distribs_container%cutoff_min = cutoff_min
279 end if
280
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 if(present(cutoff_max))then
281
4/6
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 6 times.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
8 if(all(cutoff_max.ge.0._real32)) &
282
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
8 distribs_container%cutoff_max = cutoff_max
283 end if
284
6/6
✓ Branch 0 taken 7 times.
✓ Branch 1 taken 2 times.
✓ Branch 2 taken 1 times.
✓ Branch 3 taken 6 times.
✓ Branch 4 taken 1 times.
✓ Branch 5 taken 2 times.
9 if( &
285 any(distribs_container%cutoff_max .le. distribs_container%cutoff_min) &
286 )then
287 write(stop_msg,*) &
288 "cutoff_max <= cutoff_min" // &
289 achar(13) // achar(10) // &
290 1 "cutoff min: ", distribs_container%cutoff_min, &
291 achar(13) // achar(10) // &
292 2 "cutoff max: ", distribs_container%cutoff_max
293 1 call stop_program( stop_msg )
294 1 return
295 end if
296
297
298
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 if(present(history_len)) distribs_container%history_len = history_len
299
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
2 if(allocated(distribs_container%history_deltas)) &
300 deallocate(distribs_container%history_deltas)
301
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 if(distribs_container%history_len.ge.0) &
302 allocate( &
303 distribs_container%history_deltas( &
304 distribs_container%history_len &
305 ), &
306 source = huge(0._real32) &
307
11/16
✓ 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 13 not taken.
✓ Branch 14 taken 2 times.
✓ Branch 16 taken 15 times.
✓ Branch 17 taken 2 times.
17 )
308
309
20/20
✓ Branch 0 taken 9 times.
✓ Branch 1 taken 3 times.
✓ Branch 2 taken 9 times.
✓ Branch 3 taken 3 times.
✓ Branch 4 taken 9 times.
✓ Branch 5 taken 3 times.
✓ Branch 6 taken 9 times.
✓ Branch 7 taken 3 times.
✓ Branch 8 taken 9 times.
✓ Branch 9 taken 3 times.
✓ Branch 10 taken 12 times.
✓ Branch 11 taken 3 times.
✓ Branch 12 taken 9 times.
✓ Branch 13 taken 3 times.
✓ Branch 14 taken 27 times.
✓ Branch 15 taken 9 times.
✓ Branch 16 taken 9 times.
✓ Branch 17 taken 3 times.
✓ Branch 18 taken 1 times.
✓ Branch 19 taken 2 times.
107 end function init_distribs_container
310 !###############################################################################
311
312
313 !###############################################################################
314 6 subroutine set_width(this, width)
315 !! Set the width of the gaussians used in the 2-, 3-, and 4-body
316 !! distribution functions.
317 implicit none
318
319 ! Arguments
320 class(distribs_container_type), intent(inout) :: this
321 !! Parent. Instance of distribution functions container.
322 real(real32), dimension(3), intent(in) :: width
323 !! Width of the gaussians used in the 2-, 3-, and 4-body
324 !! distribution functions.
325
326
2/2
✓ Branch 0 taken 18 times.
✓ Branch 1 taken 6 times.
24 this%width = width
327
328 6 end subroutine set_width
329 !###############################################################################
330
331
332 !###############################################################################
333 4 subroutine set_sigma(this, sigma)
334 !! Set the sigma of the gaussians used in the 2-, 3-, and 4-body
335 !! distribution functions.
336 implicit none
337
338 ! Arguments
339 class(distribs_container_type), intent(inout) :: this
340 !! Parent. Instance of distribution functions container.
341 real(real32), dimension(3), intent(in) :: sigma
342 !! Sigma of the gaussians used in the 2-, 3-, and 4-body distribution
343 !! functions.
344
345
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 4 times.
16 this%sigma = sigma
346
347 4 end subroutine set_sigma
348 !###############################################################################
349
350
351 !###############################################################################
352 2 subroutine set_cutoff_min(this, cutoff_min)
353 !! Set the minimum cutoff for the 2-, 3-, and 4-body distribution functions.
354 implicit none
355
356 ! Arguments
357 class(distribs_container_type), intent(inout) :: this
358 !! Parent. Instance of distribution functions container.
359 real(real32), dimension(3), intent(in) :: cutoff_min
360 !! Minimum cutoff for the 2-, 3-, and 4-body distribution functions.
361
362
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
8 this%cutoff_min = cutoff_min
363
364 2 end subroutine set_cutoff_min
365 !###############################################################################
366
367
368 !###############################################################################
369 2 subroutine set_cutoff_max(this, cutoff_max)
370 !! Set the maximum cutoff for the 2-, 3-, and 4-body distribution functions.
371 implicit none
372
373 ! Arguments
374 class(distribs_container_type), intent(inout) :: this
375 !! Parent. Instance of distribution functions container.
376 real(real32), dimension(3), intent(in) :: cutoff_max
377 !! Maximum cutoff for the 2-, 3-, and 4-body distribution functions.
378
379
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 2 times.
8 this%cutoff_max = cutoff_max
380
381 2 end subroutine set_cutoff_max
382 !###############################################################################
383
384
385 !###############################################################################
386 1 subroutine set_radius_distance_tol(this, radius_distance_tol)
387 !! Set the tolerance for the distance between atoms for 3- and 4-body.
388 implicit none
389
390 ! Arguments
391 class(distribs_container_type), intent(inout) :: this
392 !! Parent. Instance of distribution functions container.
393 real(real32), dimension(4), intent(in) :: radius_distance_tol
394 !! Tolerance for the distance between atoms for 3- and 4-body.
395
396
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 1 times.
5 this%radius_distance_tol = radius_distance_tol
397
398 1 end subroutine set_radius_distance_tol
399 !###############################################################################
400
401
402 !###############################################################################
403 10 subroutine set_history_len(this, history_len)
404 !! Set the length of the history for the distribution functions.
405 implicit none
406
407 ! Arguments
408 class(distribs_container_type), intent(inout) :: this
409 !! Parent. Instance of distribution functions container.
410 integer, intent(in) :: history_len
411 !! Length of the history for the distribution functions.
412
413 ! Local variables
414 integer :: min_len
415 !! Minimum length of the history.
416 10 real(real32), dimension(:), allocatable :: history_deltas
417 !! History of the changes in the distribution functions.
418
419
2/2
✓ Branch 0 taken 9 times.
✓ Branch 1 taken 1 times.
10 if(history_len.gt.0)then
420
9/16
✓ Branch 0 taken 9 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 9 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 9 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 9 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 9 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 9 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 9 times.
✓ Branch 17 taken 83 times.
✓ Branch 18 taken 9 times.
92 allocate(history_deltas(history_len), source = huge(0._real32) )
421
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 8 times.
9 if(allocated(this%history_deltas))then
422 1 min_len = min(this%history_len, history_len)
423
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 history_deltas(1:min_len) = this%history_deltas(1:min_len)
424
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 deallocate(this%history_deltas)
425 end if
426
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
9 call move_alloc(history_deltas, this%history_deltas)
427 else
428
2/4
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 1 times.
1 if(allocated(this%history_deltas)) deallocate(this%history_deltas)
429 end if
430 10 this%history_len = history_len
431
432
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 10 times.
10 end subroutine set_history_len
433 !###############################################################################
434
435
436 !###############################################################################
437 22 subroutine create( &
438
5/8
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 16 times.
✓ Branch 2 taken 6 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 6 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 22 times.
✗ Branch 7 not taken.
22 this, basis_list, energy_above_hull_list, deallocate_systems, &
439 verbose &
440 )
441 !! create the distribution functions from the input file
442 implicit none
443 ! Arguments
444 class(distribs_container_type), intent(inout) :: this
445 !! Parent. Instance of distribution functions container.
446 type(basis_type), dimension(:), intent(in) :: basis_list
447 !! List of basis structures.
448 real(real32), dimension(:), intent(in), optional :: energy_above_hull_list
449 !! List of energies above the hull for the structures.
450 logical, intent(in), optional :: deallocate_systems
451 !! Boolean whether to deallocate the systems after the
452 !! distribution functions are created.
453 integer, intent(in), optional :: verbose
454 !! Verbosity level.
455
456 ! Local variables
457 logical :: deallocate_systems_
458 !! Boolean whether to deallocate the systems after the distribution
459 character(256) :: stop_msg
460 !! Error message.
461 integer :: verbose_
462 !! Verbosity level.
463 logical :: suppress_warnings_store
464 !! Boolean to store the suppress_warnings value.
465
466
467 ! Set the verbosity level
468 22 verbose_ = 0
469
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 22 times.
22 if(present(verbose)) verbose_ = verbose
470
1/2
✓ Branch 0 taken 22 times.
✗ Branch 1 not taken.
22 if(verbose_ .eq. 0)then
471 22 suppress_warnings_store = suppress_warnings
472 22 suppress_warnings = .true.
473 end if
474
475 ! Check if element_database is allocated
476
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 21 times.
22 if(.not.allocated(element_database))then
477 write(stop_msg,*) "element_database not allocated" // &
478 achar(13) // achar(10) // &
479 "Run the set_element_energies() procedure of " // &
480 1 "distribs_container_type before calling create()"
481 1 call stop_program( stop_msg )
482 5 return
483 end if
484
485 ! Check if energy_above_hull_list and basis_list are the same size
486
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 15 times.
21 if(present(energy_above_hull_list))then
487
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 6 times.
6 if(size(energy_above_hull_list).eq.0)then
488 this%weight_by_hull = .false.
489
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 2 times.
6 elseif(size(energy_above_hull_list) .ne. size(basis_list))then
490 4 this%weight_by_hull = .true.
491 write(stop_msg,*) "energy_above_hull_list and basis_list " // &
492 "not the same size" // &
493 achar(13) // achar(10) // &
494 4 "energy_above_hull_list: ", size(energy_above_hull_list), &
495 achar(13) // achar(10) // &
496 8 "basis_list: ", size(basis_list)
497 4 call stop_program( stop_msg )
498 4 return
499 end if
500 end if
501
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 17 times.
17 if(this%weight_by_hull.and..not.present(energy_above_hull_list))then
502 write(stop_msg,*) "energy_above_hull_list not present" // &
503 achar(13) // achar(10) // &
504 "energy_above_hull_list must be present when using hull weighting"
505 call stop_program( stop_msg )
506 return
507 end if
508
509
510 ! Check if deallocate_systems is present
511 17 deallocate_systems_ = .true.
512
2/2
✓ Branch 0 taken 15 times.
✓ Branch 1 taken 2 times.
17 if(present(deallocate_systems)) deallocate_systems_ = deallocate_systems
513
514 17 this%num_evaluated = 0
515 17 this%num_evaluated_allocated = 0
516
3/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
17 if(allocated(this%gdf%df_2body)) deallocate(this%gdf%df_2body)
517
3/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
17 if(allocated(this%gdf%df_3body)) deallocate(this%gdf%df_3body)
518
3/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
17 if(allocated(this%gdf%df_4body)) deallocate(this%gdf%df_4body)
519
3/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
17 if(allocated(this%norm_2body)) deallocate(this%norm_2body)
520
3/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
17 if(allocated(this%norm_3body)) deallocate(this%norm_3body)
521
3/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
17 if(allocated(this%norm_4body)) deallocate(this%norm_4body)
522
15/26
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 14 times.
✓ Branch 2 taken 3 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 5 times.
✓ Branch 5 taken 3 times.
✓ Branch 6 taken 5 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 5 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 5 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 5 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 5 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 5 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 5 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 5 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 5 times.
✗ Branch 23 not taken.
✗ Branch 24 not taken.
✓ Branch 25 taken 3 times.
25 if(allocated(this%system)) deallocate(this%system)
523
3/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
17 if(allocated(this%in_dataset_2body)) deallocate(this%in_dataset_2body)
524
3/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
17 if(allocated(this%in_dataset_3body)) deallocate(this%in_dataset_3body)
525
3/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
17 if(allocated(this%in_dataset_4body)) deallocate(this%in_dataset_4body)
526
3/4
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
17 if(allocated(this%best_energy_pair)) deallocate(this%best_energy_pair)
527
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 12 times.
17 if(allocated(this%best_energy_per_species)) &
528
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
5 deallocate(this%best_energy_per_species)
529
4/28
✗ Branch 0 not taken.
✓ Branch 1 taken 17 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 17 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 17 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 17 times.
✗ 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 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.
17 allocate(this%system(0))
530 17 call this%add(basis_list)
531
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 15 times.
17 if(present(energy_above_hull_list).and.this%weight_by_hull)then
532
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 2 times.
5 this%system(:)%energy_above_hull = energy_above_hull_list(:)
533 end if
534 17 call this%set_bond_info()
535 17 call this%evolve()
536
2/2
✓ Branch 0 taken 8 times.
✓ Branch 1 taken 9 times.
17 if(deallocate_systems_) call this%deallocate_systems()
537
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 11 times.
17 if(this%host_system%defined) &
538 6 call this%host_system%set_element_map(this%element_info)
539
540
1/2
✓ Branch 0 taken 17 times.
✗ Branch 1 not taken.
17 if(verbose_ .eq. 0)then
541 17 suppress_warnings = suppress_warnings_store
542 end if
543
544 17 this%iteration = 0
545
546 end subroutine create
547 !###############################################################################
548
549
550 !###############################################################################
551 12 subroutine update( &
552
5/8
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 6 times.
✓ Branch 2 taken 6 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 6 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 12 times.
✗ Branch 7 not taken.
12 this, basis_list, energy_above_hull_list, from_host, &
553 deallocate_systems, &
554 verbose &
555 )
556 !! update the distribution functions from the input file
557 implicit none
558 ! Arguments
559 class(distribs_container_type), intent(inout) :: this
560 !! Parent. Instance of distribution functions container.
561 type(basis_type), dimension(:), intent(in) :: basis_list
562 !! List of basis structures.
563 real(real32), dimension(:), intent(in), optional :: energy_above_hull_list
564 !! List of energies above the hull for the structures.
565 logical, intent(in), optional :: from_host
566 !! Optional. Boolean whether structures are derived from the host.
567 logical, intent(in), optional :: deallocate_systems
568 !! Boolean whether to deallocate the systems after the
569 !! distribution functions are created.
570 integer, intent(in), optional :: verbose
571 !! Verbosity level.
572
573 ! Local variables
574 integer :: i
575 !! Loop index.
576 logical :: deallocate_systems_
577 !! Boolean whether to deallocate the systems after the distribution
578 logical :: from_host_
579 !! Boolean whether structures are derived from the host.
580 character(256) :: stop_msg
581 !! Error message.
582 integer :: verbose_
583 !! Verbosity level.
584 logical :: suppress_warnings_store
585 !! Boolean to store the suppress_warnings value.
586 12 type(distribs_base_type) :: gdf_old
587
588
589 ! Set the verbosity level
590 12 verbose_ = 0
591
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 12 times.
12 if(present(verbose)) verbose_ = verbose
592
1/2
✓ Branch 0 taken 12 times.
✗ Branch 1 not taken.
12 if(verbose_ .eq. 0)then
593 12 suppress_warnings_store = suppress_warnings
594 12 suppress_warnings = .true.
595 end if
596
597 ! Check if energy_above_hull_list and basis_list are the same size
598
2/2
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 6 times.
12 if(present(energy_above_hull_list))then
599
1/2
✓ Branch 0 taken 6 times.
✗ Branch 1 not taken.
6 if(size(energy_above_hull_list).eq.0 .and. .not. this%weight_by_hull)then
600
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 4 times.
6 elseif(size(energy_above_hull_list) .ne. size(basis_list) .and. &
601 this%weight_by_hull &
602 )then
603 write(stop_msg,*) "energy_above_hull_list and basis_list " // &
604 "not the same size whilst using hull weighting" // &
605 achar(13) // achar(10) // &
606 2 "energy_above_hull_list: ", size(energy_above_hull_list), &
607 achar(13) // achar(10) // &
608 4 "basis_list: ", size(basis_list)
609 2 call stop_program( stop_msg )
610 2 return
611 end if
612 end if
613
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 10 times.
10 if(this%weight_by_hull.and..not.present(energy_above_hull_list))then
614 write(stop_msg,*) "energy_above_hull_list not present" // &
615 achar(13) // achar(10) // &
616 "energy_above_hull_list must be present when using hull weighting"
617 call stop_program( stop_msg )
618 return
619 end if
620
621 ! Check if from_host is present
622
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 8 times.
10 if(present(from_host))then
623 2 from_host_ = from_host
624
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 if(this%weight_by_hull.and.from_host_)then
625 write(stop_msg,*) "Hull weighting and from_host are incompatible" // &
626 achar(13) // achar(10) // &
627 2 "Set from_host = .false. to use hull weighting"
628 2 call stop_program( stop_msg )
629 2 return
630 end if
631 else
632
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
8 if(this%weight_by_hull)then
633 from_host_ = .false.
634 else
635 8 from_host_ = .true.
636 end if
637 end if
638
639 ! Check if deallocate_systems is present
640 8 deallocate_systems_ = .true.
641
1/2
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
8 if(present(deallocate_systems)) deallocate_systems_ = deallocate_systems
642
643 ! Add the new basis structures
644 8 call this%add(basis_list)
645 8 call this%update_bond_info()
646
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
8 if(present(energy_above_hull_list).and.this%weight_by_hull)then
647 this%system(this%num_evaluated_allocated + 1:)%energy_above_hull = &
648 energy_above_hull_list(:)
649 end if
650
651 ! If the structures are derived from the host, subtract the interface energy
652
1/2
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
8 if(from_host_)then
653
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
8 if(.not.this%host_system%defined)then
654 write(stop_msg,*) "host not set" // &
655 achar(13) // achar(10) // &
656 "Run the set_host() procedure of parent of" // &
657 "distribs_container_type before calling create()"
658 call stop_program( stop_msg )
659 return
660 else
661
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 6 times.
8 if(.not.allocated(this%host_system%df_2body))then
662 call this%host_system%calculate( &
663 this%host_system%basis, &
664 width = this%width, &
665 sigma = this%sigma, &
666 cutoff_min = this%cutoff_min, &
667 cutoff_max = this%cutoff_max, &
668 radius_distance_tol = this%radius_distance_tol &
669 2 )
670 end if
671 8 call this%host_system%calculate_interface_energy(this%element_info)
672
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 8 times.
20 do i = this%num_evaluated_allocated + 1, size(this%system), 1
673 12 this%system(i)%from_host = .true.
674 this%system(i)%energy = this%system(i)%energy - &
675 12 this%host_system%interface_energy
676 this%system(i)%num_atoms = this%system(i)%num_atoms - &
677 20 this%host_system%num_atoms
678 end do
679 end if
680 end if
681
682
683 ! If history_len is set, temporarily store the old descriptor
684
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
8 if(this%history_len.gt.0)then
685
8/16
✓ Branch 0 taken 4 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 4 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 4 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 4 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 4 times.
✗ Branch 9 not taken.
✗ Branch 10 not taken.
✓ Branch 11 taken 4 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 4 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 4 times.
4 gdf_old = this%gdf
686
2/2
✓ Branch 0 taken 36 times.
✓ Branch 1 taken 4 times.
40 this%history_deltas(2:) = this%history_deltas(1:this%history_len-1)
687 end if
688
689 ! Evolve the distribution functions
690 8 call this%evolve()
691
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 6 times.
8 if(deallocate_systems_) call this%deallocate_systems()
692
1/2
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
8 if(this%host_system%defined) &
693 8 call this%host_system%set_element_map(this%element_info)
694
695 ! Evaluate the change in the descriptor from the last iteration
696
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
8 if(this%history_len.gt.0.and.this%num_evaluated.gt.0)then
697 4 this%history_deltas(1) = this%gdf%compare(gdf_old)
698 end if
699
700
1/2
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
8 if(verbose_ .eq. 0)then
701 8 suppress_warnings = suppress_warnings_store
702 end if
703
704 8 this%iteration = this%iteration + 1
705
706
6/6
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 8 times.
✓ Branch 2 taken 4 times.
✓ Branch 3 taken 8 times.
✓ Branch 4 taken 4 times.
✓ Branch 5 taken 8 times.
12 end subroutine update
707 !###############################################################################
708
709
710 !###############################################################################
711 10 subroutine deallocate_systems(this)
712 !! Deallocate the systems in the container.
713 implicit none
714
715 ! Arguments
716 class(distribs_container_type), intent(inout) :: this
717 !! Parent. Instance of distribution functions container.
718
719
14/26
✓ Branch 0 taken 10 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 10 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 15 times.
✓ Branch 5 taken 10 times.
✓ Branch 6 taken 15 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 15 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 15 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 15 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 15 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 15 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 15 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 15 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 15 times.
✗ Branch 23 not taken.
✗ Branch 24 not taken.
✓ Branch 25 taken 10 times.
35 if(allocated(this%system)) deallocate(this%system)
720 10 this%num_evaluated_allocated = 0
721
722 10 end subroutine deallocate_systems
723 !###############################################################################
724
725
726 !###############################################################################
727 2 subroutine write_gdfs(this, file)
728 !! Write the generalised distribution functions to a file.
729 implicit none
730
731 ! Arguments
732 class(distribs_container_type), intent(in) :: this
733 !! Parent. Instance of distribution functions container.
734 character(*), intent(in) :: file
735 !! Filename to write the generalised distribution functions to.
736
737 ! Local variables
738 integer :: unit
739 !! File unit.
740 integer :: i
741 !! Loop index.
742 character(256) :: fmt
743 !! Format string.
744 character(256) :: stop_msg
745 !! Error message.
746
747 2 if(.not.allocated(this%gdf%df_2body))then
748 write(stop_msg,*) &
749 "Generalised distribution functions are not allocated." // &
750 achar(13) // achar(10) // &
751 "create() or read() must be called before writing the " // &
752 "generalised distribution functions."
753 call stop_program( stop_msg )
754 return
755 end if
756 2 open(newunit=unit, file=file)
757 2 write(unit, '("# history_len ",I0)') this%history_len
758 write(fmt, '("(""# history_deltas""",I0,"(1X,ES0.8))")') &
759 2 size(this%history_deltas)
760 2 write(unit, fmt) this%history_deltas
761 2 write(unit, '("# nbins",3(1X,I0))') this%nbins
762 2 write(unit, '("# width",3(1X,ES0.8))') this%width
763 2 write(unit, '("# sigma",3(1X,ES0.8))') this%sigma
764 2 write(unit, '("# cutoff_min",3(1X,ES0.8))') this%cutoff_min
765 2 write(unit, '("# cutoff_max",3(1X,ES0.8))') this%cutoff_max
766 write(unit, '("# radius_distance_tol",4(1X,ES0.4))') &
767 2 this%radius_distance_tol
768 2 write(fmt, '("(""# "",A,",I0,"(1X,A))")') size(this%element_info)
769
2/2
✓ Branch 2 taken 4 times.
✓ Branch 3 taken 2 times.
6 write(unit, fmt) "elements", this%element_info(:)%name
770 2 write(fmt, '("(""# "",A,",I0,"(1X,ES0.4))")') size(this%element_info)
771
2/2
✓ Branch 2 taken 4 times.
✓ Branch 3 taken 2 times.
6 write(unit, fmt) "energies", this%element_info(:)%energy
772 2 write(unit, fmt) "best_energy_per_element", this%best_energy_per_species
773 2 write(unit, fmt) "3-body_norm", this%norm_3body
774 2 write(unit, fmt) "4-body_norm", this%norm_4body
775 2 write(fmt, '("(""# "",A,",I0,"(1X,L1))")') size(this%element_info)
776 2 write(unit, fmt) "in_dataset_3body", this%in_dataset_3body
777 2 write(unit, fmt) "in_dataset_4body", this%in_dataset_4body
778 2 write(fmt, '("(""# "",A,",I0,"(1X,A))")') size(this%bond_info)
779 2 write(unit, fmt) "element_pairs", &
780 ( &
781 trim(this%bond_info(i)%element(1)) // "-" // &
782
2/4
✓ Branch 2 taken 7 times.
✗ Branch 3 not taken.
✓ Branch 6 taken 7 times.
✗ Branch 7 not taken.
9 trim(this%bond_info(i)%element(2)), &
783
2/2
✓ Branch 0 taken 7 times.
✓ Branch 1 taken 2 times.
16 i = 1, size(this%bond_info) &
784
1/2
✗ Branch 1 not taken.
✓ Branch 2 taken 9 times.
13 )
785 2 write(fmt, '("(""# "",A,",I0,"(1X,ES0.4))")') size(this%bond_info)
786
2/2
✓ Branch 2 taken 7 times.
✓ Branch 3 taken 2 times.
9 write(unit, fmt) "radii", this%bond_info(:)%radius_covalent
787 2 write(unit, fmt) "best_energy_per_pair", this%best_energy_pair
788 2 write(unit, fmt) "2-body_norm", this%norm_2body
789 2 write(fmt, '("(""# "",A,",I0,"(1X,L1))")') size(this%bond_info)
790 2 write(unit, fmt) "in_dataset_2body", this%in_dataset_2body
791 2 write(unit, *)
792 2 write(unit, '("# 2-body")')
793 2 write(fmt,'("(""# bond-length "",",I0,"(1X,A))")') size(this%bond_info)
794 write(unit, fmt) &
795 ( &
796 trim(this%bond_info(i)%element(1)) // "-" // &
797
2/4
✓ Branch 2 taken 7 times.
✗ Branch 3 not taken.
✓ Branch 6 taken 7 times.
✗ Branch 7 not taken.
9 trim(this%bond_info(i)%element(2)), &
798
2/2
✓ Branch 0 taken 7 times.
✓ Branch 1 taken 2 times.
16 i = 1, size(this%bond_info) &
799
1/2
✗ Branch 1 not taken.
✓ Branch 2 taken 9 times.
11 )
800
2/2
✓ Branch 0 taken 112 times.
✓ Branch 1 taken 2 times.
114 do i = 1, this%nbins(1)
801 write(unit, *) &
802 112 this%cutoff_min(1) + this%width(1) * ( i - 1 ), &
803 226 this%gdf%df_2body(i,:)
804 end do
805 2 write(unit, *)
806 2 write(unit, '("# 3-body")')
807 2 write(fmt,'("(""# bond-angle "",",I0,"(1X,A))")') size(this%bond_info)
808
2/2
✓ Branch 1 taken 4 times.
✓ Branch 2 taken 2 times.
6 write(unit, fmt) this%element_info(:)%name
809
2/2
✓ Branch 0 taken 64 times.
✓ Branch 1 taken 2 times.
66 do i = 1, this%nbins(2)
810 write(unit, *) &
811 64 this%cutoff_min(2) + this%width(2) * ( i - 1 ), &
812 130 this%gdf%df_3body(i,:)
813 end do
814 2 write(unit, *)
815 2 write(unit, '("# 4-body")')
816 2 write(fmt,'("(""# dihedral-angle "",",I0,"(1X,A))")') size(this%bond_info)
817
2/2
✓ Branch 1 taken 4 times.
✓ Branch 2 taken 2 times.
6 write(unit, fmt) this%element_info(:)%name
818
2/2
✓ Branch 0 taken 64 times.
✓ Branch 1 taken 2 times.
66 do i = 1, this%nbins(3)
819 write(unit, *) &
820 64 this%cutoff_min(2) + this%width(2) * ( i - 1 ), &
821 130 this%gdf%df_4body(i,:)
822 end do
823 2 close(unit)
824
825
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
2 end subroutine write_gdfs
826 !###############################################################################
827
828
829 !###############################################################################
830 2 subroutine read_gdfs(this, file)
831 !! Read the generalised distribution functions from a file.
832 implicit none
833
834 ! Arguments
835 class(distribs_container_type), intent(inout) :: this
836 !! Parent. Instance of distribution functions container.
837 character(*), intent(in) :: file
838 !! Filename to read the generalised distribution functions from.
839
840 ! Local variables
841 integer :: unit
842 !! File unit.
843 integer :: iostat
844 !! I/O status.
845
846 integer :: i
847 !! Loop index.
848 integer :: nspec
849 !! Number of species.
850 logical :: exist
851 !! Boolean whether the file exists.
852 character(256) :: buffer, buffer1
853 !! Buffer for reading lines.
854
855 ! check if file exists
856 2 inquire(file=file, exist=exist)
857
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
2 if(.not.exist)then
858 call stop_program( "File does not exist" )
859 return
860 end if
861
862 ! read the file
863 2 open(newunit=unit, file=file)
864 42 do
865 44 read(unit, '(A)', iostat=iostat) buffer
866
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 44 times.
44 if(iostat.ne.0) exit
867
3/4
✓ Branch 2 taken 44 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 42 times.
✓ Branch 5 taken 2 times.
44 buffer = trim(adjustl(buffer))
868
4/4
✓ Branch 1 taken 42 times.
✓ Branch 2 taken 2 times.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 42 times.
44 if(trim(buffer) .eq. "") cycle
869
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 42 times.
42 if(buffer(1:1) .ne. "#") cycle
870 ! get the header
871
2/4
✓ Branch 2 taken 42 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 42 times.
✗ Branch 5 not taken.
42 buffer = trim(adjustl(buffer(2:)))
872
3/4
✓ Branch 2 taken 42 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✓ Branch 5 taken 40 times.
42 if(trim(adjustl(buffer)) .eq. "2-body") exit
873
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 38 times.
40 if(index(buffer, "history_len") .ne. 0) then
874 2 read(buffer, *) buffer1, this%history_len
875 2 call this%set_history_len(this%history_len)
876
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 36 times.
38 else if(index(buffer, "history_deltas") .ne. 0) then
877 2 read(buffer, *) buffer1, this%history_deltas
878
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 34 times.
36 else if(index(buffer, "nbins") .ne. 0) then
879 2 read(buffer, *) buffer1, this%nbins
880
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 32 times.
34 else if(index(buffer, "width") .ne. 0) then
881 2 read(buffer, *) buffer1, this%width
882
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 30 times.
32 else if(index(buffer, "sigma") .ne. 0) then
883 2 read(buffer, *) buffer1, this%sigma
884
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 28 times.
30 else if(index(buffer, "cutoff_min") .ne. 0) then
885 2 read(buffer, *) buffer1, this%cutoff_min
886
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 26 times.
28 else if(index(buffer, "cutoff_max") .ne. 0) then
887 2 read(buffer, *) buffer1, this%cutoff_max
888
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 24 times.
26 else if(index(buffer, "radius_distance_tol") .ne. 0) then
889 2 read(buffer, *) buffer1, this%radius_distance_tol
890
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 22 times.
24 else if(index(buffer, "elements") .ne. 0) then
891 2 nspec = icount(buffer(index(buffer,"elements")+8:))
892
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
2 if(allocated(this%element_info)) deallocate(this%element_info)
893
9/16
✓ 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 4 times.
✓ Branch 18 taken 2 times.
6 allocate(this%element_info(nspec))
894
2/2
✓ Branch 2 taken 4 times.
✓ Branch 3 taken 2 times.
6 read(buffer, *) buffer1, this%element_info(:)%name
895
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 20 times.
22 else if(index(buffer, "energies") .ne. 0) then
896
2/2
✓ Branch 2 taken 4 times.
✓ Branch 3 taken 2 times.
6 read(buffer, *) buffer1, this%element_info(:)%energy
897
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 2 times.
6 do i = 1, nspec
898 call this%set_element_energy( &
899 this%element_info(i)%name, &
900 this%element_info(i)%energy &
901 4 )
902 6 call this%element_info(i)%set(this%element_info(i)%name)
903 end do
904 2 call this%update_bond_info()
905
7/14
✓ 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.
2 allocate(this%best_energy_per_species(nspec))
906
7/14
✓ 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.
2 allocate(this%norm_3body(nspec))
907
7/14
✓ 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.
2 allocate(this%norm_4body(nspec))
908
7/14
✓ 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.
2 allocate(this%in_dataset_3body(nspec))
909
7/14
✓ 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.
2 allocate(this%in_dataset_4body(nspec))
910
7/14
✓ 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.
2 allocate(this%best_energy_pair(size(this%bond_info)))
911
7/14
✓ 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.
2 allocate(this%norm_2body(size(this%bond_info)))
912
7/14
✓ 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.
2 allocate(this%in_dataset_2body(size(this%bond_info)))
913
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 18 times.
20 else if(index(buffer, "best_energy_per_element") .ne. 0) then
914 2 read(buffer, *) buffer1, this%best_energy_per_species
915
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 16 times.
18 else if(index(buffer, "3-body_norm") .ne. 0) then
916 2 read(buffer, *) buffer1, this%norm_3body
917
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 14 times.
16 else if(index(buffer, "4-body_norm") .ne. 0) then
918 2 read(buffer, *) buffer1, this%norm_4body
919
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 12 times.
14 else if(index(buffer, "in_dataset_3body") .ne. 0) then
920 2 read(buffer, *) buffer1, this%in_dataset_3body
921
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 10 times.
12 else if(index(buffer, "in_dataset_4body") .ne. 0) then
922 2 read(buffer, *) buffer1, this%in_dataset_4body
923
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 8 times.
10 else if(index(buffer, "element_pairs") .ne. 0) then
924
2/2
✓ Branch 2 taken 7 times.
✓ Branch 3 taken 2 times.
9 read(buffer, *) buffer1, this%bond_info(:)%element(1)
925
2/2
✓ Branch 2 taken 7 times.
✓ Branch 3 taken 2 times.
9 read(buffer, *) buffer1, this%bond_info(:)%element(2)
926
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 6 times.
8 else if(index(buffer, "radii") .ne. 0) then
927
2/2
✓ Branch 2 taken 7 times.
✓ Branch 3 taken 2 times.
9 read(buffer, *) buffer1, this%bond_info(:)%radius_covalent
928
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 4 times.
6 else if(index(buffer, "best_energy_per_pair") .ne. 0) then
929 2 read(buffer, *) buffer1, this%best_energy_pair
930
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
4 else if(index(buffer, "3-body_norm") .ne. 0) then
931 read(buffer, *) buffer1, this%norm_3body
932
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
4 else if(index(buffer, "4-body_norm") .ne. 0) then
933 read(buffer, *) buffer1, this%norm_4body
934
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
4 else if(index(buffer, "in_dataset_3body") .ne. 0) then
935 read(buffer, *) buffer1, this%in_dataset_3body
936
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
4 else if(index(buffer, "in_dataset_4body") .ne. 0) then
937 read(buffer, *) buffer1, this%in_dataset_4body
938
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 2 times.
4 else if(index(buffer, "2-body_norm") .ne. 0) then
939 2 read(buffer, *) buffer1, this%norm_2body
940
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 else if(index(buffer, "in_dataset_2body") .ne. 0) then
941 2 read(buffer, *) buffer1, this%in_dataset_2body
942 else
943 write(0,*) "Unknown header: ", trim(buffer)
944 cycle
945 end if
946 end do
947
948 2 read(unit, *)
949
9/18
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 2 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 2 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 2 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 2 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 2 times.
2 allocate(this%gdf%df_2body(this%nbins(1),size(this%bond_info)))
950
2/2
✓ Branch 0 taken 112 times.
✓ Branch 1 taken 2 times.
114 do i = 1, this%nbins(1)
951 114 read(unit, *) buffer, this%gdf%df_2body(i,:)
952 end do
953 2 read(unit, *)
954 2 read(unit, *)
955 2 read(unit, *)
956
9/18
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 2 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 2 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 2 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 2 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 2 times.
2 allocate(this%gdf%df_3body(this%nbins(2),nspec))
957
2/2
✓ Branch 0 taken 64 times.
✓ Branch 1 taken 2 times.
66 do i = 1, this%nbins(2)
958 66 read(unit, *) buffer, this%gdf%df_3body(i,:)
959 end do
960 2 read(unit, *)
961 2 read(unit, *)
962 2 read(unit, *)
963
9/18
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 2 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 2 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 2 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 2 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 2 times.
2 allocate(this%gdf%df_4body(this%nbins(3),nspec))
964
2/2
✓ Branch 0 taken 64 times.
✓ Branch 1 taken 2 times.
66 do i = 1, this%nbins(3)
965 66 read(unit, *) buffer, this%gdf%df_4body(i,:)
966 end do
967 2 close(unit)
968
969 2 end subroutine read_gdfs
970 !###############################################################################
971
972
973 !###############################################################################
974 subroutine write_dfs(this, file)
975 !! Write all distribution functions for each system to a file.
976 implicit none
977
978 ! Arguments
979 class(distribs_container_type), intent(in) :: this
980 !! Parent. Instance of distribution functions container.
981 character(*), intent(in) :: file
982 !! Filename to write the distribution functions to.
983
984 ! Local variables
985 integer :: unit
986 !! File unit.
987 integer :: i, j
988 !! Loop indices.
989 character(256) :: stop_msg
990 !! Error message.
991
992 if(.not.allocated(this%system))then
993 write(stop_msg,*) "No systems to write" // &
994 achar(13) // achar(10) // &
995 "Systems either not created or deallocated after evolve" // &
996 achar(13) // achar(10) // &
997 "To stop automatic deallocation, " // &
998 "use the following flag in create()" // &
999 achar(13) // achar(10) // &
1000 " deallocate_systems = .false."
1001 call stop_program( stop_msg )
1002 return
1003 end if
1004 open(newunit=unit, file=file)
1005 write(unit, *) "nbins", this%nbins
1006 write(unit, *) "width", this%width
1007 write(unit, *) "sigma", this%sigma
1008 write(unit, *) "cutoff_min", this%cutoff_min
1009 write(unit, *) "cutoff_max", this%cutoff_max
1010 write(unit, *)
1011 do i = 1, size(this%system,1)
1012 write(unit, *) this%system(i)%energy
1013 write(unit, *) this%system(i)%element_symbols
1014 write(unit, *) this%system(i)%stoichiometry
1015 do j = 1, this%nbins(1)
1016 write(unit, *) this%system(i)%df_2body(j,:)
1017 end do
1018 do j = 1, this%nbins(2)
1019 write(unit, *) this%system(i)%df_3body(j,:)
1020 end do
1021 do j = 1, this%nbins(3)
1022 write(unit, *) this%system(i)%df_4body(j,:)
1023 end do
1024 write(unit, *)
1025 end do
1026 close(unit)
1027
1028 end subroutine write_dfs
1029 !###############################################################################
1030
1031
1032 !###############################################################################
1033 subroutine read_dfs(this, file)
1034 !! Read all distribution functions for each system from a file.
1035 implicit none
1036
1037 ! Arguments
1038 class(distribs_container_type), intent(inout) :: this
1039 !! Parent. Instance of distribution functions container.
1040 character(*), intent(in) :: file
1041 !! Filename to read the distribution functions from.
1042
1043 ! Local variables
1044 integer :: unit
1045 !! File unit.
1046 integer :: j
1047 !! Loop indices.
1048 integer :: iostat
1049 !! I/O status.
1050 integer :: num_species, num_pairs
1051 !! Number of species and pairs.
1052 character(256) :: buffer
1053 !! Buffer for reading lines.
1054 type(distribs_type) :: system
1055 !! System to read distribution functions into.
1056
1057
1058 open(newunit=unit, file=file)
1059 read(unit, *) buffer, this%nbins
1060 read(unit, *) buffer, this%width
1061 read(unit, *) buffer, this%sigma
1062 read(unit, *) buffer, this%cutoff_min
1063 read(unit, *) buffer, this%cutoff_max
1064 do
1065 read(unit, '(A)', iostat=iostat) buffer
1066 if(iostat.ne.0) exit
1067 if(trim(buffer).eq.''.or.trim(buffer).eq.'#') cycle
1068 read(buffer, *) system%energy
1069 read(unit, '(A)') buffer
1070 num_species = icount(buffer)
1071 allocate(system%element_symbols(num_species))
1072 allocate(system%stoichiometry(num_species))
1073 read(buffer, *) system%element_symbols
1074 read(unit, *) system%stoichiometry
1075 system%num_atoms = sum(system%stoichiometry)
1076 num_pairs = nint( &
1077 gamma(real(num_species + 2, real32)) / &
1078 ( gamma(real(num_species, real32)) * gamma( 3._real32 ) ) &
1079 )
1080 allocate(system%df_2body(this%nbins(1),num_pairs))
1081 do j = 1, this%nbins(1)
1082 read(unit, *) system%df_2body(j,:)
1083 end do
1084 allocate(system%df_3body(this%nbins(2),num_species))
1085 do j = 1, this%nbins(2)
1086 read(unit, *) system%df_3body(j,:)
1087 end do
1088 allocate(system%df_4body(this%nbins(3),num_species))
1089 do j = 1, this%nbins(3)
1090 read(unit, *) system%df_4body(j,:)
1091 end do
1092
1093 this%system = [ this%system, system ]
1094 deallocate(&
1095 system%element_symbols, system%stoichiometry, &
1096 system%df_2body, system%df_3body, system%df_4body &
1097 )
1098 end do
1099 close(unit)
1100
1101 end subroutine read_dfs
1102 !###############################################################################
1103
1104
1105 !###############################################################################
1106 subroutine write_2body(this, file)
1107 !! Write the learned 2-body distribution functions to a file.
1108 implicit none
1109
1110 ! Arguments
1111 class(distribs_container_type), intent(in) :: this
1112 !! Parent. Instance of distribution functions container.
1113 character(*), intent(in) :: file
1114 !! Filename to write the 2-body distribution functions to.
1115
1116 ! Local variables
1117 integer :: unit
1118 !! File unit.
1119 integer :: i, j, is, js
1120 !! Loop indices.
1121 integer :: num_pairs
1122 !! Number of pairs.
1123 integer, allocatable, dimension(:,:) :: idx
1124 !! Pair indices.
1125
1126
1127 num_pairs = nint( &
1128 gamma(real(size(this%element_info) + 2, real32)) / &
1129 ( gamma(real(size(this%element_info), real32)) * gamma( 3._real32 ) ) &
1130 )
1131 allocate(idx(2,num_pairs))
1132 i = 0
1133 do is = 1, size(this%element_info)
1134 do js = is, size(this%element_info), 1
1135 i = i + 1
1136 idx(:,i) = [is, js]
1137 end do
1138 end do
1139
1140 open(newunit=unit, file=file)
1141 do i = 1, size(this%gdf%df_2body, dim=2)
1142 write(unit,'("# ",A,2X,A)') &
1143 this%element_info(idx(1,i))%name, &
1144 this%element_info(idx(2,i))%name
1145 do j = 1, size(this%gdf%df_2body, dim=1)
1146 write(unit,*) &
1147 this%cutoff_min(1) + this%width(1) * ( j - 1 ), &
1148 this%gdf%df_2body(j,i)
1149 end do
1150 write(unit,*)
1151 end do
1152 close(unit)
1153
1154 end subroutine write_2body
1155 !###############################################################################
1156
1157
1158 !###############################################################################
1159 subroutine write_3body(this, file)
1160 !! Write the learned 3-body distribution functions to a file.
1161 implicit none
1162
1163 ! Arguments
1164 class(distribs_container_type), intent(in) :: this
1165 !! Parent. Instance of distribution functions container.
1166 character(*), intent(in) :: file
1167 !! Filename to write the 3-body distribution functions to.
1168
1169 ! Local variables
1170 integer :: unit
1171 !! File unit.
1172 integer :: i, j
1173 !! Loop indices.
1174
1175
1176 open(newunit=unit, file=file)
1177 do i = 1, size(this%gdf%df_3body, dim=2)
1178 write(unit,'("# ",A)') this%element_info(i)%name
1179 do j = 1, size(this%gdf%df_3body, dim=1)
1180 write(unit,*) &
1181 this%cutoff_min(2) + this%width(2) * ( j - 1 ), &
1182 this%gdf%df_3body(j,i)
1183 end do
1184 write(unit,*)
1185 end do
1186 close(unit)
1187
1188 end subroutine write_3body
1189 !###############################################################################
1190
1191
1192 !###############################################################################
1193 subroutine write_4body(this, file)
1194 !! Write the learned 4-body distribution functions to a file.
1195 implicit none
1196
1197 ! Arguments
1198 class(distribs_container_type), intent(in) :: this
1199 !! Parent. Instance of distribution functions container.
1200 character(*), intent(in) :: file
1201 !! Filename to write the 4-body distribution functions to.
1202
1203 ! Local variables
1204 integer :: unit
1205 !! File unit.
1206 integer :: i, j
1207 !! Loop indices.
1208
1209
1210 open(newunit=unit, file=file)
1211 do i = 1, size(this%gdf%df_4body, dim=2)
1212 write(unit,'("# ",A)') this%element_info(i)%name
1213 do j = 1, size(this%gdf%df_4body, dim=1)
1214 write(unit,*) &
1215 this%cutoff_min(3) + this%width(3) * ( j - 1 ), &
1216 this%gdf%df_4body(j,i)
1217 end do
1218 write(unit,*)
1219 end do
1220 close(unit)
1221
1222 end subroutine write_4body
1223 !###############################################################################
1224
1225
1226 !###############################################################################
1227 function get_2body(this) result(output)
1228 !! Get the 2-body distribution functions.
1229 implicit none
1230
1231 ! Arguments
1232 class(distribs_container_type), intent(in) :: this
1233 !! Parent. Instance of distribution functions container.
1234 real(real32), dimension(this%nbins(1),size(this%bond_info)) :: output
1235
1236 output = this%gdf%df_2body
1237
1238 end function get_2body
1239 !###############################################################################
1240
1241
1242 !###############################################################################
1243 function get_3body(this) result(output)
1244 !! Get the 3-body distribution functions.
1245 implicit none
1246
1247 ! Arguments
1248 class(distribs_container_type), intent(in) :: this
1249 !! Parent. Instance of distribution functions container.
1250 real(real32), dimension(this%nbins(2),size(this%element_info)) :: output
1251
1252 output = this%gdf%df_3body
1253
1254 end function get_3body
1255 !###############################################################################
1256
1257
1258 !###############################################################################
1259 function get_4body(this) result(output)
1260 !! Get the 4-body distribution functions.
1261 implicit none
1262
1263 ! Arguments
1264 class(distribs_container_type), intent(in) :: this
1265 !! Parent. Instance of distribution functions container.
1266 real(real32), dimension(this%nbins(3),size(this%element_info)) :: output
1267
1268 output = this%gdf%df_4body
1269
1270 end function get_4body
1271 !###############################################################################
1272
1273
1274 !###############################################################################
1275 function generate_fingerprint(this, structure) result(output)
1276 !! Generate a descriptor for the structure.
1277 implicit none
1278
1279 ! Arguments
1280 class(distribs_container_type), intent(inout) :: this
1281 !! Parent. Instance of distribution functions container.
1282 type(basis_type), intent(in) :: structure
1283 !! Structure to generate the descriptor for.
1284 type(distribs_type) :: output
1285 !! Descriptor for the structure.
1286
1287 call output%calculate( &
1288 structure, &
1289 width = this%width, &
1290 sigma = this%sigma, &
1291 cutoff_min = this%cutoff_min, &
1292 cutoff_max = this%cutoff_max, &
1293 radius_distance_tol = this%radius_distance_tol &
1294 )
1295
1296 end function generate_fingerprint
1297 !-------------------------------------------------------------------------------
1298 subroutine generate_fingerprint_python( &
1299 this, structure, output_2body, output_3body, output_4body &
1300 )
1301 !! Generate a descriptor for the structure.
1302 implicit none
1303
1304 ! Arguments
1305 class(distribs_container_type), intent(inout) :: this
1306 !! Parent. Instance of distribution functions container.
1307 type(basis_type), intent(in) :: structure
1308 !! Structure to generate the descriptor for.
1309 real(real32), dimension(:,:), intent(out) :: output_2body
1310 !! 2-body descriptor for the structure.
1311 real(real32), dimension(:,:), intent(out) :: output_3body
1312 !! 3-body descriptor for the structure.
1313 real(real32), dimension(:,:), intent(out) :: output_4body
1314 !! 4-body descriptor for the structure.
1315
1316 ! Local variables
1317 type(distribs_type) :: distrib
1318 !! Descriptor for the structure.
1319
1320 distrib = this%generate_fingerprint(structure)
1321 output_2body = distrib%df_2body
1322 output_3body = distrib%df_3body
1323 output_4body = distrib%df_4body
1324
1325 end subroutine generate_fingerprint_python
1326 !###############################################################################
1327
1328
1329 !###############################################################################
1330 35 subroutine add(this, system)
1331 !! Add a system to the container.
1332 implicit none
1333
1334 ! Arguments
1335 class(distribs_container_type), intent(inout) :: this
1336 !! Parent. Instance of distribution functions container.
1337 class(*), dimension(..), intent(in) :: system
1338 !! System to add to the container.
1339
1340 ! Local variables
1341 integer :: i
1342 !! Loop index.
1343 integer :: num_structures_previous
1344 !! Number of structures in the container before adding the system.
1345 character(256) :: stop_msg
1346 !! Error message.
1347
1348 select rank(rank_ptr => system)
1349 rank(0)
1350
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 1 times.
6 select type(type_ptr => rank_ptr)
1351 type is (distribs_type)
1352
45/84
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✓ Branch 7 taken 3 times.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 3 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 3 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 3 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 3 times.
✗ Branch 16 not taken.
✓ Branch 17 taken 3 times.
✗ Branch 18 not taken.
✓ 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 not taken.
✓ Branch 25 taken 3 times.
✗ Branch 26 not taken.
✓ Branch 27 taken 3 times.
✗ Branch 28 not taken.
✓ Branch 29 taken 1 times.
✗ Branch 30 not taken.
✗ Branch 31 not taken.
✓ Branch 32 taken 1 times.
✗ Branch 33 not taken.
✓ Branch 34 taken 1 times.
✗ Branch 35 not taken.
✗ Branch 36 not taken.
✗ Branch 37 not taken.
✗ Branch 38 not taken.
✓ Branch 39 taken 1 times.
✗ Branch 40 not taken.
✓ Branch 41 taken 2 times.
✓ Branch 42 taken 1 times.
✓ Branch 43 taken 2 times.
✗ Branch 44 not taken.
✓ Branch 45 taken 2 times.
✗ Branch 46 not taken.
✓ Branch 47 taken 2 times.
✗ Branch 48 not taken.
✓ Branch 49 taken 2 times.
✗ Branch 50 not taken.
✓ Branch 51 taken 2 times.
✗ Branch 52 not taken.
✓ Branch 53 taken 2 times.
✗ Branch 54 not taken.
✓ Branch 55 taken 2 times.
✗ Branch 56 not taken.
✓ Branch 57 taken 2 times.
✗ Branch 58 not taken.
✓ Branch 59 taken 2 times.
✗ Branch 60 not taken.
✓ Branch 61 taken 1 times.
✗ Branch 62 not taken.
✓ Branch 63 taken 3 times.
✓ Branch 64 taken 1 times.
✓ Branch 65 taken 3 times.
✓ Branch 66 taken 1 times.
✗ Branch 67 not taken.
✓ Branch 68 taken 3 times.
✗ Branch 69 not taken.
✓ Branch 70 taken 3 times.
✗ Branch 71 not taken.
✓ Branch 72 taken 3 times.
✗ Branch 73 not taken.
✓ Branch 74 taken 3 times.
✗ Branch 75 not taken.
✓ Branch 76 taken 3 times.
✗ Branch 77 not taken.
✓ Branch 78 taken 3 times.
✗ Branch 79 not taken.
✓ Branch 80 taken 3 times.
✗ Branch 81 not taken.
✓ Branch 82 taken 3 times.
✗ Branch 83 not taken.
✓ Branch 84 taken 3 times.
16 this%system = [ this%system, type_ptr ]
1353 class is (basis_type)
1354 #if defined(GFORTRAN)
1355 call this%add_basis(type_ptr)
1356 #else
1357 32 block
1358
19/34
✓ 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.
✓ Branch 6 taken 4 times.
✓ Branch 7 taken 4 times.
✓ Branch 8 taken 4 times.
✗ Branch 9 not taken.
✗ Branch 10 not taken.
✓ Branch 11 taken 4 times.
✗ 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 4 times.
✓ Branch 21 taken 4 times.
✗ Branch 22 not taken.
✓ Branch 23 taken 4 times.
✗ Branch 24 not taken.
✓ Branch 25 taken 4 times.
✓ 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 not taken.
✓ Branch 33 taken 4 times.
104 type(basis_type), dimension(1) :: basis
1359
1360
11/28
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 4 times.
✓ Branch 2 taken 4 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 4 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 4 times.
✓ Branch 7 taken 4 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 4 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 4 times.
✓ Branch 12 taken 4 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 4 times.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✓ Branch 17 taken 4 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.
12 basis = type_ptr
1361 4 call this%add_basis(basis(1))
1362 end block
1363 #endif
1364 class default
1365 write(stop_msg,*) "Invalid type for system" // &
1366 achar(13) // achar(10) // &
1367 1 "Expected type distribs_type or basis_type"
1368 1 call stop_program( stop_msg )
1369 1 return
1370 end select
1371 rank(1)
1372 28 num_structures_previous = size(this%system)
1373 28 if(.not.allocated(this%system))then
1374
4/28
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 2 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 2 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 2 times.
✗ 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 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.
2 allocate(this%system(0))
1375 end if
1376
4/4
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 26 times.
✓ Branch 2 taken 27 times.
✓ Branch 3 taken 1 times.
56 select type(type_ptr => rank_ptr)
1377 type is (distribs_type)
1378
48/88
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✓ Branch 3 taken 3 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✓ Branch 8 taken 3 times.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 1 times.
✓ Branch 12 taken 6 times.
✓ Branch 13 taken 1 times.
✓ Branch 14 taken 6 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 6 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 6 times.
✗ Branch 19 not taken.
✓ Branch 20 taken 6 times.
✗ Branch 21 not taken.
✓ Branch 22 taken 6 times.
✗ Branch 23 not taken.
✓ Branch 24 taken 6 times.
✗ Branch 25 not taken.
✓ Branch 26 taken 6 times.
✗ Branch 27 not taken.
✓ Branch 28 taken 6 times.
✗ Branch 29 not taken.
✓ Branch 30 taken 6 times.
✗ Branch 31 not taken.
✓ Branch 32 taken 6 times.
✗ Branch 33 not taken.
✓ Branch 34 taken 1 times.
✗ Branch 35 not taken.
✗ Branch 36 not taken.
✓ Branch 37 taken 1 times.
✗ Branch 38 not taken.
✓ Branch 39 taken 1 times.
✗ Branch 40 not taken.
✗ Branch 41 not taken.
✗ Branch 42 not taken.
✗ Branch 43 not taken.
✓ Branch 44 taken 1 times.
✗ Branch 45 not taken.
✓ Branch 46 taken 3 times.
✓ Branch 47 taken 1 times.
✓ Branch 48 taken 3 times.
✗ Branch 49 not taken.
✓ Branch 50 taken 3 times.
✗ Branch 51 not taken.
✓ Branch 52 taken 3 times.
✗ Branch 53 not taken.
✓ Branch 54 taken 3 times.
✗ Branch 55 not taken.
✓ Branch 56 taken 3 times.
✗ Branch 57 not taken.
✓ Branch 58 taken 3 times.
✗ Branch 59 not taken.
✓ Branch 60 taken 3 times.
✗ Branch 61 not taken.
✓ Branch 62 taken 3 times.
✗ Branch 63 not taken.
✓ Branch 64 taken 3 times.
✗ Branch 65 not taken.
✓ Branch 66 taken 1 times.
✗ Branch 67 not taken.
✓ Branch 68 taken 6 times.
✓ Branch 69 taken 1 times.
✓ Branch 70 taken 6 times.
✓ Branch 71 taken 1 times.
✗ Branch 72 not taken.
✓ Branch 73 taken 6 times.
✗ Branch 74 not taken.
✓ Branch 75 taken 6 times.
✗ Branch 76 not taken.
✓ Branch 77 taken 6 times.
✗ Branch 78 not taken.
✓ Branch 79 taken 6 times.
✗ Branch 80 not taken.
✓ Branch 81 taken 6 times.
✗ Branch 82 not taken.
✓ Branch 83 taken 6 times.
✗ Branch 84 not taken.
✓ Branch 85 taken 6 times.
✗ Branch 86 not taken.
✓ Branch 87 taken 6 times.
✗ Branch 88 not taken.
✓ Branch 89 taken 6 times.
30 this%system = [ this%system, type_ptr ]
1379 class is (basis_type)
1380
2/2
✓ Branch 0 taken 36 times.
✓ Branch 1 taken 26 times.
88 do i = 1, size(type_ptr)
1381 62 call this%add_basis(type_ptr(i))
1382 end do
1383 class default
1384 write(stop_msg,*) "Invalid type for system" // &
1385 achar(13) // achar(10) // &
1386 1 "Expected type distribs_type or basis_type"
1387 1 call stop_program( stop_msg )
1388 1 return
1389 end select
1390 rank default
1391 write(stop_msg,*) "Invalid rank for system" // &
1392 achar(13) // achar(10) // &
1393 1 "Expected rank 0 or 1, got ", rank(rank_ptr)
1394 1 call stop_program( stop_msg )
1395 1 return
1396 end select
1397 32 call this%update_element_info()
1398 32 call this%update_bond_info()
1399
1400 end subroutine add
1401 !###############################################################################
1402
1403
1404 !###############################################################################
1405 40 subroutine add_basis(this, basis)
1406 !! Add a basis to the container.
1407 implicit none
1408
1409 ! Arguments
1410 class(distribs_container_type), intent(inout) :: this
1411 !! Parent. Instance of distribution functions container.
1412 type(basis_type), intent(in) :: basis
1413 !! Basis to add to the container.
1414
1415 ! Local variables
1416 40 type(distribs_type) :: system
1417 !! System to add to the container.
1418
1419 call system%calculate( &
1420 basis, &
1421 width = this%width, &
1422 sigma = this%sigma, &
1423 cutoff_min = this%cutoff_min, &
1424 cutoff_max = this%cutoff_max, &
1425 radius_distance_tol = this%radius_distance_tol &
1426 40 )
1427
1428
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 36 times.
40 if(.not.allocated(this%system))then
1429
27/78
✗ Branch 0 not taken.
✓ Branch 1 taken 4 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✓ Branch 4 taken 4 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 4 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 4 times.
✓ Branch 9 taken 4 times.
✗ 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 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 4 times.
✓ Branch 37 taken 4 times.
✓ Branch 38 taken 4 times.
✗ Branch 39 not taken.
✓ Branch 40 taken 4 times.
✗ Branch 41 not taken.
✓ Branch 42 taken 4 times.
✗ Branch 43 not taken.
✓ Branch 44 taken 4 times.
✗ Branch 45 not taken.
✓ Branch 46 taken 4 times.
✗ Branch 47 not taken.
✓ Branch 48 taken 4 times.
✗ Branch 49 not taken.
✓ Branch 50 taken 4 times.
✗ Branch 51 not taken.
✓ Branch 52 taken 4 times.
✗ Branch 53 not taken.
✓ Branch 54 taken 4 times.
✗ Branch 55 not taken.
✓ Branch 56 taken 4 times.
✗ Branch 57 not taken.
✓ Branch 58 taken 4 times.
✗ Branch 59 not taken.
✗ Branch 60 not taken.
✓ Branch 61 taken 4 times.
✗ Branch 62 not taken.
✓ Branch 63 taken 4 times.
✗ Branch 64 not taken.
✓ Branch 65 taken 4 times.
✗ Branch 66 not taken.
✓ Branch 67 taken 4 times.
✗ Branch 68 not taken.
✓ Branch 69 taken 4 times.
✗ Branch 70 not taken.
✓ Branch 71 taken 4 times.
✗ Branch 72 not taken.
✓ Branch 73 taken 4 times.
✗ Branch 74 not taken.
✓ Branch 75 taken 4 times.
✗ Branch 76 not taken.
✓ Branch 77 taken 4 times.
16 this%system = [ system ]
1430 else
1431
45/84
✗ Branch 0 not taken.
✓ Branch 1 taken 36 times.
✓ Branch 3 taken 25 times.
✓ Branch 4 taken 36 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 36 times.
✓ Branch 7 taken 61 times.
✓ Branch 8 taken 36 times.
✓ Branch 9 taken 61 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 61 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 61 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 61 times.
✗ Branch 16 not taken.
✓ Branch 17 taken 61 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 61 times.
✗ Branch 20 not taken.
✓ Branch 21 taken 61 times.
✗ Branch 22 not taken.
✓ Branch 23 taken 61 times.
✗ Branch 24 not taken.
✓ Branch 25 taken 61 times.
✗ Branch 26 not taken.
✓ Branch 27 taken 61 times.
✗ Branch 28 not taken.
✓ Branch 29 taken 36 times.
✗ Branch 30 not taken.
✗ Branch 31 not taken.
✓ Branch 32 taken 36 times.
✗ Branch 33 not taken.
✓ Branch 34 taken 36 times.
✗ Branch 35 not taken.
✗ Branch 36 not taken.
✗ Branch 37 not taken.
✗ Branch 38 not taken.
✓ Branch 39 taken 36 times.
✗ Branch 40 not taken.
✓ Branch 41 taken 25 times.
✓ Branch 42 taken 36 times.
✓ Branch 43 taken 25 times.
✗ Branch 44 not taken.
✓ Branch 45 taken 25 times.
✗ Branch 46 not taken.
✓ Branch 47 taken 25 times.
✗ Branch 48 not taken.
✓ Branch 49 taken 25 times.
✗ Branch 50 not taken.
✓ Branch 51 taken 25 times.
✗ Branch 52 not taken.
✓ Branch 53 taken 25 times.
✗ Branch 54 not taken.
✓ Branch 55 taken 25 times.
✗ Branch 56 not taken.
✓ Branch 57 taken 25 times.
✗ Branch 58 not taken.
✓ Branch 59 taken 25 times.
✗ Branch 60 not taken.
✓ Branch 61 taken 36 times.
✗ Branch 62 not taken.
✓ Branch 63 taken 61 times.
✓ Branch 64 taken 36 times.
✓ Branch 65 taken 61 times.
✓ Branch 66 taken 36 times.
✗ Branch 67 not taken.
✓ Branch 68 taken 61 times.
✗ Branch 69 not taken.
✓ Branch 70 taken 61 times.
✗ Branch 71 not taken.
✓ Branch 72 taken 61 times.
✗ Branch 73 not taken.
✓ Branch 74 taken 61 times.
✗ Branch 75 not taken.
✓ Branch 76 taken 61 times.
✗ Branch 77 not taken.
✓ Branch 78 taken 61 times.
✗ Branch 79 not taken.
✓ Branch 80 taken 61 times.
✗ Branch 81 not taken.
✓ Branch 82 taken 61 times.
✗ Branch 83 not taken.
✓ Branch 84 taken 61 times.
341 this%system = [ this%system, system ]
1432 end if
1433
9/18
✓ Branch 0 taken 40 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 40 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 40 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 40 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 40 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 40 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 40 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 40 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 40 times.
✗ Branch 17 not taken.
40 end subroutine add_basis
1434 !###############################################################################
1435
1436
1437 !###############################################################################
1438
1/2
✓ Branch 0 taken 9 times.
✗ Branch 1 not taken.
9 subroutine set_element_map(this, element_list)
1439 !! Set the element map for the container.
1440 implicit none
1441
1442 ! Arguments
1443 class(distribs_container_type), intent(inout) :: this
1444 !! Parent of the procedure. Instance of distribution functions container.
1445 character(3), dimension(:), intent(in) :: element_list
1446 !! Element information.
1447
1448 ! Local variables
1449 integer :: is
1450 !! Loop index.
1451 integer :: idx
1452 !! Index of the element in the element_info array.
1453 character(256) :: stop_msg
1454 !! Error message.
1455
1456
3/4
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 6 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 3 times.
9 if(allocated(this%element_map)) deallocate(this%element_map)
1457
7/14
✓ Branch 0 taken 9 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 9 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 9 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 9 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 9 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 9 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 9 times.
9 allocate(this%element_map(size(element_list)))
1458
2/2
✓ Branch 0 taken 11 times.
✓ Branch 1 taken 9 times.
20 do is = 1, size(element_list)
1459 idx = findloc( &
1460 [ this%element_info(:)%name ], element_list(is), dim=1 &
1461
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 11 times.
✓ Branch 3 taken 17 times.
✓ Branch 4 taken 11 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 11 times.
✓ Branch 7 taken 17 times.
✓ Branch 8 taken 11 times.
45 )
1462
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 11 times.
11 if(idx.eq.0)then
1463 write(stop_msg,*) "Element not found in element_info array" // &
1464 achar(13) // achar(10) // &
1465 "Element: ", element_list(is)
1466 call stop_program( stop_msg )
1467 return
1468 end if
1469 20 this%element_map(is) = idx
1470 end do
1471
1472 end subroutine set_element_map
1473 !###############################################################################
1474
1475
1476 !###############################################################################
1477 5 subroutine set_element_info(this)
1478 !! Set the list of elements for the container.
1479 implicit none
1480
1481 ! Arguments
1482 class(distribs_container_type), intent(inout) :: this
1483 !! Parent of the procedure. Instance of distribution functions container.
1484
1485 ! Local variables
1486 integer :: i
1487 !! Loop index.
1488 real(real32) :: radius
1489 !! Element radii.
1490 5 character(len=3), dimension(:), allocatable :: element_list
1491 !! List of elements in the container.
1492
1493
1494 !---------------------------------------------------------------------------
1495 ! get list of species in dataset
1496 !---------------------------------------------------------------------------
1497
3/6
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 5 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 5 times.
5 allocate(element_list(0))
1498
8/12
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
✓ Branch 3 taken 5 times.
✓ Branch 4 taken 5 times.
✓ Branch 5 taken 5 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 5 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 5 times.
✓ Branch 11 taken 5 times.
✓ Branch 12 taken 5 times.
15 element_list = [ this%system(1)%element_symbols ]
1499
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 5 times.
8 do i = 2, size(this%system),1
1500
14/20
✗ 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 8 taken 5 times.
✓ Branch 9 taken 3 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 3 times.
✓ Branch 12 taken 8 times.
✓ Branch 13 taken 3 times.
✓ Branch 14 taken 3 times.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✓ Branch 17 taken 3 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 3 times.
✓ Branch 20 taken 8 times.
✓ Branch 21 taken 3 times.
32 element_list = [ element_list, this%system(i)%element_symbols ]
1501 end do
1502 5 call set(element_list)
1503
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
5 if(allocated(this%element_info)) deallocate(this%element_info)
1504
1/10
✗ Branch 0 not taken.
✓ Branch 1 taken 5 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 8 not taken.
✗ Branch 9 not taken.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
5 if(.not.allocated(element_database)) allocate(element_database(0))
1505
9/16
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 5 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 5 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 5 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 5 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 5 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 5 times.
✓ Branch 17 taken 9 times.
✓ Branch 18 taken 5 times.
14 allocate(this%element_info(size(element_list)))
1506
2/2
✓ Branch 0 taken 9 times.
✓ Branch 1 taken 5 times.
14 do i = 1, size(element_list)
1507
7/10
✗ Branch 0 not taken.
✓ Branch 1 taken 9 times.
✓ Branch 3 taken 25 times.
✓ Branch 4 taken 9 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 9 times.
✓ Branch 7 taken 25 times.
✓ Branch 8 taken 9 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 9 times.
59 if( findloc( &
1508 [ element_database(:)%name ], element_list(i), dim=1 ) .lt. 1 )then
1509 call get_element_properties(element_list(i), radius=radius)
1510 element_database = [ &
1511 element_database(:), &
1512 element_type(name = element_list(i), radius = radius) &
1513 ]
1514 end if
1515 14 call this%element_info(i)%set(element_list(i))
1516 end do
1517
1518
1/2
✓ Branch 0 taken 5 times.
✗ Branch 1 not taken.
5 end subroutine set_element_info
1519 !###############################################################################
1520
1521
1522 !###############################################################################
1523 32 subroutine update_element_info(this)
1524 !! Update the element information in the container.
1525 implicit none
1526
1527 ! Arguments
1528 class(distribs_container_type), intent(inout) :: this
1529 !! Parent of the procedure. Instance of distribution functions container.
1530
1531 ! Local variables
1532 integer :: i
1533 !! Loop index.
1534 real(real32) :: radius
1535 !! Element radii.
1536 32 character(len=3), dimension(:), allocatable :: element_list
1537 !! List of elements in the container.
1538
1539
1540 !---------------------------------------------------------------------------
1541 ! check if element_info is allocated, if not, set it and return
1542 !---------------------------------------------------------------------------
1543
2/2
✓ Branch 0 taken 5 times.
✓ Branch 1 taken 27 times.
32 if(.not.allocated(this%element_info))then
1544 5 call this%set_element_info()
1545 5 return
1546
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 27 times.
27 elseif(size(this%element_info).eq.0)then
1547 call this%set_element_info()
1548 return
1549 end if
1550
1551
1552 !---------------------------------------------------------------------------
1553 ! get list of species in dataset
1554 !---------------------------------------------------------------------------
1555
3/6
✗ Branch 0 not taken.
✓ Branch 1 taken 27 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 27 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 27 times.
27 allocate(element_list(0))
1556
8/12
✗ Branch 0 not taken.
✓ Branch 1 taken 27 times.
✓ Branch 3 taken 29 times.
✓ Branch 4 taken 27 times.
✓ Branch 5 taken 27 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 27 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 27 times.
✓ Branch 11 taken 29 times.
✓ Branch 12 taken 27 times.
85 element_list = [ this%system(1)%element_symbols ]
1557
2/2
✓ Branch 0 taken 25 times.
✓ Branch 1 taken 27 times.
52 do i = 2, size(this%system),1
1558
14/20
✗ Branch 0 not taken.
✓ Branch 1 taken 25 times.
✓ Branch 3 taken 47 times.
✓ Branch 4 taken 25 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 25 times.
✓ Branch 8 taken 34 times.
✓ Branch 9 taken 25 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 25 times.
✓ Branch 12 taken 81 times.
✓ Branch 13 taken 25 times.
✓ Branch 14 taken 25 times.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✓ Branch 17 taken 25 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 25 times.
✓ Branch 20 taken 81 times.
✓ Branch 21 taken 25 times.
295 element_list = [ element_list, this%system(i)%element_symbols ]
1559 end do
1560 27 call set(element_list)
1561
1562
1563 !---------------------------------------------------------------------------
1564 ! check if all elements are in the element_info array
1565 !---------------------------------------------------------------------------
1566
1/10
✗ Branch 0 not taken.
✓ Branch 1 taken 27 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 8 not taken.
✗ Branch 9 not taken.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
27 if(.not.allocated(element_database)) allocate(element_database(0))
1567
2/2
✓ Branch 0 taken 43 times.
✓ Branch 1 taken 27 times.
70 do i = 1, size(element_list)
1568
7/10
✗ Branch 0 not taken.
✓ Branch 1 taken 43 times.
✓ Branch 3 taken 103 times.
✓ Branch 4 taken 43 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 43 times.
✓ Branch 7 taken 103 times.
✓ Branch 8 taken 43 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 43 times.
249 if(findloc( &
1569 [ element_database(:)%name ], &
1570 element_list(i), dim=1 ) .lt. 1 )then
1571 call get_element_properties(element_list(i), radius=radius)
1572 element_database = [ &
1573 element_database(:), &
1574 element_type(name = element_list(i), radius = radius) &
1575 ]
1576 end if
1577
8/10
✗ Branch 0 not taken.
✓ Branch 1 taken 43 times.
✓ Branch 3 taken 89 times.
✓ Branch 4 taken 43 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 43 times.
✓ Branch 7 taken 89 times.
✓ Branch 8 taken 43 times.
✓ Branch 10 taken 1 times.
✓ Branch 11 taken 42 times.
221 if( findloc( &
1578 [ this%element_info(:)%name ], &
1579 27 element_list(i), dim=1 ) .lt. 1 )then
1580 this%element_info = [ &
1581 this%element_info(:), &
1582 element_type(element_list(i)) &
1583
11/16
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
✓ Branch 3 taken 2 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 1 times.
✓ Branch 7 taken 3 times.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
✗ Branch 11 not taken.
✓ Branch 12 taken 1 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 1 times.
✓ Branch 15 taken 3 times.
✓ Branch 16 taken 1 times.
9 ]
1584 1 call this%element_info(size(this%element_info))%set(element_list(i))
1585 end if
1586 end do
1587
1588
2/2
✓ Branch 0 taken 27 times.
✓ Branch 1 taken 5 times.
32 end subroutine update_element_info
1589 !###############################################################################
1590
1591
1592 !###############################################################################
1593 15 subroutine add_to_element_info(this, element)
1594 !! Add an element to the element_info array.
1595 implicit none
1596
1597 ! Arguments
1598 class(distribs_container_type), intent(inout) :: this
1599 !! Parent of the procedure. Instance of distribution functions container.
1600 character(len=3), intent(in) :: element
1601 !! Element name.
1602
1603
1604
6/10
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 3 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 12 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 12 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 12 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 12 times.
15 if(.not.allocated(this%element_info)) allocate(this%element_info(0))
1605 this%element_info = [ &
1606 this%element_info(:), &
1607 element_type(element) &
1608
11/16
✗ Branch 0 not taken.
✓ Branch 1 taken 15 times.
✓ Branch 3 taken 4 times.
✓ Branch 4 taken 15 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 15 times.
✓ Branch 7 taken 19 times.
✓ Branch 8 taken 15 times.
✓ Branch 9 taken 15 times.
✗ Branch 10 not taken.
✗ Branch 11 not taken.
✓ Branch 12 taken 15 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 15 times.
✓ Branch 15 taken 19 times.
✓ Branch 16 taken 15 times.
57 ]
1609 15 call this%element_info(size(this%element_info))%set(element)
1610
1611 15 end subroutine add_to_element_info
1612 !###############################################################################
1613
1614
1615 !###############################################################################
1616 24 subroutine set_element_energy(this, element, energy)
1617 !! Set the energy of an element in the container.
1618 implicit none
1619
1620 ! Arguments
1621 class(distribs_container_type), intent(inout) :: this
1622 !! Parent of the procedure. Instance of distribution functions container.
1623 character(len=3), intent(in) :: element
1624 !! Element name.
1625 real(real32), intent(in) :: energy
1626 !! Energy of the element.
1627
1628 ! Local variables
1629 integer :: idx, idx_db
1630 !! Index of the element in the element_info array.
1631 real(real32) :: radius
1632 !! Element radius.
1633 character(len=3) :: element_
1634 !! Element name without null characters.
1635 logical :: in_element_info
1636 !! Boolean whether the element is in the element_info array.
1637
1638
1639 !---------------------------------------------------------------------------
1640 ! remove python formatting
1641 !---------------------------------------------------------------------------
1642 24 element_ = strip_null(element)
1643
1644
1645 !---------------------------------------------------------------------------
1646 ! if element_info is allocated, update energy of associated index
1647 !---------------------------------------------------------------------------
1648 24 in_element_info = .false.
1649
2/2
✓ Branch 0 taken 12 times.
✓ Branch 1 taken 12 times.
24 if(allocated(this%element_info))then
1650
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 12 times.
✓ Branch 3 taken 26 times.
✓ Branch 4 taken 12 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 12 times.
✓ Branch 7 taken 26 times.
✓ Branch 8 taken 12 times.
64 idx = findloc( [ this%element_info(:)%name ], element_, dim=1 )
1651
2/2
✓ Branch 0 taken 9 times.
✓ Branch 1 taken 3 times.
12 if(idx.ge.1)then
1652 9 this%element_info(idx)%energy = energy
1653 9 in_element_info = .true.
1654 end if
1655 end if
1656
1657
1658 !---------------------------------------------------------------------------
1659 ! if element_database is allocated, update energy of associated index
1660 !---------------------------------------------------------------------------
1661
6/10
✓ Branch 0 taken 6 times.
✓ Branch 1 taken 18 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 6 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 6 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 6 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 6 times.
24 if(.not.allocated(element_database)) allocate(element_database(0))
1662
7/8
✗ Branch 0 not taken.
✓ Branch 1 taken 24 times.
✓ Branch 3 taken 41 times.
✓ Branch 4 taken 24 times.
✓ Branch 5 taken 6 times.
✓ Branch 6 taken 18 times.
✓ Branch 7 taken 41 times.
✓ Branch 8 taken 24 times.
106 idx_db = findloc( [ element_database(:)%name ], element_, dim=1 )
1663
2/2
✓ Branch 0 taken 8 times.
✓ Branch 1 taken 16 times.
24 if(idx_db.lt.1)then
1664 8 call get_element_properties( element_, radius = radius )
1665 element_database = [ &
1666 element_database(:), &
1667 element_type(name = element_, energy = energy, radius = radius) &
1668
11/16
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
✓ Branch 3 taken 3 times.
✓ Branch 4 taken 8 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 8 times.
✓ Branch 7 taken 11 times.
✓ Branch 8 taken 8 times.
✓ Branch 9 taken 8 times.
✗ Branch 10 not taken.
✗ Branch 11 not taken.
✓ Branch 12 taken 8 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 8 times.
✓ Branch 15 taken 11 times.
✓ Branch 16 taken 8 times.
33 ]
1669 else
1670 16 element_database(idx_db)%energy = energy
1671 end if
1672
1673
1674 !---------------------------------------------------------------------------
1675 ! if element is not in element_info, add it to reserve_element_names
1676 !---------------------------------------------------------------------------
1677
2/2
✓ Branch 0 taken 15 times.
✓ Branch 1 taken 9 times.
24 if(.not.in_element_info) call this%add_to_element_info(element_)
1678
1679 24 end subroutine set_element_energy
1680 !###############################################################################
1681
1682
1683 !###############################################################################
1684
2/4
✓ Branch 0 taken 17 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 17 times.
✗ Branch 3 not taken.
17 subroutine set_element_energies(this, elements, energies)
1685 !! Set the energies of elements in the container.
1686 implicit none
1687
1688 ! Arguments
1689 class(distribs_container_type), intent(inout) :: this
1690 !! Parent of the procedure. Instance of distribution functions container.
1691 character(len=3), dimension(:), intent(in) :: elements
1692 !! Element names.
1693 real(real32), dimension(:), intent(in) :: energies
1694 !! Energies of the elements.
1695
1696 ! Local variables
1697 integer :: i
1698
1699
2/2
✓ Branch 0 taken 19 times.
✓ Branch 1 taken 17 times.
36 do i = 1, size(elements)
1700 36 call this%set_element_energy(elements(i), energies(i))
1701 end do
1702
1703 17 end subroutine set_element_energies
1704 !###############################################################################
1705
1706
1707 !###############################################################################
1708 1 subroutine get_element_energies(this, elements, energies)
1709 !! Return the energies of elements in the container.
1710 implicit none
1711
1712 ! Arguments
1713 class(distribs_container_type), intent(in) :: this
1714 !! Parent of the procedure. Instance of distribution functions container.
1715 character(len=3), dimension(:), allocatable, intent(out) :: elements
1716 !! Element names.
1717 real(real32), dimension(:), allocatable, intent(out) :: energies
1718 !! Energies of the elements.
1719
1720 ! Local variables
1721 integer :: i
1722 !! Loop index.
1723
1724
1725
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(elements(size(this%element_info)))
1726
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(energies(size(this%element_info)))
1727
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 do i = 1, size(this%element_info)
1728 1 elements(i) = this%element_info(i)%name
1729 2 energies(i) = this%element_info(i)%energy
1730 end do
1731
1732 1 end subroutine get_element_energies
1733 !###############################################################################
1734
1735
1736 !###############################################################################
1737 1 subroutine get_element_energies_staticmem(this, elements, energies)
1738 !! Return the energies of elements in the container.
1739 !!
1740 !! This subroutine is used when the memory for the output arrays is
1741 !! allocated outside of the subroutine. Used in Python interface.
1742 implicit none
1743
1744 ! Arguments
1745 class(distribs_container_type), intent(in) :: this
1746 !! Parent of the procedure. Instance of distribution functions container.
1747 character(len=3), dimension(size(this%element_info,1)), intent(out) :: &
1748 elements
1749 !! Element names.
1750 real(real32), dimension(size(this%element_info,1)), intent(out) :: energies
1751 !! Energies of the elements.
1752
1753 ! Local variables
1754 integer :: i
1755 !! Loop index.
1756
1757
1758
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 1 times.
2 do i = 1, size(this%element_info,1)
1759 1 elements(i) = this%element_info(i)%name
1760 2 energies(i) = this%element_info(i)%energy
1761 end do
1762
1763 1 end subroutine get_element_energies_staticmem
1764 !###############################################################################
1765
1766
1767 !###############################################################################
1768 35 subroutine set_bond_info(this)
1769 !! Set the 2-body bond information for the container.
1770 implicit none
1771
1772 ! Arguments
1773 class(distribs_container_type), intent(inout) :: this
1774 !! Parent of the procedure. Instance of distribution functions container.
1775
1776 ! Local variables
1777 integer :: i, j
1778 !! Loop index.
1779 integer :: num_elements, num_pairs
1780 !! Number of elements and pairs.
1781 logical :: success
1782 !! Success flag.
1783
1784
1785 !---------------------------------------------------------------------------
1786 ! allocate the bond information array
1787 !---------------------------------------------------------------------------
1788 35 num_elements = size(this%element_info)
1789 num_pairs = nint(gamma(real(num_elements + 2, real32)) / &
1790 35 ( gamma(real(num_elements, real32)) * gamma( 3._real32 ) ) )
1791
3/4
✓ Branch 0 taken 17 times.
✓ Branch 1 taken 18 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 17 times.
35 if(allocated(this%bond_info)) deallocate(this%bond_info)
1792
9/16
✓ Branch 0 taken 35 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 35 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 35 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 35 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 35 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 35 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 35 times.
✓ Branch 17 taken 89 times.
✓ Branch 18 taken 35 times.
124 allocate(this%bond_info(num_pairs))
1793
1794
1795 !---------------------------------------------------------------------------
1796 ! loop over all pairs of elements to set the bond information
1797 !---------------------------------------------------------------------------
1798 35 num_pairs = 0
1799
2/2
✓ Branch 0 taken 57 times.
✓ Branch 1 taken 35 times.
92 pair_loop1: do i = 1, num_elements
1800
2/2
✓ Branch 0 taken 89 times.
✓ Branch 1 taken 57 times.
181 pair_loop2: do j = i, num_elements
1801 89 num_pairs = num_pairs + 1
1802 call this%bond_info(num_pairs)%set( &
1803 this%element_info(i)%name, &
1804 this%element_info(j)%name, &
1805 success &
1806 89 )
1807
2/2
✓ Branch 0 taken 87 times.
✓ Branch 1 taken 2 times.
89 if(success) cycle pair_loop2
1808 call set_bond_radius_to_default( [ &
1809 this%element_info(i)%name, &
1810 this%element_info(j)%name &
1811
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 2 times.
6 ] )
1812 call this%bond_info(num_pairs)%set( &
1813 this%element_info(i)%name, &
1814 this%element_info(j)%name, &
1815 success &
1816 59 )
1817 end do pair_loop2
1818 end do pair_loop1
1819
1820 35 end subroutine set_bond_info
1821 !###############################################################################
1822
1823
1824 !###############################################################################
1825 2 subroutine set_bond_radius_to_default(elements)
1826 !! Set the bond radius to the default value.
1827 !!
1828 !! The default value is the average of the covalent radii of the elements.
1829 implicit none
1830
1831 ! Arguments
1832 character(len=3), dimension(2), intent(in) :: elements
1833 !! Element symbols.
1834
1835 ! Local variables
1836 integer :: idx1, idx2
1837 !! Index of the elements in the element database.
1838 real(real32) :: radius, radius1, radius2
1839 !! Average of covalent radii.
1840 character(256) :: warn_msg
1841
1842
1843 write(warn_msg,'("No bond data for element pair ",A," and ",A)') &
1844 2 elements(1), elements(2)
1845 warn_msg = trim(warn_msg) // &
1846 achar(13) // achar(10) // &
1847
2/4
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
✓ Branch 6 taken 2 times.
✗ Branch 7 not taken.
2 "Setting bond to average of covalent radii"
1848 2 call print_warning(warn_msg)
1849
1/10
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 8 not taken.
✗ Branch 9 not taken.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
2 if(.not.allocated(element_database)) allocate(element_database(0))
1850 idx1 = findloc([ element_database(:)%name ], &
1851
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✓ Branch 3 taken 6 times.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 2 times.
✓ Branch 7 taken 6 times.
✓ Branch 8 taken 2 times.
14 elements(1), dim=1)
1852
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
2 if(idx1.lt.1)then
1853 call get_element_properties(elements(1), radius=radius1)
1854 element_database = [ element_database, &
1855 element_type(name=elements(1), radius=radius1) ]
1856 idx1 = size(element_database)
1857 end if
1858 idx2 = findloc([ element_database(:)%name ], &
1859
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✓ Branch 3 taken 6 times.
✓ Branch 4 taken 2 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 2 times.
✓ Branch 7 taken 6 times.
✓ Branch 8 taken 2 times.
14 elements(2), dim=1)
1860
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
2 if(idx2.lt.1)then
1861 call get_element_properties(elements(2), radius=radius2)
1862 element_database = [ element_database, &
1863 element_type(name=elements(2), radius=radius2) ]
1864 idx2 = size(element_database)
1865 end if
1866 radius = ( element_database(idx1)%radius + &
1867 2 element_database(idx2)%radius ) / 2._real32
1868
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
2 if(.not.allocated(element_bond_database)) &
1869 allocate(element_bond_database(0))
1870 element_bond_database = [ element_bond_database, &
1871 element_bond_type(elements=[ &
1872 elements(1), &
1873 elements(2) &
1874 ], radius=radius) &
1875
13/18
✗ Branch 0 not taken.
✓ Branch 1 taken 2 times.
✓ Branch 3 taken 9 times.
✓ Branch 4 taken 2 times.
✓ Branch 5 taken 4 times.
✓ Branch 6 taken 2 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 2 times.
✓ Branch 9 taken 11 times.
✓ Branch 10 taken 2 times.
✓ Branch 11 taken 2 times.
✗ Branch 12 not taken.
✗ Branch 13 not taken.
✓ Branch 14 taken 2 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 2 times.
✓ Branch 17 taken 11 times.
✓ Branch 18 taken 2 times.
37 ]
1876 call sort_str( &
1877 element_bond_database(size(element_bond_database))%element &
1878 2 )
1879
1880 2 end subroutine set_bond_radius_to_default
1881 !###############################################################################
1882
1883
1884 !###############################################################################
1885 42 subroutine update_bond_info(this)
1886 !! Update the element information in the container.
1887 implicit none
1888
1889 ! Arguments
1890 class(distribs_container_type), intent(inout) :: this
1891 !! Parent of the procedure. Instance of distribution functions container.
1892
1893 ! Local variables
1894 integer :: i, j, k, is, js
1895 !! Loop index.
1896 real(real32) :: radius, radius1, radius2
1897 !! Average of covalent radii.
1898 42 character(len=3), dimension(:), allocatable :: element_list
1899 !! List of elements in the container.
1900 42 character(len=3), dimension(:,:), allocatable :: pair_list
1901 !! List of element pairs in the container.
1902
1903
1904 !---------------------------------------------------------------------------
1905 ! check if bond_info is allocated, if not, set it and return
1906 !---------------------------------------------------------------------------
1907
2/2
✓ Branch 0 taken 18 times.
✓ Branch 1 taken 24 times.
42 if(.not.allocated(this%bond_info))then
1908 18 call this%set_bond_info()
1909 18 return
1910
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 24 times.
24 elseif(size(this%bond_info).eq.0)then
1911 call this%set_bond_info()
1912 return
1913 end if
1914
1915
1916 !---------------------------------------------------------------------------
1917 ! get list of element pairs in dataset
1918 !---------------------------------------------------------------------------
1919
3/6
✗ Branch 0 not taken.
✓ Branch 1 taken 24 times.
✗ Branch 3 not taken.
✓ Branch 4 taken 24 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 24 times.
24 allocate(element_list(0))
1920
8/12
✗ Branch 0 not taken.
✓ Branch 1 taken 24 times.
✓ Branch 3 taken 24 times.
✓ Branch 4 taken 24 times.
✓ Branch 5 taken 24 times.
✗ Branch 6 not taken.
✗ Branch 7 not taken.
✓ Branch 8 taken 24 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 24 times.
✓ Branch 11 taken 24 times.
✓ Branch 12 taken 24 times.
72 element_list = [ this%system(1)%element_symbols ]
1921
2/2
✓ Branch 0 taken 39 times.
✓ Branch 1 taken 24 times.
63 do i = 2, size(this%system),1
1922
14/20
✗ Branch 0 not taken.
✓ Branch 1 taken 39 times.
✓ Branch 3 taken 72 times.
✓ Branch 4 taken 39 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 39 times.
✓ Branch 8 taken 54 times.
✓ Branch 9 taken 39 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 39 times.
✓ Branch 12 taken 126 times.
✓ Branch 13 taken 39 times.
✓ Branch 14 taken 39 times.
✗ Branch 15 not taken.
✗ Branch 16 not taken.
✓ Branch 17 taken 39 times.
✗ Branch 18 not taken.
✓ Branch 19 taken 39 times.
✓ Branch 20 taken 126 times.
✓ Branch 21 taken 39 times.
441 element_list = [ element_list, this%system(i)%element_symbols ]
1923 end do
1924 24 call set(element_list)
1925
8/16
✓ Branch 0 taken 24 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 24 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 24 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 24 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 24 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 24 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 24 times.
✗ Branch 16 not taken.
✓ Branch 17 taken 24 times.
24 allocate(pair_list(triangular_number(size(element_list)),2))
1926 24 k = 0
1927
2/2
✓ Branch 0 taken 46 times.
✓ Branch 1 taken 24 times.
70 do i = 1, size(element_list)
1928
2/2
✓ Branch 0 taken 79 times.
✓ Branch 1 taken 46 times.
149 do j = i, size(element_list)
1929 79 k = k + 1
1930
2/2
✓ Branch 0 taken 158 times.
✓ Branch 1 taken 79 times.
237 pair_list(k,:) = [ element_list(i), element_list(j) ]
1931 125 call sort_str(pair_list(k,:))
1932 end do
1933 end do
1934
1935 !---------------------------------------------------------------------------
1936 ! check if all element pairs are in the database
1937 !---------------------------------------------------------------------------
1938
1/10
✗ Branch 0 not taken.
✓ Branch 1 taken 24 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✗ Branch 8 not taken.
✗ Branch 9 not taken.
✗ Branch 11 not taken.
✗ Branch 12 not taken.
24 if(.not.allocated(element_bond_database)) allocate(element_bond_database(0))
1939
2/2
✓ Branch 0 taken 79 times.
✓ Branch 1 taken 24 times.
103 pair_loop1: do i = 1, size(pair_list,1)
1940
1/2
✓ Branch 0 taken 244 times.
✗ Branch 1 not taken.
244 do j = 1, size(element_bond_database)
1941 if( ( &
1942 element_bond_database(j)%element(1) .eq. pair_list(i,1) .and. &
1943 element_bond_database(j)%element(2) .eq. pair_list(i,2) &
1944
2/2
✓ Branch 0 taken 79 times.
✓ Branch 1 taken 165 times.
244 ) .or. ( &
1945 element_bond_database(j)%element(1) .eq. pair_list(i,2) .and. &
1946 element_bond_database(j)%element(2) .eq. pair_list(i,1) &
1947 79 ) ) cycle pair_loop1
1948 end do
1949 ! if not found, add to the database
1950 is = findloc([ this%element_info(:)%name ], pair_list(i,1), dim=1)
1951 js = findloc([ this%element_info(:)%name ], pair_list(i,2), dim=1)
1952 radius1 = this%element_info(is)%radius
1953 if(radius1.le.1.E-6) &
1954 call get_element_properties(pair_list(i,1), radius = radius1)
1955 radius2 = this%element_info(js)%radius
1956 if(radius2.le.1.E-6) &
1957 call get_element_properties(pair_list(i,2), radius = radius2)
1958 radius = ( radius1 + radius2 ) / 2._real32
1959 element_bond_database = [ element_bond_database, &
1960 element_bond_type(elements=[pair_list(i,:)], radius=radius) ]
1961 24 call sort_str(element_bond_database(size(element_bond_database))%element)
1962 end do pair_loop1
1963
1964
1965 ! --------------------------------------------------------------------------
1966 ! check if all element pairs are in the bond_info array
1967 ! --------------------------------------------------------------------------
1968
2/2
✓ Branch 0 taken 79 times.
✓ Branch 1 taken 24 times.
103 pair_loop2: do i = 1, size(pair_list,1)
1969
2/2
✓ Branch 0 taken 241 times.
✓ Branch 1 taken 3 times.
244 info_loop: do j = 1, size(this%bond_info)
1970 if( ( &
1971 this%bond_info(j)%element(1) .eq. pair_list(i,1) .and. &
1972 this%bond_info(j)%element(2) .eq. pair_list(i,2) &
1973
2/2
✓ Branch 0 taken 76 times.
✓ Branch 1 taken 165 times.
241 ) .or. ( &
1974 this%bond_info(j)%element(1) .eq. pair_list(i,2) .and. &
1975 this%bond_info(j)%element(2) .eq. pair_list(i,1) &
1976 79 ) ) cycle pair_loop2
1977 end do info_loop
1978 this%bond_info = [ &
1979 this%bond_info(:), &
1980 element_bond_type( [ pair_list(i,1:2) ] ) &
1981
15/20
✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
✓ Branch 3 taken 12 times.
✓ Branch 4 taken 3 times.
✓ Branch 5 taken 6 times.
✓ Branch 6 taken 3 times.
✓ Branch 7 taken 6 times.
✓ Branch 8 taken 3 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 3 times.
✓ Branch 11 taken 15 times.
✓ Branch 12 taken 3 times.
✓ Branch 13 taken 3 times.
✗ Branch 14 not taken.
✗ Branch 15 not taken.
✓ Branch 16 taken 3 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 3 times.
✓ Branch 19 taken 15 times.
✓ Branch 20 taken 3 times.
57 ]
1982 call this%bond_info(size(this%bond_info))%set( &
1983 pair_list(i,1), &
1984 27 pair_list(i,2) )
1985 end do pair_loop2
1986
1987
4/4
✓ Branch 0 taken 24 times.
✓ Branch 1 taken 18 times.
✓ Branch 2 taken 24 times.
✓ Branch 3 taken 18 times.
42 end subroutine update_bond_info
1988 !###############################################################################
1989
1990
1991 !###############################################################################
1992 3 subroutine set_bond_radius(this, elements, radius)
1993 !! Set the bond radius for a pair of elements in the container.
1994 implicit none
1995
1996 ! Arguments
1997 class(distribs_container_type), intent(inout) :: this
1998 !! Parent of the procedure. Instance of distribution functions container.
1999 character(len=3), dimension(2), intent(in) :: elements
2000 !! Element name.
2001 real(real32), intent(in) :: radius
2002 !! Bond radius.
2003
2004 ! Local variables
2005 integer :: idx, i
2006 !! Index of the bond in the bond_info array.
2007 character(len=3) :: element_1, element_2
2008 !! Element names.
2009
2010
2011 !---------------------------------------------------------------------------
2012 ! remove python formatting
2013 !---------------------------------------------------------------------------
2014 3 element_1 = strip_null(elements(1))
2015 3 element_2 = strip_null(elements(2))
2016
2017
2018 !---------------------------------------------------------------------------
2019 ! if bond_info is allocated, update radius of associated index
2020 !---------------------------------------------------------------------------
2021
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 2 times.
3 if(allocated(this%bond_info))then
2022 1 idx = this%get_pair_index(element_1, element_2)
2023
1/2
✓ Branch 0 taken 1 times.
✗ Branch 1 not taken.
1 if(idx.ge.1) this%bond_info(idx)%radius_covalent = radius
2024 end if
2025
2026
2027 !---------------------------------------------------------------------------
2028 ! if element_bond_database is allocated, update radius of associated index
2029 !---------------------------------------------------------------------------
2030
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
3 if(.not.allocated(element_bond_database))then
2031 allocate(element_bond_database(1))
2032 element_bond_database(1)%element = [ element_1, element_2 ]
2033 call sort_str(element_bond_database(1)%element)
2034 element_bond_database(1)%radius_covalent = radius
2035 3 return
2036 end if
2037
1/2
✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
3 do i = 1, size(element_bond_database)
2038 if( ( &
2039 element_bond_database(i)%element(1) .eq. element_1 .and. &
2040 element_bond_database(i)%element(2) .eq. element_2 &
2041
1/2
✓ Branch 0 taken 3 times.
✗ Branch 1 not taken.
3 ) .or. ( &
2042 element_bond_database(i)%element(1) .eq. element_2 .and. &
2043 element_bond_database(i)%element(2) .eq. element_1 &
2044 ) )then
2045 3 element_bond_database(i)%radius_covalent = radius
2046 3 return
2047 end if
2048 end do
2049 ! if allocated and not found, add to the database
2050 element_bond_database = [ element_bond_database, &
2051 element_bond_type([ element_1, element_2 ], radius) ]
2052 call sort_str(element_bond_database(size(element_bond_database))%element)
2053
2054 end subroutine set_bond_radius
2055 !###############################################################################
2056
2057
2058 !###############################################################################
2059
2/4
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
✓ Branch 2 taken 2 times.
✗ Branch 3 not taken.
2 subroutine set_bond_radii(this, elements, radii)
2060 !! Set the bond radii for a pair of elements in the container.
2061 implicit none
2062
2063 ! Arguments
2064 class(distribs_container_type), intent(inout) :: this
2065 !! Parent of the procedure. Instance of distribution functions container.
2066 character(len=3), dimension(:,:), intent(in) :: elements
2067 !! Element names.
2068 real(real32), dimension(:), intent(in) :: radii
2069 !! Bond radii.
2070
2071 ! Local variables
2072 integer :: i
2073 !! Loop index.
2074
2075
2076
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 2 times.
4 do i = 1, size(elements,1)
2077
1/2
✗ Branch 2 not taken.
✓ Branch 3 taken 2 times.
4 call this%set_bond_radius(elements(i,:), radii(i))
2078 end do
2079
2080 2 end subroutine set_bond_radii
2081 !###############################################################################
2082
2083
2084 !###############################################################################
2085 2 subroutine get_bond_radii(this, elements, radii)
2086 !! Return the bond radii of elements in the container.
2087 implicit none
2088
2089 ! Arguments
2090 class(distribs_container_type), intent(in) :: this
2091 !! Parent of the procedure. Instance of distribution functions container.
2092 character(len=3), dimension(:,:), allocatable, intent(out) :: elements
2093 !! Element pair names.
2094 real(real32), dimension(:), allocatable, intent(out) :: radii
2095 !! Radii of the bond pairs.
2096
2097 ! Local variables
2098 integer :: i
2099 !! Loop index.
2100
2101
2102
8/16
✓ 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 10 not taken.
✓ Branch 11 taken 2 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 2 times.
✗ Branch 16 not taken.
✓ Branch 17 taken 2 times.
2 allocate(elements(size(this%bond_info),2))
2103
7/14
✓ 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.
2 allocate(radii(size(this%bond_info)))
2104
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 2 times.
4 do i = 1, size(this%bond_info)
2105
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 2 times.
6 elements(i,:) = this%bond_info(i)%element
2106 4 radii(i) = this%bond_info(i)%radius_covalent
2107 end do
2108
2109 2 end subroutine get_bond_radii
2110 !###############################################################################
2111
2112
2113 !###############################################################################
2114 2 subroutine get_bond_radii_staticmem(this, elements, radii)
2115 !! Return the energies of elements in the container.
2116 !!
2117 !! This subroutine is used when the memory for the output arrays is
2118 !! allocated outside of the subroutine. Used in Python interface.
2119 implicit none
2120
2121 ! Arguments
2122 class(distribs_container_type), intent(in) :: this
2123 !! Parent of the procedure. Instance of distribution functions container.
2124 character(len=3), dimension(size(this%bond_info,1),2), intent(out) :: &
2125 elements
2126 !! Element pair names.
2127 real(real32), dimension(size(this%bond_info,1)), intent(out) :: radii
2128 !! Radii of the bond pairs.
2129
2130 ! Local variables
2131 integer :: i
2132 !! Loop index.
2133
2134
2135
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 2 times.
4 do i = 1, size(this%bond_info)
2136
2/2
✓ Branch 0 taken 4 times.
✓ Branch 1 taken 2 times.
6 elements(i,:) = this%bond_info(i)%element
2137 4 radii(i) = this%bond_info(i)%radius_covalent
2138 end do
2139
2140 2 end subroutine get_bond_radii_staticmem
2141 !###############################################################################
2142
2143
2144 !###############################################################################
2145 25 subroutine set_best_energy(this)
2146 !! Set the best energy in the container.
2147 implicit none
2148
2149 ! Arguments
2150 class(distribs_container_type), intent(inout) :: this
2151 !! Parent of the procedure. Instance of distribution functions container.
2152
2153 ! Local variables
2154 integer :: i, j, is, js, idx1, idx2
2155 !! Loop index.
2156 real(real32) :: energy, energy_per_species, energy_pair
2157 !! Energy of the system.
2158 25 integer, dimension(:,:), allocatable :: idx_list
2159 !! Index list for pairs of elements.
2160 character(len=256) :: warn_msg
2161 !! Warning message.
2162
2163
2/2
✓ Branch 0 taken 17 times.
✓ Branch 1 taken 8 times.
25 if(.not.allocated(this%best_energy_pair))then
2164 allocate( &
2165 this%best_energy_pair(size(this%bond_info,1)), &
2166 source = 0._real32 &
2167
9/16
✓ Branch 0 taken 17 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 17 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 17 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 17 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 17 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 17 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 17 times.
✓ Branch 16 taken 49 times.
✓ Branch 17 taken 17 times.
66 )
2168
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 7 times.
8 elseif(size(this%best_energy_pair).ne.size(this%bond_info))then
2169
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 deallocate(this%best_energy_pair)
2170 allocate( &
2171 this%best_energy_pair(size(this%bond_info,1)), &
2172 source = 0._real32 &
2173
9/16
✓ 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 13 not taken.
✓ Branch 14 taken 1 times.
✓ Branch 16 taken 6 times.
✓ Branch 17 taken 1 times.
7 )
2174 end if
2175
2176
2/2
✓ Branch 0 taken 17 times.
✓ Branch 1 taken 8 times.
25 if(.not.allocated(this%best_energy_per_species))then
2177 allocate( &
2178 this%best_energy_per_species(size(this%element_info,1)), &
2179 source = 0._real32 &
2180
9/16
✓ Branch 0 taken 17 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 17 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 17 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 17 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 17 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 17 times.
✗ Branch 13 not taken.
✓ Branch 14 taken 17 times.
✓ Branch 16 taken 30 times.
✓ Branch 17 taken 17 times.
47 )
2181
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 7 times.
8 elseif(size(this%best_energy_per_species).ne.size(this%element_info))then
2182
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 deallocate(this%best_energy_per_species)
2183 allocate( &
2184 this%best_energy_per_species(size(this%element_info,1)), &
2185 source = 0._real32 &
2186
9/16
✓ 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 13 not taken.
✓ Branch 14 taken 1 times.
✓ Branch 16 taken 3 times.
✓ Branch 17 taken 1 times.
4 )
2187 end if
2188
2189
2/2
✓ Branch 0 taken 45 times.
✓ Branch 1 taken 25 times.
70 do i = 1, size(this%system)
2190 45 j = 0
2191 allocate( idx_list( &
2192 size(this%system(i)%element_symbols), &
2193 size(this%system(i)%element_symbols) &
2194
9/18
✓ Branch 0 taken 45 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 45 times.
✓ Branch 4 taken 45 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 45 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 45 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 45 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 45 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 45 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 45 times.
45 ) )
2195
2/2
✓ Branch 0 taken 58 times.
✓ Branch 1 taken 45 times.
103 do is = 1, size(this%system(i)%element_symbols)
2196
2/2
✓ Branch 0 taken 72 times.
✓ Branch 1 taken 58 times.
175 do js = is, size(this%system(i)%element_symbols), 1
2197 72 j = j + 1
2198 72 idx_list(is,js) = j
2199 130 idx_list(js,is) = j
2200 end do
2201 end do
2202
2203 45 energy = this%system(i)%energy
2204
2/2
✓ Branch 0 taken 58 times.
✓ Branch 1 taken 45 times.
103 do is = 1, size(this%system(i)%element_symbols)
2205 idx1 = findloc( &
2206 [ this%element_info(:)%name ], &
2207 this%system(i)%element_symbols(is), &
2208 dim = 1 &
2209
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 58 times.
✓ Branch 3 taken 129 times.
✓ Branch 4 taken 58 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 58 times.
✓ Branch 7 taken 129 times.
✓ Branch 8 taken 58 times.
316 )
2210
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 58 times.
58 if(idx1.lt.1)then
2211 call stop_program( "Species not found in element_info" )
2212 return
2213 end if
2214 energy = energy - &
2215 103 this%system(i)%stoichiometry(is) * this%element_info(idx1)%energy
2216 end do
2217 45 energy = energy / this%system(i)%num_atoms
2218
2219
2/2
✓ Branch 0 taken 58 times.
✓ Branch 1 taken 45 times.
103 do is = 1, size(this%system(i)%element_symbols)
2220
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 58 times.
58 if(this%system(i)%num_per_species(is).eq.0)then
2221 write(warn_msg, &
2222 '("No neighbours found for species ",A," (",I0,") &
2223 &in system ",I0)' &
2224 ) trim(this%system(i)%element_symbols(is)), is, i
2225 call print_warning(warn_msg)
2226 cycle
2227 end if
2228 idx1 = findloc( &
2229 [ this%element_info(:)%name ], &
2230 this%system(i)%element_symbols(is), &
2231 dim = 1 &
2232
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 58 times.
✓ Branch 3 taken 129 times.
✓ Branch 4 taken 58 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 58 times.
✓ Branch 7 taken 129 times.
✓ Branch 8 taken 58 times.
316 )
2233 energy_per_species = &
2234 energy * this%system(i)%weight_per_species(is) / &
2235
2/2
✓ Branch 0 taken 86 times.
✓ Branch 1 taken 58 times.
144 real( sum( this%system(i)%num_per_species(:) ), real32 )
2236
2237
2/2
✓ Branch 0 taken 10 times.
✓ Branch 1 taken 48 times.
58 if( energy_per_species .lt. this%best_energy_per_species(idx1) )then
2238 10 this%best_energy_per_species(idx1) = energy_per_species
2239 end if
2240
2/2
✓ Branch 0 taken 58 times.
✓ Branch 1 taken 86 times.
189 do js = 1, size(this%system(i)%element_symbols)
2241 idx2 = findloc( &
2242 [ this%element_info(:)%name ], &
2243 this%system(i)%element_symbols(js), &
2244 dim = 1 &
2245
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 86 times.
✓ Branch 3 taken 213 times.
✓ Branch 4 taken 86 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 86 times.
✓ Branch 7 taken 213 times.
✓ Branch 8 taken 86 times.
512 )
2246 j = nint( &
2247 ( &
2248 size(this%element_info) - &
2249 min( idx1, idx2 ) / 2._real32 &
2250 ) * ( min( idx1, idx2 ) - 1._real32 ) + max( idx1, idx2 ) &
2251 86 )
2252
2253 energy_pair = &
2254 energy * this%system(i)%weight_pair(idx_list(is,js)) / &
2255
2/2
✓ Branch 0 taken 148 times.
✓ Branch 1 taken 86 times.
234 real( sum( this%system(i)%num_per_species(:) ), real32 )
2256
2257
2/2
✓ Branch 0 taken 14 times.
✓ Branch 1 taken 72 times.
144 if( energy_pair .lt. this%best_energy_pair(j) )then
2258 14 this%best_energy_pair(j) = energy_pair
2259 end if
2260
2261 end do
2262 end do
2263
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 45 times.
45 deallocate(idx_list)
2264
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 45 times.
70 if( this%best_energy_pair(j) .lt. -1.E1 )then
2265 write(warn_msg, &
2266 '("Best energy pair is less than -10 eV, &
2267 &this is likely to be unphysical. Check the energy values.")' &
2268 )
2269 call print_warning(warn_msg)
2270 end if
2271
2272 end do
2273
2274
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 25 times.
25 end subroutine set_best_energy
2275 !###############################################################################
2276
2277
2278 !###############################################################################
2279 17886882 pure function get_pair_index(this, species1, species2) result(idx)
2280 !! Get the index of a pair of elements in the container.
2281 implicit none
2282
2283 ! Arguments
2284 class(distribs_container_type), intent(in) :: this
2285 !! Parent of the procedure. Instance of distribution functions container.
2286 character(len=3), intent(in) :: species1, species2
2287 !! Element names.
2288 integer :: idx
2289 !! Index of the pair in the bond_info array.
2290
2291 ! Local variables
2292 integer :: is, js
2293 !! Index of the elements in the element_info array.
2294
2295
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 17886882 times.
✓ Branch 3 taken 52945302 times.
✓ Branch 4 taken 17886882 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 17886882 times.
✓ Branch 7 taken 52945302 times.
✓ Branch 8 taken 17886882 times.
123777486 is = findloc([ this%element_info(:)%name ], species1, dim=1)
2296
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 17886882 times.
✓ Branch 3 taken 52945302 times.
✓ Branch 4 taken 17886882 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 17886882 times.
✓ Branch 7 taken 52945302 times.
✓ Branch 8 taken 17886882 times.
123777486 js = findloc([ this%element_info(:)%name ], species2, dim=1)
2297 !! This comes from subtraction of nth triangular numbers
2298 !! nth triangular number: N_n = n(n+1)/2 = ( n^2 + n ) / 2
2299 !! idx = N_n - N_{n-is+1} + ( js - is + 1)
2300 !! idx = ( n - is/2 ) * ( is - 1 ) + js
2301 !idx = nint( ( size(this%element_info) - min( is, js ) / 2._real32 ) * &
2302 ! ( is - 1._real32 ) + js )
2303 idx = nint( ( size(this%element_info) - min( is, js ) / 2._real32 ) * &
2304 17886882 ( min( is, js ) - 1._real32 ) + max( is, js ) )
2305
2306 17886882 end function get_pair_index
2307 !###############################################################################
2308
2309
2310 !###############################################################################
2311 1 pure function get_element_index(this, species) result(idx)
2312 !! Get the index of an element in the container.
2313 implicit none
2314
2315 ! Arguments
2316 class(distribs_container_type), intent(in) :: this
2317 !! Parent of the procedure. Instance of distribution functions container.
2318 character(len=3), intent(in) :: species
2319 !! Element name.
2320 integer :: idx
2321 !! Index of the element in the element_info array.
2322
2323
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 idx = findloc([ this%element_info(:)%name ], species, dim=1)
2324
2325 1 end function get_element_index
2326 !###############################################################################
2327
2328
2329 !###############################################################################
2330 27 subroutine set_num_bins(this)
2331 !! Set the number of bins for the n-body distribution functions.
2332 implicit none
2333
2334 ! Arguments
2335 class(distribs_container_type), intent(inout) :: this
2336 !! Parent of the procedure. Instance of distribution functions container.
2337
2338 ! Local variables
2339 integer :: i
2340 !! Loop index.
2341
2342
2/2
✓ Branch 0 taken 81 times.
✓ Branch 1 taken 27 times.
108 do i = 1, 3
2343
2/2
✓ Branch 0 taken 38 times.
✓ Branch 1 taken 43 times.
81 if(this%nbins(i).eq.-1)then
2344 this%nbins(i) = 1 + &
2345 nint( &
2346 ( this%cutoff_max(i) - this%cutoff_min(i) ) / &
2347 this%width(i) &
2348 38 )
2349 end if
2350 this%width_inv(i) = ( this%nbins(i) - 1 ) / &
2351 108 ( this%cutoff_max(i) - this%cutoff_min(i) )
2352 end do
2353
2354 27 end subroutine set_num_bins
2355 !###############################################################################
2356
2357
2358 !###############################################################################
2359 289517616 pure function get_bin(this, value, dim) result(bin)
2360 !! Get the bin index for a value in a dimension.
2361 implicit none
2362
2363 ! Arguments
2364 class(distribs_container_type), intent(in) :: this
2365 !! Parent of the procedure. Instance of distribution functions container.
2366 real(real32), intent(in) :: value
2367 !! Value to get the bin index for.
2368 integer, intent(in) :: dim
2369 !! Dimension to get the bin index for.
2370 integer :: bin
2371 !! Bin index for the value.
2372
2373 ! Local variables
2374 real(real32) :: min_val, width_inv
2375 !! Temporary variables.
2376
2377 ! Prefetch frequently accessed values
2378 289517616 min_val = this%cutoff_min(dim)
2379 289517616 width_inv = this%width_inv(dim)
2380
2381 ! Calculate bin using optimized operations
2382 289517616 bin = nint((value - min_val) * width_inv) + 1
2383
2384 ! Ensure bin stays within bounds (floating point safety)
2385 289517616 bin = min(max(bin, 1), this%nbins(dim))
2386
2387 289517616 end function get_bin
2388 !###############################################################################
2389
2390
2391 !###############################################################################
2392 17 subroutine initialise_gdfs(this)
2393 !! Initialise the distribution functions for the container.
2394 implicit none
2395
2396 ! Arguments
2397 class(distribs_container_type), intent(inout) :: this
2398 !! Parent of the procedure. Instance of distribution functions container.
2399
2400 ! Local variables
2401 integer :: num_pairs
2402 !! Number of pairs.
2403
2404
2405 num_pairs = nint( gamma(real(size(this%element_info) + 2, real32)) / &
2406 17 ( gamma(real(size(this%element_info), real32)) * gamma( 3._real32 ) ) )
2407 allocate(this%gdf%df_2body(this%nbins(1),num_pairs), &
2408
13/22
✓ Branch 0 taken 17 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 17 times.
✓ Branch 4 taken 17 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 17 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 17 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 17 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 17 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 17 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 17 times.
✓ Branch 20 taken 49 times.
✓ Branch 21 taken 17 times.
✓ Branch 22 taken 9674 times.
✓ Branch 23 taken 49 times.
9740 source = 0._real32 )
2409 allocate(this%gdf%df_3body(this%nbins(2),size(this%element_info)), &
2410
13/22
✓ Branch 0 taken 17 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 17 times.
✓ Branch 4 taken 17 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 17 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 17 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 17 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 17 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 17 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 17 times.
✓ Branch 20 taken 30 times.
✓ Branch 21 taken 17 times.
✓ Branch 22 taken 2362 times.
✓ Branch 23 taken 30 times.
2409 source = 0._real32 )
2411 allocate(this%gdf%df_4body(this%nbins(3),size(this%element_info)), &
2412
13/22
✓ Branch 0 taken 17 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 17 times.
✓ Branch 4 taken 17 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 17 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 17 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 17 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 17 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 17 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 17 times.
✓ Branch 20 taken 30 times.
✓ Branch 21 taken 17 times.
✓ Branch 22 taken 2362 times.
✓ Branch 23 taken 30 times.
2409 source = 0._real32 )
2413
9/16
✓ Branch 0 taken 17 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 17 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 17 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 17 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 17 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 17 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 17 times.
✓ Branch 17 taken 49 times.
✓ Branch 18 taken 17 times.
66 allocate(this%in_dataset_2body(num_pairs), source = .false. )
2414
9/16
✓ Branch 0 taken 17 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 17 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 17 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 17 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 17 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 17 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 17 times.
✓ Branch 17 taken 30 times.
✓ Branch 18 taken 17 times.
47 allocate(this%in_dataset_3body(size(this%element_info)), source = .false. )
2415
9/16
✓ Branch 0 taken 17 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 17 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 17 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 17 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 17 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 17 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 17 times.
✓ Branch 17 taken 30 times.
✓ Branch 18 taken 17 times.
47 allocate(this%in_dataset_4body(size(this%element_info)), source = .false. )
2416
2417 17 end subroutine initialise_gdfs
2418 !###############################################################################
2419
2420
2421 !###############################################################################
2422 56 subroutine set_gdfs_to_default(this, body, index)
2423 !! Initialise the gdfs for index of body distribution function.
2424 implicit none
2425
2426 ! Arguments
2427 class(distribs_container_type), intent(inout) :: this
2428 !! Parent of the procedure. Instance of distribution functions container.
2429 integer, intent(in) :: body
2430 !! Body distribution function to initialise.
2431 integer, intent(in) :: index
2432 !! Index of the pair in the bond_info array.
2433
2434 ! Local variables
2435 real(real32) :: eta, weight, height
2436 !! Parameters for the distribution functions.
2437 real(real32), dimension(1) :: bonds
2438
2439
2440
2/2
✓ Branch 0 taken 34 times.
✓ Branch 1 taken 22 times.
56 if( body .eq. 2 )then
2441 34 weight = exp( -4._real32 )
2442 34 height = 1._real32 / this%nbins(1)
2443 34 eta = 1._real32 / ( 2._real32 * ( this%sigma(1) )**2._real32 )
2444
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 34 times.
34 if(size(this%bond_info).eq.0)then
2445 call set_bond_radius_to_default( [ &
2446 this%bond_info(index)%element(1), &
2447 this%bond_info(index)%element(2) &
2448 ] )
2449 end if
2450
2/2
✓ Branch 0 taken 34 times.
✓ Branch 1 taken 34 times.
68 bonds = [ 2._real32 * this%bond_info(index)%radius_covalent ]
2451
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 34 times.
34 if(abs(bonds(1)).lt.1.E-6)then
2452 call stop_program( "Bond radius is zero" )
2453 end if
2454 this%gdf%df_2body(:,index) = weight * height * get_distrib( &
2455 bonds , &
2456 this%nbins(1), eta, this%width(1), &
2457 this%cutoff_min(1), &
2458 scale_list = [ 1._real32 ] &
2459
3/4
✗ Branch 0 not taken.
✓ Branch 1 taken 34 times.
✓ Branch 3 taken 7184 times.
✓ Branch 4 taken 34 times.
7218 )
2460
2/2
✓ Branch 0 taken 11 times.
✓ Branch 1 taken 11 times.
22 elseif( body .eq. 3 )then
2461
2/2
✓ Branch 0 taken 715 times.
✓ Branch 1 taken 11 times.
726 this%gdf%df_3body(:,index) = 1._real32/this%nbins(2)
2462
1/2
✓ Branch 0 taken 11 times.
✗ Branch 1 not taken.
11 elseif( body .eq. 4 )then
2463
2/2
✓ Branch 0 taken 715 times.
✓ Branch 1 taken 11 times.
726 this%gdf%df_4body(:,index) = 1._real32/this%nbins(3)
2464 end if
2465
2466 56 end subroutine set_gdfs_to_default
2467 !###############################################################################
2468
2469
2470 !###############################################################################
2471 25 subroutine evolve(this, system)
2472 !! Evolve the generalised distribution functions for the container.
2473 implicit none
2474
2475 ! Arguments
2476 class(distribs_container_type), intent(inout) :: this
2477 !! Parent of the procedure. Instance of distribution functions container.
2478 type(distribs_type), dimension(..), intent(in), optional :: system
2479 !! Optional. System to add to the container.
2480
2481 ! Local variables
2482 integer :: i, j, is, js
2483 !! Loop index.
2484 integer :: idx1, idx2
2485 !! Index of the element in the element_info array.
2486 integer :: num_evaluated
2487 !! Number of systems evaluated this iteration.
2488 real(real32) :: weight, energy
2489 !! Energy and weight variables for a system.
2490 real(real32), dimension(:), allocatable :: &
2491 25 best_energy_pair_old, &
2492 25 best_energy_per_species_old
2493 !! Old best energies.
2494 25 integer, dimension(:,:), allocatable :: idx_list
2495 !! Index list for the element pairs in a system.
2496 25 real(real32), dimension(:,:), allocatable :: tmp_df
2497 !! Temporary array for the distribution functions.
2498 25 logical, dimension(:), allocatable :: tmp_in_dataset
2499
2500 character(256) :: err_msg
2501 25 integer, dimension(:), allocatable :: host_idx_list
2502
2503
2504 25 weight = 1._real32
2505
2506 !---------------------------------------------------------------------------
2507 ! if present, add the system to the container
2508 !---------------------------------------------------------------------------
2509
1/4
✗ Branch 0 not taken.
✓ Branch 1 taken 25 times.
✗ Branch 2 not taken.
✗ Branch 3 not taken.
25 if(present(system)) call this%add(system)
2510 25 call this%set_num_bins()
2511
2512
2513 !---------------------------------------------------------------------------
2514 ! initialise the generalised distribution functions and get
2515 ! best energies from lowest formation energy system
2516 !---------------------------------------------------------------------------
2517
2/2
✓ Branch 0 taken 17 times.
✓ Branch 1 taken 8 times.
25 if(.not.allocated(this%gdf%df_2body))then
2518 17 call this%set_best_energy()
2519 17 call this%initialise_gdfs()
2520 else
2521
7/14
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 8 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 8 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 8 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 8 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 25 times.
✓ Branch 13 taken 8 times.
33 best_energy_pair_old = this%best_energy_pair
2522
7/14
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 8 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 8 times.
✗ Branch 7 not taken.
✓ Branch 8 taken 8 times.
✗ Branch 9 not taken.
✓ Branch 10 taken 8 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 15 times.
✓ Branch 13 taken 8 times.
23 best_energy_per_species_old = this%best_energy_per_species
2523 8 call this%set_best_energy()
2524
2/2
✓ Branch 0 taken 25 times.
✓ Branch 1 taken 8 times.
33 do i = 1, size(this%gdf%df_2body,2)
2525 this%gdf%df_2body(:,i) = this%gdf%df_2body(:,i) * &
2526 exp( this%best_energy_pair(i) / this%kBT ) / &
2527
2/2
✓ Branch 0 taken 5525 times.
✓ Branch 1 taken 25 times.
5558 exp( best_energy_pair_old(i) / this%kBT )
2528 end do
2529
2/2
✓ Branch 0 taken 15 times.
✓ Branch 1 taken 8 times.
23 do i = 1, size(this%gdf%df_3body,2)
2530 this%gdf%df_3body(:,i) = &
2531 this%gdf%df_3body(:,i) * exp( &
2532 this%best_energy_per_species(i) / this%kBT &
2533
2/2
✓ Branch 0 taken 975 times.
✓ Branch 1 taken 15 times.
998 ) / exp( best_energy_per_species_old(i) / this%kBT )
2534 end do
2535
2/2
✓ Branch 0 taken 15 times.
✓ Branch 1 taken 8 times.
23 do i = 1, size(this%gdf%df_4body,2)
2536 this%gdf%df_4body(:,i) = &
2537 this%gdf%df_4body(:,i) * exp( &
2538 this%best_energy_per_species(i) / this%kBT &
2539
2/2
✓ Branch 0 taken 975 times.
✓ Branch 1 taken 15 times.
998 ) / exp( best_energy_per_species_old(i) / this%kBT )
2540 end do
2541
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 7 times.
8 if(size(this%gdf%df_2body,2).ne.size(this%bond_info))then
2542 allocate(tmp_df(this%nbins(1),size(this%bond_info)), &
2543
13/22
✓ 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 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 1 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 1 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 1 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 1 times.
✓ Branch 20 taken 6 times.
✓ Branch 21 taken 1 times.
✓ Branch 22 taken 1326 times.
✓ Branch 23 taken 6 times.
1333 source = 0._real32 )
2544
4/4
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 663 times.
✓ Branch 3 taken 3 times.
667 tmp_df(:,1:size(this%gdf%df_2body,2)) = this%gdf%df_2body
2545
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 deallocate(this%gdf%df_2body)
2546
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 call move_alloc( tmp_df, this%gdf%df_2body )
2547
9/16
✓ 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.
✓ Branch 17 taken 6 times.
✓ Branch 18 taken 1 times.
7 allocate(tmp_in_dataset(size(this%bond_info)), source = .false. )
2548
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 1 times.
4 tmp_in_dataset(1:size(this%in_dataset_2body)) = this%in_dataset_2body
2549
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 deallocate(this%in_dataset_2body)
2550
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 call move_alloc( tmp_in_dataset, this%in_dataset_2body )
2551 end if
2552
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 7 times.
8 if(size(this%gdf%df_3body,2).ne.size(this%element_info))then
2553 allocate(tmp_df(this%nbins(2),size(this%element_info)), &
2554
13/22
✓ 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 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 1 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 1 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 1 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 1 times.
✓ Branch 20 taken 3 times.
✓ Branch 21 taken 1 times.
✓ Branch 22 taken 195 times.
✓ Branch 23 taken 3 times.
199 source = 0._real32 )
2555
4/4
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 130 times.
✓ Branch 3 taken 2 times.
133 tmp_df(:,1:size(this%gdf%df_3body,2)) = this%gdf%df_3body
2556
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 deallocate(this%gdf%df_3body)
2557
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 call move_alloc( tmp_df, this%gdf%df_3body )
2558
9/16
✓ 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.
✓ Branch 17 taken 3 times.
✓ Branch 18 taken 1 times.
4 allocate(tmp_in_dataset(size(this%element_info)), source = .false. )
2559
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 tmp_in_dataset(1:size(this%in_dataset_3body)) = this%in_dataset_3body
2560
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 deallocate(this%in_dataset_3body)
2561
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 call move_alloc( tmp_in_dataset, this%in_dataset_3body )
2562 end if
2563
2/2
✓ Branch 0 taken 1 times.
✓ Branch 1 taken 7 times.
8 if(size(this%gdf%df_4body,2).ne.size(this%element_info))then
2564 allocate(tmp_df(this%nbins(3),size(this%element_info)), &
2565
13/22
✓ 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 not taken.
✓ Branch 7 taken 1 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 1 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 1 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 1 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 1 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 1 times.
✓ Branch 20 taken 3 times.
✓ Branch 21 taken 1 times.
✓ Branch 22 taken 195 times.
✓ Branch 23 taken 3 times.
199 source = 0._real32 )
2566
4/4
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 130 times.
✓ Branch 3 taken 2 times.
133 tmp_df(:,1:size(this%gdf%df_4body,2)) = this%gdf%df_4body
2567
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 deallocate(this%gdf%df_4body)
2568
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 call move_alloc( tmp_df, this%gdf%df_4body )
2569
9/16
✓ 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.
✓ Branch 17 taken 3 times.
✓ Branch 18 taken 1 times.
4 allocate(tmp_in_dataset(size(this%element_info)), source = .false. )
2570
2/2
✓ Branch 0 taken 2 times.
✓ Branch 1 taken 1 times.
3 tmp_in_dataset(1:size(this%in_dataset_4body)) = this%in_dataset_4body
2571
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 deallocate(this%in_dataset_4body)
2572
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 1 times.
1 call move_alloc( tmp_in_dataset, this%in_dataset_4body )
2573 end if
2574
2/2
✓ Branch 0 taken 28 times.
✓ Branch 1 taken 8 times.
36 do j = 1, size(this%gdf%df_2body,2)
2575
2/2
✓ Branch 0 taken 20 times.
✓ Branch 1 taken 8 times.
36 if(.not.this%in_dataset_2body(j))then
2576
2/2
✓ Branch 0 taken 4420 times.
✓ Branch 1 taken 20 times.
4440 this%gdf%df_2body(:,j) = 0._real32
2577 else
2578 this%gdf%df_2body(:,j) = &
2579
2/2
✓ Branch 0 taken 1768 times.
✓ Branch 1 taken 8 times.
1776 this%gdf%df_2body(:,j) * this%norm_2body(j)
2580 end if
2581 end do
2582
2/2
✓ Branch 0 taken 16 times.
✓ Branch 1 taken 8 times.
24 do is = 1, size(this%element_info)
2583
2/2
✓ Branch 0 taken 8 times.
✓ Branch 1 taken 8 times.
16 if(.not.this%in_dataset_3body(is))then
2584
2/2
✓ Branch 0 taken 520 times.
✓ Branch 1 taken 8 times.
528 this%gdf%df_3body(:,is) = 0._real32
2585 else
2586 this%gdf%df_3body(:,is) = &
2587
2/2
✓ Branch 0 taken 520 times.
✓ Branch 1 taken 8 times.
528 this%gdf%df_3body(:,is) * this%norm_3body(is)
2588 end if
2589
2/2
✓ Branch 0 taken 8 times.
✓ Branch 1 taken 8 times.
24 if(.not.this%in_dataset_4body(is))then
2590
2/2
✓ Branch 0 taken 520 times.
✓ Branch 1 taken 8 times.
528 this%gdf%df_4body(:,is) = 0._real32
2591 else
2592 this%gdf%df_4body(:,is) = &
2593
2/2
✓ Branch 0 taken 520 times.
✓ Branch 1 taken 8 times.
528 this%gdf%df_4body(:,is) * this%norm_4body(is)
2594 end if
2595 end do
2596
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
8 deallocate(this%norm_2body)
2597
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
8 deallocate(this%norm_3body)
2598
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
8 deallocate(this%norm_4body)
2599 end if
2600
2601 if( &
2602
6/6
✓ Branch 0 taken 31 times.
✓ Branch 1 taken 17 times.
✓ Branch 2 taken 8 times.
✓ Branch 3 taken 23 times.
✓ Branch 4 taken 8 times.
✓ Branch 5 taken 17 times.
48 any(this%system(this%num_evaluated_allocated+1:)%from_host) .and. &
2603 this%host_system%defined &
2604 )then
2605 ! set host_idx_list
2606
7/14
✓ Branch 0 taken 8 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 8 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 8 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 8 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 8 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 8 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 8 times.
8 allocate(host_idx_list(size(this%element_info)))
2607
2/2
✓ Branch 0 taken 16 times.
✓ Branch 1 taken 8 times.
24 host_idx_list = 0
2608
2/2
✓ Branch 0 taken 8 times.
✓ Branch 1 taken 8 times.
16 do is = 1, size(this%host_system%element_symbols)
2609 idx1 = findloc( &
2610 [ this%element_info(:)%name ], &
2611 this%host_system%element_symbols(is), &
2612 dim = 1 &
2613
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
✓ Branch 3 taken 16 times.
✓ Branch 4 taken 8 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 8 times.
✓ Branch 7 taken 16 times.
✓ Branch 8 taken 8 times.
40 )
2614
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 8 times.
8 if(idx1.lt.1)then
2615 call stop_program( "Host species not found in species list" )
2616 return
2617 end if
2618 16 host_idx_list(idx1) = is
2619 end do
2620 end if
2621
2622 !---------------------------------------------------------------------------
2623 ! loop over all systems to calculate the generalised distribution functions
2624 !---------------------------------------------------------------------------
2625 25 num_evaluated = 0
2626
2/2
✓ Branch 0 taken 35 times.
✓ Branch 1 taken 25 times.
60 do i = this%num_evaluated_allocated + 1, size(this%system), 1
2627 35 num_evaluated = num_evaluated + 1
2628
2/2
✓ Branch 0 taken 3 times.
✓ Branch 1 taken 32 times.
35 if(this%weight_by_hull)then
2629 3 weight = exp( this%system(i)%energy_above_hull / this%kBT )
2630
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 3 times.
3 if(weight.lt.1.E-6_real32) cycle
2631 end if
2632 !------------------------------------------------------------------------
2633 ! get the list of 2-body species pairs the system
2634 !------------------------------------------------------------------------
2635 35 j = 0
2636 allocate( idx_list( &
2637 size(this%system(i)%element_symbols), &
2638 size(this%system(i)%element_symbols) &
2639
9/18
✓ Branch 0 taken 35 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 35 times.
✓ Branch 4 taken 35 times.
✗ Branch 5 not taken.
✗ Branch 6 not taken.
✓ Branch 7 taken 35 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 35 times.
✗ Branch 10 not taken.
✓ Branch 11 taken 35 times.
✗ Branch 12 not taken.
✓ Branch 13 taken 35 times.
✗ Branch 15 not taken.
✓ Branch 16 taken 35 times.
✗ Branch 17 not taken.
✓ Branch 18 taken 35 times.
35 ) )
2640
2/2
✓ Branch 0 taken 46 times.
✓ Branch 1 taken 35 times.
81 do is = 1, size(this%system(i)%element_symbols)
2641
2/2
✓ Branch 0 taken 58 times.
✓ Branch 1 taken 46 times.
139 do js = is, size(this%system(i)%element_symbols), 1
2642 58 j = j + 1
2643 58 idx_list(is,js) = j
2644 104 idx_list(js,is) = j
2645 end do
2646 end do
2647
2648
2649 !------------------------------------------------------------------------
2650 ! calculate the weight for the system
2651 !------------------------------------------------------------------------
2652 35 energy = this%system(i)%energy
2653
2/2
✓ Branch 0 taken 46 times.
✓ Branch 1 taken 35 times.
81 do is = 1, size(this%system(i)%element_symbols)
2654 idx1 = findloc( &
2655 [ this%element_info(:)%name ], &
2656 this%system(i)%element_symbols(is), &
2657 dim = 1 &
2658
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 46 times.
✓ Branch 3 taken 103 times.
✓ Branch 4 taken 46 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 46 times.
✓ Branch 7 taken 103 times.
✓ Branch 8 taken 46 times.
252 )
2659
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 46 times.
46 if(idx1.lt.1)then
2660 call stop_program( "Species not found in species list" )
2661 return
2662 end if
2663 energy = energy - this%system(i)%stoichiometry(is) * &
2664 81 this%element_info(idx1)%energy
2665 end do
2666 35 energy = energy / this%system(i)%num_atoms
2667 35 j = 0
2668 !------------------------------------------------------------------------
2669 ! loop over all species in the system to add the distributions
2670 !------------------------------------------------------------------------
2671
2/2
✓ Branch 0 taken 46 times.
✓ Branch 1 taken 35 times.
81 do is = 1, size(this%system(i)%element_symbols)
2672
2673
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 46 times.
46 if( this%system(i)%num_per_species(is).eq.0 )cycle
2674
2675 idx1 = findloc( &
2676 [ this%element_info(:)%name ], &
2677 this%system(i)%element_symbols(is), &
2678 dim = 1 &
2679
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 46 times.
✓ Branch 3 taken 103 times.
✓ Branch 4 taken 46 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 46 times.
✓ Branch 7 taken 103 times.
✓ Branch 8 taken 46 times.
252 )
2680
2681
2/2
✓ Branch 0 taken 42 times.
✓ Branch 1 taken 4 times.
46 if(.not.this%weight_by_hull)then
2682 weight = exp( &
2683 ( &
2684 this%best_energy_per_species(is) - &
2685 energy * ( &
2686 this%system(i)%weight_per_species(is) / &
2687 real( &
2688 sum( this%system(i)%num_per_species(:) ), &
2689 real32 &
2690 ) &
2691 ) &
2692 ) / this%kBT &
2693
2/2
✓ Branch 0 taken 64 times.
✓ Branch 1 taken 42 times.
106 )
2694
2/2
✓ Branch 0 taken 8 times.
✓ Branch 1 taken 34 times.
42 if(weight.lt.1.E-6_real32) cycle
2695 end if
2696
2697 this%gdf%df_3body(:,idx1) = this%gdf%df_3body(:,idx1) + &
2698 set_difference( &
2699 weight * this%system(i)%df_3body(:,is), &
2700 this%gdf%df_3body(:,idx1), &
2701 set_min_zero = .true. &
2702
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 38 times.
✓ Branch 2 taken 2849 times.
✓ Branch 3 taken 38 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 38 times.
✓ Branch 7 taken 2849 times.
✓ Branch 8 taken 38 times.
5736 )
2703
2704 this%gdf%df_4body(:,idx1) = this%gdf%df_4body(:,idx1) + &
2705 set_difference( &
2706 weight * this%system(i)%df_4body(:,is), &
2707 this%gdf%df_4body(:,idx1), &
2708 set_min_zero = .true. &
2709
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 38 times.
✓ Branch 2 taken 2849 times.
✓ Branch 3 taken 38 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 38 times.
✓ Branch 7 taken 2849 times.
✓ Branch 8 taken 38 times.
5736 )
2710
2711
2/2
✓ Branch 0 taken 46 times.
✓ Branch 1 taken 38 times.
119 do js = is, size(this%system(i)%element_symbols), 1
2712 idx2 = findloc( &
2713 [ this%element_info(:)%name ], &
2714 this%system(i)%element_symbols(js), &
2715 dim = 1 &
2716
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 46 times.
✓ Branch 3 taken 103 times.
✓ Branch 4 taken 46 times.
✗ Branch 5 not taken.
✓ Branch 6 taken 46 times.
✓ Branch 7 taken 103 times.
✓ Branch 8 taken 46 times.
252 )
2717 j = nint( ( &
2718 size(this%element_info) - min( idx1, idx2 ) / 2._real32 &
2719 46 ) * ( min( idx1, idx2 ) - 1._real32 ) + max( idx1, idx2 ) )
2720
2721
2/2
✓ Branch 0 taken 41 times.
✓ Branch 1 taken 5 times.
46 if(.not.this%weight_by_hull)then
2722 weight = exp( &
2723 ( &
2724 this%best_energy_pair(j) - &
2725 energy * ( &
2726 this%system(i)%weight_pair(idx_list(is,js)) / &
2727 real( &
2728 sum( this%system(i)%num_per_species(:) ), &
2729 real32 &
2730 ) &
2731 ) &
2732 ) / this%kBT &
2733
2/2
✓ Branch 0 taken 65 times.
✓ Branch 1 taken 41 times.
106 )
2734
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 41 times.
41 if(weight.lt.1.E-6_real32) cycle
2735 end if
2736
2737 this%gdf%df_2body(:,j) = this%gdf%df_2body(:,j) + &
2738 set_difference( &
2739 weight * this%system(i)%df_2body(:,idx_list(is,js)), &
2740 this%gdf%df_2body(:,j), &
2741 set_min_zero = .true. &
2742
6/8
✗ Branch 0 not taken.
✓ Branch 1 taken 46 times.
✓ Branch 2 taken 9176 times.
✓ Branch 3 taken 46 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 46 times.
✓ Branch 7 taken 9176 times.
✓ Branch 8 taken 46 times.
18436 )
2743
2744 end do
2745 end do
2746
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 35 times.
60 deallocate(idx_list)
2747 end do
2748
2749 !---------------------------------------------------------------------------
2750 ! if not in the dataset, set distribution functions to default
2751 !---------------------------------------------------------------------------
2752
2/2
✓ Branch 0 taken 77 times.
✓ Branch 1 taken 25 times.
102 do j = 1, size(this%gdf%df_2body,2)
2753
6/6
✓ Branch 0 taken 9068 times.
✓ Branch 1 taken 34 times.
✓ Branch 2 taken 43 times.
✓ Branch 3 taken 9025 times.
✓ Branch 4 taken 34 times.
✓ Branch 5 taken 43 times.
9127 if(all(abs(this%gdf%df_2body(:,j)).lt.1.E-6_real32))then
2754 34 call this%set_gdfs_to_default(2, j)
2755 else
2756 43 this%in_dataset_2body(j) = .true.
2757 end if
2758 end do
2759
2/2
✓ Branch 0 taken 46 times.
✓ Branch 1 taken 25 times.
71 do is = 1, size(this%element_info)
2760
6/6
✓ Branch 0 taken 1674 times.
✓ Branch 1 taken 11 times.
✓ Branch 2 taken 35 times.
✓ Branch 3 taken 1639 times.
✓ Branch 4 taken 11 times.
✓ Branch 5 taken 35 times.
1685 if(all(abs(this%gdf%df_3body(:,is)).lt.1.E-6_real32))then
2761 11 call this%set_gdfs_to_default(3, is)
2762 else
2763 35 this%in_dataset_3body(is) = .true.
2764 end if
2765
6/6
✓ Branch 0 taken 750 times.
✓ Branch 1 taken 11 times.
✓ Branch 2 taken 35 times.
✓ Branch 3 taken 715 times.
✓ Branch 4 taken 11 times.
✓ Branch 5 taken 35 times.
786 if(all(abs(this%gdf%df_4body(:,is)).lt.1.E-6_real32))then
2766 11 call this%set_gdfs_to_default(4, is)
2767 else
2768 35 this%in_dataset_4body(is) = .true.
2769 end if
2770 end do
2771
2772
7/14
✓ Branch 0 taken 25 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 25 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 25 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 25 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 25 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 25 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 25 times.
25 allocate(this%norm_2body(size(this%gdf%df_2body,2)))
2773
2/2
✓ Branch 0 taken 77 times.
✓ Branch 1 taken 25 times.
102 do j = 1, size(this%gdf%df_2body,2)
2774
6/10
✓ Branch 0 taken 77 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 77 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 15862 times.
✓ Branch 7 taken 77 times.
✓ Branch 8 taken 1829 times.
✓ Branch 9 taken 14033 times.
16016 this%norm_2body(j) = maxval(this%gdf%df_2body(:,j))
2775
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 77 times.
77 if(abs(this%norm_2body(j)).lt.1.E-6_real32)then
2776 call stop_program( "Zero norm for 2-body distribution function" )
2777 return
2778 end if
2779 this%gdf%df_2body(:,j) = &
2780
2/2
✓ Branch 0 taken 15862 times.
✓ Branch 1 taken 77 times.
15939 this%gdf%df_2body(:,j) / this%norm_2body(j)
2781
4/6
✓ Branch 0 taken 15862 times.
✓ Branch 1 taken 77 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 15862 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 77 times.
15964 if(any(isnan(this%gdf%df_2body(:,j))))then
2782 write(err_msg, &
2783 '("NaN in 2-body distribution function for ",A,"-",A,&
2784 &" with norm of ",F0.3)' &
2785 ) &
2786 this%bond_info(j)%element(1), &
2787 this%bond_info(j)%element(2), &
2788 this%norm_2body(j)
2789 call stop_program( err_msg )
2790 return
2791 end if
2792 end do
2793
7/14
✓ Branch 0 taken 25 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 25 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 25 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 25 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 25 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 25 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 25 times.
25 allocate(this%norm_3body(size(this%element_info)))
2794
7/14
✓ Branch 0 taken 25 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 25 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 25 times.
✗ Branch 6 not taken.
✓ Branch 7 taken 25 times.
✗ Branch 8 not taken.
✓ Branch 9 taken 25 times.
✗ Branch 11 not taken.
✓ Branch 12 taken 25 times.
✗ Branch 14 not taken.
✓ Branch 15 taken 25 times.
25 allocate(this%norm_4body(size(this%element_info)))
2795
2/2
✓ Branch 0 taken 46 times.
✓ Branch 1 taken 25 times.
71 do is = 1, size(this%element_info)
2796
6/10
✓ Branch 0 taken 46 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 46 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 3402 times.
✓ Branch 7 taken 46 times.
✓ Branch 8 taken 652 times.
✓ Branch 9 taken 2750 times.
3494 this%norm_3body(is) = maxval(this%gdf%df_3body(:,is))
2797
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 46 times.
46 if(abs(this%norm_3body(is)).lt.1.E-6_real32)then
2798 call stop_program( "Zero norm for 3-body distribution function" )
2799 return
2800 end if
2801
6/10
✓ Branch 0 taken 46 times.
✗ Branch 1 not taken.
✗ Branch 2 not taken.
✓ Branch 3 taken 46 times.
✗ Branch 4 not taken.
✗ Branch 5 not taken.
✓ Branch 6 taken 3402 times.
✓ Branch 7 taken 46 times.
✓ Branch 8 taken 190 times.
✓ Branch 9 taken 3212 times.
3494 this%norm_4body(is) = maxval(this%gdf%df_4body(:,is))
2802
1/2
✗ Branch 0 not taken.
✓ Branch 1 taken 46 times.
46 if(abs(this%norm_4body(is)).lt.1.E-6_real32)then
2803 call stop_program( "Zero norm for 4-body distribution function" )
2804 return
2805 end if
2806 this%gdf%df_3body(:,is) = &
2807
2/2
✓ Branch 0 taken 3402 times.
✓ Branch 1 taken 46 times.
3448 this%gdf%df_3body(:,is) / this%norm_3body(is)
2808 this%gdf%df_4body(:,is) = &
2809
2/2
✓ Branch 0 taken 3402 times.
✓ Branch 1 taken 46 times.
3448 this%gdf%df_4body(:,is) / this%norm_4body(is)
2810
2811
4/6
✓ Branch 0 taken 3402 times.
✓ Branch 1 taken 46 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 3402 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 46 times.
3473 if(any(isnan(this%gdf%df_3body(:,is))))then
2812 write(err_msg,'("NaN in 3-body distribution function for ",A,&
2813 &" with norm of ",F0.3)' &
2814 ) &
2815 this%element_info(is)%name, this%norm_3body(is)
2816 call stop_program( err_msg )
2817 return
2818
4/6
✓ Branch 0 taken 3402 times.
✓ Branch 1 taken 46 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 3402 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 46 times.
3448 elseif(any(isnan(this%gdf%df_4body(:,is))))then
2819 write(err_msg,'("NaN in 4-body distribution function for ",A,&
2820 &" with norm of ",F0.3)' &
2821 ) &
2822 this%element_info(is)%name, this%norm_4body(is)
2823 call stop_program( err_msg )
2824 return
2825 end if
2826 end do
2827
2828 25 this%num_evaluated_allocated = size(this%system)
2829 25 this%num_evaluated = this%num_evaluated + num_evaluated
2830
2831 this%viability_2body_default = sum( this%gdf%df_2body ) / &
2832
7/8
✓ Branch 0 taken 77 times.
✓ Branch 1 taken 25 times.
✓ Branch 2 taken 15862 times.
✓ Branch 3 taken 77 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 50 times.
✓ Branch 6 taken 50 times.
✓ Branch 7 taken 25 times.
16014 real( size( this%gdf%df_2body ), real32 )
2833 this%viability_3body_default = sum( this%gdf%df_3body ) / &
2834
7/8
✓ Branch 0 taken 46 times.
✓ Branch 1 taken 25 times.
✓ Branch 2 taken 3402 times.
✓ Branch 3 taken 46 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 50 times.
✓ Branch 6 taken 50 times.
✓ Branch 7 taken 25 times.
3523 real( size( this%gdf%df_3body ), real32 )
2835 this%viability_4body_default = sum( this%gdf%df_4body ) / &
2836
7/8
✓ Branch 0 taken 46 times.
✓ Branch 1 taken 25 times.
✓ Branch 2 taken 3402 times.
✓ Branch 3 taken 46 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 50 times.
✓ Branch 6 taken 50 times.
✓ Branch 7 taken 25 times.
3523 real( size( this%gdf%df_4body ), real32 )
2837
2838
9/12
✗ Branch 0 not taken.
✓ Branch 1 taken 25 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 25 times.
✗ Branch 4 not taken.
✓ Branch 5 taken 25 times.
✓ Branch 6 taken 8 times.
✓ Branch 7 taken 17 times.
✓ Branch 8 taken 8 times.
✓ Branch 9 taken 17 times.
✓ Branch 10 taken 8 times.
✓ Branch 11 taken 17 times.
25 end subroutine evolve
2839 !###############################################################################
2840
2841
2842 !###############################################################################
2843 2 function is_converged(this, threshold) result(converged)
2844 !! Check if the distribution functions have converged.
2845 implicit none
2846
2847 ! Arguments
2848 class(distribs_container_type), intent(in) :: this
2849 !! Parent of the procedure. Instance of distribution functions container.
2850 real(real32), intent(in), optional :: threshold
2851 !! Threshold for convergence.
2852 logical :: converged
2853 !! Convergence flag.
2854
2855 ! Local variables
2856 real(real32) :: threshold_
2857 !! Threshold for convergence.
2858
2859
2860 2 threshold_ = 1.E-4_real32
2861
1/2
✓ Branch 0 taken 2 times.
✗ Branch 1 not taken.
2 if(present(threshold)) threshold_ = threshold
2862
2863
6/6
✓ Branch 0 taken 11 times.
✓ Branch 1 taken 1 times.
✓ Branch 2 taken 1 times.
✓ Branch 3 taken 10 times.
✓ Branch 4 taken 1 times.
✓ Branch 5 taken 1 times.
12 if(any(abs(this%history_deltas-huge(0._real32)).lt.1.E-6_real32))then
2864 1 converged = .false.
2865 1 return
2866 end if
2867
4/6
✓ Branch 0 taken 10 times.
✓ Branch 1 taken 1 times.
✗ Branch 2 not taken.
✓ Branch 3 taken 10 times.
✓ Branch 4 taken 1 times.
✗ Branch 5 not taken.
11 if(all(abs(this%history_deltas - this%history_deltas(1)).lt.threshold))then
2868 1 converged = .true.
2869 else
2870 converged = .false.
2871 end if
2872
2873 1 end function is_converged
2874 !###############################################################################
2875
2876
91/154
✓ Branch 0 taken 9 times.
✓ Branch 1 taken 32 times.
✓ Branch 2 taken 3 times.
✓ Branch 3 taken 6 times.
✓ Branch 5 taken 7 times.
✓ Branch 6 taken 4 times.
✓ Branch 7 taken 34 times.
✓ Branch 8 taken 1 times.
✓ Branch 9 taken 7 times.
✓ Branch 10 taken 30 times.
✓ Branch 12 taken 27 times.
✓ Branch 13 taken 6 times.
✓ Branch 14 taken 30 times.
✓ Branch 15 taken 4 times.
✓ Branch 16 taken 35 times.
✓ Branch 17 taken 6 times.
✗ Branch 4 not taken.
✓ Branch 11 taken 3 times.
✓ Branch 18 taken 3 times.
✓ Branch 19 taken 3 times.
✓ Branch 20 taken 3 times.
✓ Branch 21 taken 3 times.
✓ Branch 22 taken 3 times.
✓ Branch 23 taken 3 times.
✓ Branch 24 taken 3 times.
✓ Branch 25 taken 3 times.
✓ Branch 26 taken 3 times.
✓ Branch 27 taken 3 times.
✓ Branch 28 taken 3 times.
✓ Branch 29 taken 3 times.
✓ Branch 30 taken 3 times.
✓ Branch 31 taken 3 times.
✓ Branch 32 taken 3 times.
✓ Branch 33 taken 3 times.
✓ Branch 34 taken 3 times.
✓ Branch 35 taken 3 times.
✓ Branch 36 taken 3 times.
✓ Branch 37 taken 3 times.
✓ Branch 38 taken 3 times.
✓ Branch 39 taken 3 times.
✓ Branch 40 taken 3 times.
✓ Branch 41 taken 3 times.
✓ Branch 42 taken 3 times.
✓ Branch 43 taken 3 times.
✓ Branch 44 taken 3 times.
✓ Branch 45 taken 3 times.
✓ Branch 46 taken 3 times.
✓ Branch 47 taken 3 times.
✓ Branch 48 taken 3 times.
✗ Branch 49 not taken.
✓ Branch 50 taken 3 times.
✗ Branch 51 not taken.
✓ Branch 52 taken 3 times.
✗ Branch 53 not taken.
✓ Branch 54 taken 3 times.
✗ Branch 55 not taken.
✓ Branch 56 taken 3 times.
✓ Branch 57 taken 3 times.
✓ Branch 58 taken 3 times.
✓ Branch 59 taken 3 times.
✓ Branch 60 taken 3 times.
✓ Branch 61 taken 3 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 not taken.
✓ Branch 70 taken 3 times.
✗ Branch 71 not taken.
✓ Branch 72 taken 3 times.
✗ Branch 73 not taken.
✓ Branch 74 taken 3 times.
✗ Branch 75 not taken.
✓ Branch 76 taken 3 times.
✗ Branch 77 not taken.
✓ Branch 78 taken 3 times.
✗ Branch 79 not taken.
✓ Branch 80 taken 3 times.
✗ Branch 81 not taken.
✓ Branch 82 taken 3 times.
✓ Branch 83 taken 3 times.
✓ Branch 84 taken 3 times.
✓ Branch 85 taken 3 times.
✓ Branch 86 taken 3 times.
✗ Branch 87 not taken.
✓ Branch 88 taken 3 times.
✗ Branch 89 not taken.
✓ Branch 90 taken 3 times.
✗ Branch 91 not taken.
✓ Branch 92 taken 3 times.
✗ Branch 93 not taken.
✓ Branch 94 taken 3 times.
✗ Branch 95 not taken.
✓ Branch 96 taken 3 times.
✗ Branch 97 not taken.
✓ Branch 98 taken 3 times.
✗ Branch 99 not taken.
✗ Branch 100 not taken.
✓ Branch 101 taken 3 times.
✗ Branch 102 not taken.
✗ Branch 103 not taken.
✗ Branch 104 not taken.
✗ Branch 105 not taken.
✗ Branch 106 not taken.
✗ Branch 107 not taken.
✗ Branch 108 not taken.
✗ Branch 109 not taken.
✓ Branch 110 taken 3 times.
✗ Branch 111 not taken.
✓ Branch 112 taken 3 times.
✗ Branch 113 not taken.
✓ Branch 114 taken 3 times.
✗ Branch 115 not taken.
✓ Branch 116 taken 3 times.
✗ Branch 117 not taken.
✓ Branch 118 taken 3 times.
✗ Branch 119 not taken.
✓ Branch 120 taken 3 times.
✗ Branch 121 not taken.
✗ Branch 122 not taken.
✓ Branch 123 taken 3 times.
✗ Branch 124 not taken.
✗ Branch 125 not taken.
✗ 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 taken 3 times.
✗ Branch 145 not taken.
✓ Branch 146 taken 3 times.
✗ Branch 147 not taken.
✓ Branch 148 taken 3 times.
✗ Branch 149 not taken.
✓ Branch 150 taken 3 times.
✗ Branch 151 not taken.
✓ Branch 152 taken 3 times.
✗ Branch 153 not taken.
145 end module raffle__distribs_container
2877