GCC Code Coverage Report


Directory: src/fortran/lib/
File: mod_distribs_container.f90
Date: 2025-04-05 12:17:58
Exec Total Coverage
Lines: 514 843 61.0%
Functions: 0 0 -%
Branches: 1380 2896 47.7%

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