BraWl
Loading...
Searching...
No Matches
analytics Module Reference

Functions/Subroutines

subroutine, public store_state (averages, config, setup)
 Subroutine to add this configuration to the average.
 
subroutine, public average_state (averages, setup, n_steps)
 Subroutine to compute average occupancies.
 
integer function, public total_particle_count (setup, config)
 Function to count the total number of particles in the box.
 
subroutine, public print_particle_count (setup, config, my_rank)
 Subroutine to print the number of atoms of each species.
 
subroutine, public lattice_shells (setup, shells, configuration)
 Subroutine to compute lattice shell distances.
 
real(real64) function, dimension(setup%n_species, setup%n_species, n_shells), public radial_densities (setup, configuration, n_shells, shell_distances)
 Subroutine to compute radial densities (ASRO parameters)
 
recursive subroutine quicksort (array)
 Implementation of the quicksort algorithm for arrays.
 

Function/Subroutine Documentation

◆ average_state()

subroutine, public analytics::average_state ( real(real64), dimension(:,:,:,:), intent(inout), allocatable averages,
type(run_params), intent(in) setup,
integer, intent(in) n_steps )

Subroutine to compute average occupancies.

At the end of the simulation, divide the stored occupancies by the number of times we stored them, to get the average occupancy of each lattice site.

Author
C. D. Woodgate
Date
2019-2025
Parameters
averagesArray of floats where averages are being stored
setupDerived type containing simulation parameters
n_stepsNumber of steps at which the state was stored
Returns
None

Definition at line 80 of file analytics.f90.

81 type(run_params), intent(in) :: setup
82 integer, intent(in) :: n_steps
83 real(real64), dimension(:,:,:,:), intent(inout), allocatable :: averages
84 integer :: i
85
86 do i=1, setup%n_species
87 averages(i,:,:,:) = (1.0/real(n_steps, real64))*averages(i,:,:,:)
88 end do

◆ lattice_shells()

subroutine, public analytics::lattice_shells ( type(run_params), intent(in) setup,
real(real64), dimension(:), allocatable shells,
integer(array_int), dimension(:,:,:,:) configuration )

Subroutine to compute lattice shell distances.

Could just calculate these once, but this routine is good for a variety of lattice types.

Author
C. D. Woodgate
Date
2019-2025
Parameters
setupDerived type containing simulation parameters
shellsArray where shell distances will be stored
configCurrent atomic configuration
Returns
None

Definition at line 205 of file analytics.f90.

206
207 integer(array_int), dimension(:,:,:,:) :: configuration
208 type(run_params), intent(in) :: setup
209 integer :: i,j,k,b,l
210 real(real64) :: dist
211 !real(real64), dimension(3) :: r_vec
212 real(real64), dimension(:), allocatable :: all_shells, shells
213
214 ! Factor of eight to account for the fact that simulation
215 ! doubles number of cells in each direction to build lattice
216 allocate(all_shells(8*setup%n_1*setup%n_2*setup%n_3*setup%n_basis+1))
217
218 all_shells = 0.0_real64
219 shells = 0.0_real64
220
221 l = 1
222
223! ! Loop over all lattice sites
224! do k=1, 2*setup%n_3
225! do j=1, 2*setup%n_2
226! do i=1, 2*setup%n_1
227! do b=1, setup%n_basis
228! r_vec = real(i)*setup%lattice_vectors(:,1) + &
229! real(j)*setup%lattice_vectors(:,2) + &
230! real(k)*setup%lattice_vectors(:,3) + &
231! real(b)*setup%basis_vectors
232! dist = norm2(r_vec)
233! all_shells(l) = dist
234! l=l+1
235! end do
236! end do
237! end do
238! end do
239
240 ! Loop over all lattice sites
241 do k=1, 2*setup%n_3
242 do j=1, 2*setup%n_2
243 do i=1, 2*setup%n_1
244 do b=1, setup%n_basis
245 ! Cycle if this lattice site is empty
246 if (configuration(b,i,j,k) .eq. 0_array_int) cycle
247 dist = sqrt(real((k-1)**2) + &
248 real((j-1)**2) + &
249 real((i-1)**2))
250 all_shells(l) = dist
251 l=l+1
252 end do
253 end do
254 end do
255 end do
256
257 ! Order the list
258 call quicksort(all_shells)
259
260 ! Counter for how many non-repeated distances
261 ! we have counted
262 l=1
263
264 ! Count the non-repeated distances
265 do i=1, size(all_shells)-1
266 if (abs(all_shells(i)-all_shells(i+1)) .lt. 1e-3_real64) cycle
267 shells(l) = all_shells(i)
268 l=l+1
269 if (l .gt. setup%wc_range) exit
270 end do
271
272 ! Deallocate the array of all distances
273 deallocate(all_shells)
274
Here is the call graph for this function:
Here is the caller graph for this function:

◆ print_particle_count()

subroutine, public analytics::print_particle_count ( type(run_params) setup,
integer(array_int), dimension(:,:,:,:), intent(in) config,
integer my_rank )

Subroutine to print the number of atoms of each species.

Author
C. D. Woodgate
Date
2019-2023
Parameters
setupDerived type containing simulation parameters
configCurrent atomic configuration
Returns
None

Definition at line 135 of file analytics.f90.

136 !integer(array_int), allocatable, dimension(:,:,:,:), intent(in) :: config
137 integer(array_int), dimension(:,:,:,:), intent(in) :: config
138 type(run_params) :: setup
139 integer, dimension(4) :: sizes
140 integer, dimension(:), allocatable :: species_count
141 integer :: i,j,k, n, my_rank
142
143 if(my_rank == 0) then
144 write(6,'(16("-"),x,"Checking contents of simulation cell(s)",x, 15("-"),/)')
145 end if
146
147 sizes = shape(config)
148
149 allocate(species_count(setup%n_species))
150
151 species_count = 0
152 n=0
153
154 do k=1, sizes(4)
155 do j=1, sizes(3)
156 do i=1, sizes(2)
157 if (config(1,i,j,k) .ne. 0_array_int) then
158 n = n+1
159 species_count(config(1,i,j,k)) = &
160 species_count(config(1,i,j,k)) + 1
161 end if
162 end do
163 end do
164 end do
165
166 if(my_rank == 0) then
167 write(6,'(x,"Simulation cell is",x,A,/)') setup%lattice
168 write(6,'(x,"There are:",/)')
169 write(6,'(x,I3,x,"cells in direction 1,")') setup%n_1
170 write(6,'(x,I3,x,"cells in direction 2,")') setup%n_2
171 write(6,'(x,I3,x,"cells in direction 3,",/)') setup%n_3
172 write(6,'(x,"for a total of ",I5,x,"atoms in the cell.",/)') n
173
174 write(6,'(x,"The breakdown is:",/)')
175
176 write(6,'(x,"Index | Element | Number of Atoms")')
177 write(6,'(x,33("-"))')
178 do i=1, setup%n_species
179 write(6,'(x,I5," | ", A, " | ", I9)') &
180 i, setup%species_names(i), species_count(i)
181 end do
182 end if
183
184 deallocate(species_count)
185
186 if(my_rank == 0) then
187 write(6,'(/,17("-"),x,"End of info about simulation cell(s)",x, 17("-"),/)')
188 end if
189
Here is the caller graph for this function:

◆ quicksort()

recursive subroutine analytics::quicksort ( real(real64), dimension(:), intent(inout) array)
private

Implementation of the quicksort algorithm for arrays.

Puts an array of real numbers into size order from smallest to largest. Note that this operates on the input array—if you would like to keep the unsorted array, make a copy of it.

Author
C. D. Woodgate
Date
2019-2023
Parameters
arrayArray of real (real64) numbers to sort
Returns
None

Definition at line 420 of file analytics.f90.

421
422 real(real64), intent(inout)::array(:)
423 real(real64) :: temp,pivot
424 integer :: i,j,last,left,right
425
426 last=size(array)
427
428 if (last.lt.50) then ! use insertion sort on small arrays
429 do i=2,last
430 temp=array(i)
431 do j=i-1,1,-1
432 if (array(j).le.temp) exit
433 array(j+1)=array(j)
434 enddo
435 array(j+1)=temp
436 enddo
437 return
438 endif
439 ! find median of three pivot
440 ! and place sentinels at first and last elements
441 temp=array(last/2)
442 array(last/2)=array(2)
443 if (temp.gt.array(last)) then
444 array(2)=array(last)
445 array(last)=temp
446 else
447 array(2)=temp
448 endif
449 if (array(1).gt.array(last)) then
450 temp=array(1)
451 array(1)=array(last)
452 array(last)=temp
453 endif
454 if (array(1).gt.array(2)) then
455 temp=array(1)
456 array(1)=array(2)
457 array(2)=temp
458 endif
459 pivot=array(2)
460
461 left=3
462 right=last-1
463 do
464 do while(array(left).lt.pivot)
465 left=left+1
466 enddo
467 do while(array(right).gt.pivot)
468 right=right-1
469 enddo
470 if (left.ge.right) exit
471 temp=array(left)
472 array(left)=array(right)
473 array(right)=temp
474 left=left+1
475 right=right-1
476 enddo
477 if (left.eq.right) left=left+1
478 call quicksort(array(1:left-1))
479 call quicksort(array(left:))
480
Here is the call graph for this function:
Here is the caller graph for this function:

◆ radial_densities()

real(real64) function, dimension(setup%n_species,setup%n_species, n_shells), public analytics::radial_densities ( type(run_params), intent(in) setup,
integer(array_int), dimension(:,:,:,:) configuration,
integer, intent(in) n_shells,
real(real64), dimension(:), allocatable shell_distances )

Subroutine to compute radial densities (ASRO parameters)

This routine computes the conditional probabilities of one type of atom neighbouring another type of atom. These are not the Warren-Cowley ASRO parameters, but you can convert to them using a simple rescaling.

Author
C. D. Woodgate
Date
2019-2025
Parameters
setupDerived type containing simulation parameters
configurationCurrent atomic configuration
n_shellsNumber of shells on which to compute probabilities
shell_distancesArray of lattice shell distances
Returns
The computed radial densities (conditional probabilities)

Definition at line 293 of file analytics.f90.

295 type(run_params), intent(in) :: setup
296 integer(array_int), dimension(:,:,:,:) :: configuration
297 real(real64), dimension(:), allocatable :: shell_distances
298 real(real64), dimension(setup%n_species,setup%n_species, & n_shells) :: r_densities
299 integer, intent(in) :: n_shells
300 integer :: i_1,i_2,i_3,j_1,j_2,j_3,j_b,jj_1,jj_2,jj_3, &
301 l, species_i, species_j, i,j, i_b
302 integer :: loop_1, loop_2, loop_3
303 integer, dimension(setup%n_species) :: particle_counts
304 real(real64) :: distance, d_x, d_y, d_z
305
306 ! Array for counting the number of each species
307 ! Initialise it to zero
308 particle_counts = 0
309
310 ! Output array of radial densities
311 ! Initialise it to zero
312 r_densities = 0.0_real64
313
314 ! Count how many of each species there are
315 do i_3=1, setup%n_3*2
316 do i_2=1, setup%n_2*2
317 do i_1=1, setup%n_1*2
318 do i_b=1, setup%n_basis
319 do l=1, setup%n_species
320 if (configuration(i_b, i_1, i_2, i_3) .eq. &
321 int(l, kind=array_int)) then
322 particle_counts(l) = particle_counts(l) + 1
323 end if
324 end do
325 end do
326 end do
327 end do
328 end do
329
330 ! Check that we won't divide by zero later
331 do l=1, setup%n_species
332 if (particle_counts(l) .eq. 0) then
333 print*, 'Warning, one or more particle counts are zero in radial_densities()'
334 end if
335 end do
336
337 ! For small systems, limit loop size to prevent double counting
338 loop_1 = min(setup%n_1, 5)
339 loop_2 = min(setup%n_2, 5)
340 loop_3 = min(setup%n_3, 5)
341
342 ! Loop over all lattice sites
343 do i_3=1, 2*setup%n_3
344 do i_2=1, 2*setup%n_2
345 do i_1=1, 2*setup%n_1
346 do i_b=1, setup%n_basis
347 ! Cycle if this site is empty
348 if (configuration(i_b, i_1, i_2, i_3) .eq. 0_array_int) cycle
349 ! Loop over neighbouring sites, accounting for
350 ! P.B.C.s
351 do jj_3=i_3-loop_3, i_3+loop_3, 1
352 j_3 = modulo(jj_3-1, 2*setup%n_3) + 1
353 do jj_2=i_2-loop_2, i_2+loop_2, 1
354 j_2 = modulo(jj_2-1, 2*setup%n_2) + 1
355 do jj_1=i_1-loop_1, i_1+loop_1, 1
356 j_1 = modulo(jj_1-1, 2*setup%n_1) + 1
357 do j_b=1, setup%n_basis
358 if (configuration(j_b, j_1, j_2, j_3) .eq. 0_array_int) cycle
359 ! Compute the distance to this site, accounting
360 ! for PBCs
361 d_x = real(i_1-j_1)
362 d_y = real(i_2-j_2)
363 d_z = real(i_3-j_3)
364
365 d_x = d_x - float(2*setup%n_1)* &
366 nint(d_x/float(2*setup%n_1))
367 d_y = d_y - float(2*setup%n_2)* &
368 nint(d_y/float(2*setup%n_2))
369 d_z = d_z - float(2*setup%n_3)* &
370 nint(d_z/float(2*setup%n_3))
371
372 distance = sqrt(d_x**2 + d_y**2 + d_z**2)
373
374 ! Loop over and find which shell this sits in
375 do l=1, n_shells
376 if (abs(distance - shell_distances(l)) &
377 .lt. 1e-3_real64) then
378
379 ! Add it to the relevant entry for this shell
380 species_i = configuration(i_b,i_1, i_2, i_3)
381 species_j = configuration(j_b,j_1, j_2, j_3)
382 r_densities(species_i, species_j, l) = &
383 r_densities(species_i, species_j, l) + 1.0_real64
384 end if
385 end do
386 end do
387 end do
388 end do
389 end do
390 end do
391 end do
392 end do
393 end do
394 ! Nice nested do loop...
395
396 ! Average them
397 do i=1, n_shells
398 do j=1, setup%n_species
399 r_densities(j,:,i) = r_densities(j,:,i)/particle_counts(j)
400 end do
401 end do
402
403
Here is the caller graph for this function:

◆ store_state()

subroutine, public analytics::store_state ( real(real64), dimension(:,:,:,:,:), intent(inout), allocatable averages,
integer(array_int), dimension(:,:,:,:), intent(in) config,
type(run_params), intent(in) setup )

Subroutine to add this configuration to the average.

This is needed to compute the average occupancy of each lattice site at the end of a simulation.

Author
C. D. Woodgate
Date
2019-2025
Parameters
averagesArray of floats where averages are being stored
configCurrent atomic configuration
setupDerived type containing simulation parameters
Returns
None

Definition at line 43 of file analytics.f90.

44
45 integer(array_int), dimension(:,:,:,:), intent(in) :: config
46 type(run_params), intent(in) :: setup
47 real(real64), dimension(:,:,:,:,:), intent(inout), allocatable :: averages
48 integer :: i,j,k,l,m
49
50 do m=1, 2*setup%n_3
51 do l=1, 2*setup%n_2
52 do k=1, 2*setup%n_1
53 do j=1, setup%n_basis
54 do i=1, setup%n_species
55 if (config(j,k,l,m) == i) then
56 averages(i,j,k,l,m) = averages(i,j,k,l,m) + 1.0_real64
57 end if
58 end do
59 end do
60 end do
61 end do
62 end do
63

◆ total_particle_count()

integer function, public analytics::total_particle_count ( type(run_params) setup,
integer(array_int), dimension(:,:,:,:), intent(in) config )

Function to count the total number of particles in the box.

This function was mainly used for testing during code development, to make sure no particles were dissapearing.

Author
C. D. Woodgate
Date
2019-2025
Parameters
setupDerived type containing simulation parameters
configCurrent atomic configuration
Returns
The total number of particles in the simulation cell

Definition at line 103 of file analytics.f90.

104 !integer(array_int), allocatable, dimension(:,:,:,:), intent(in) :: config
105 integer(array_int), dimension(:,:,:,:), intent(in) :: config
106 type(run_params) :: setup
107 integer :: total_count
108 integer :: i,j,k,b
109
110 total_count = 0
111
112 do b=1, setup%n_basis
113 do k=1, 2*setup%n_3
114 do j=1, 2*setup%n_2
115 do i=1, 2*setup%n_1
116 if (config(b,i,j,k) .ne. 0_array_int) then
117 total_count = total_count + 1
118 end if
119 end do
120 end do
121 end do
122 end do
123
Here is the caller graph for this function: