(git:34ef472)
tmc_analysis_types.F
Go to the documentation of this file.
1 !--------------------------------------------------------------------------------------------------!
2 ! CP2K: A general program to perform molecular dynamics simulations !
3 ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 ! !
5 ! SPDX-License-Identifier: GPL-2.0-or-later !
6 !--------------------------------------------------------------------------------------------------!
7 
8 ! **************************************************************************************************
9 !> \brief module provides variables for the TMC analysis tool
10 !> \par History
11 !> 02.2013 created [Mandes Schoenherr]
12 !> \author Mandes
13 ! **************************************************************************************************
14 
16  USE cell_types, ONLY: cell_type
17  USE kinds, ONLY: default_path_length,&
19  dp
20  USE tmc_tree_types, ONLY: tree_type
21  USE tmc_types, ONLY: tmc_atom_type
22 #include "../base/base_uses.f90"
23 
24  IMPLICIT NONE
25 
26  PRIVATE
27 
28  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'tmc_analysis_types'
29 
30  PUBLIC :: tmc_analysis_env, tmc_ana_list_type
32  PUBLIC :: tmc_ana_density_create
33  PUBLIC :: pair_correl_type, tmc_ana_pair_correl_create, &
34  search_pair_in_list, atom_pairs_type
35  PUBLIC :: dipole_moment_type, tmc_ana_dipole_moment_create
38 
39  CHARACTER(LEN=default_path_length), PARAMETER, &
40  PUBLIC :: tmc_ana_density_file_name = "tmc_ana_density.dat"
41  CHARACTER(LEN=default_path_length), PARAMETER, &
42  PUBLIC :: tmc_ana_pair_correl_file_name = "tmc_ana_g_r.dat"
43 
44  INTEGER, PARAMETER, PUBLIC :: ana_type_default = 0
45  INTEGER, PARAMETER, PUBLIC :: ana_type_ice = 1
46  INTEGER, PARAMETER, PUBLIC :: ana_type_sym_xyz = 2
47 
48  TYPE tmc_ana_list_type
49  TYPE(tmc_analysis_env), POINTER :: temp => null()
50  END TYPE tmc_ana_list_type
51 
52  TYPE tmc_analysis_env
53  INTEGER :: io_unit = -1
54  CHARACTER(len=default_string_length), &
55  DIMENSION(:), POINTER :: dirs => null()
56  CHARACTER(LEN=default_path_length) :: out_file_prefix = ""
57  INTEGER :: conf_offset = 0
58  TYPE(cell_type), POINTER :: cell => null()
59  TYPE(tmc_atom_type), DIMENSION(:), POINTER :: atoms => null()
60  INTEGER :: dim_per_elem = 3
61  INTEGER :: nr_dim = -1
62  REAL(kind=dp) :: temperature = 0.0_dp
63  TYPE(tree_type), POINTER :: last_elem => null()
64  INTEGER :: from_elem = -1, to_elem = -1
65  INTEGER :: id_traj = -1, id_cell = -1, id_frc = -1, id_dip = -1, id_ener = -1
66  INTEGER :: lc_traj = 0, lc_cell = 0, lc_frc = 0, lc_dip = 0, lc_ener = 0
67  CHARACTER(LEN=default_path_length) :: costum_pos_file_name = ""
68  CHARACTER(LEN=default_path_length) :: costum_dip_file_name = ""
69  CHARACTER(LEN=default_path_length) :: costum_cell_file_name = ""
70  LOGICAL :: restart = .true., restarted = .false.
71  LOGICAL :: print_test_output = .false.
72 
73  TYPE(density_3d_type), POINTER :: density_3d => null()
74  TYPE(pair_correl_type), POINTER :: pair_correl => null()
75  TYPE(dipole_moment_type), POINTER :: dip_mom => null()
76  TYPE(dipole_analysis_type), POINTER :: dip_ana => null()
77  TYPE(displacement_type), POINTER :: displace => null()
78  END TYPE tmc_analysis_env
79 
80  TYPE density_3d_type
81  INTEGER :: conf_counter = 0
82  INTEGER, DIMENSION(3) :: nr_bins = 0
83  REAL(kind=dp) :: sum_vol = 0.0_dp
84  REAL(kind=dp) :: sum_vol2 = 0.0_dp
85  REAL(kind=dp), DIMENSION(3) :: sum_box_length = 0.0_dp
86  REAL(kind=dp), DIMENSION(3) :: sum_box_length2 = 0.0_dp
87  REAL(kind=dp), DIMENSION(:, :, :), POINTER :: sum_density => null(), sum_dens2 => null()
88  LOGICAL :: print_dens = .true.
89  END TYPE density_3d_type
90 
91  TYPE pair_correl_type
92  INTEGER :: conf_counter = 0
93  INTEGER :: nr_bins = 0
94  REAL(kind=dp) :: step_length = -1.0_dp
95  TYPE(atom_pairs_type), DIMENSION(:), POINTER :: pairs => null()
96  REAL(kind=dp), DIMENSION(:, :), POINTER :: g_r => null()
97  REAL(kind=dp) :: sum_box_scale(3) = 0.0_dp
98  END TYPE pair_correl_type
99 
100  TYPE atom_pairs_type
101  CHARACTER(LEN=default_string_length) :: f_n = ""
102  CHARACTER(LEN=default_string_length) :: s_n = ""
103  INTEGER :: pair_count = 0
104  END TYPE atom_pairs_type
105 
106  TYPE dipole_moment_type
107  INTEGER :: conf_counter = 0
108  TYPE(tmc_atom_type), DIMENSION(:), POINTER :: charges_inp => null()
109  REAL(kind=dp), DIMENSION(:), POINTER :: charges => null()
110  REAL(kind=dp), DIMENSION(:), POINTER :: last_dip_cl => null()
111  LOGICAL :: print_cl_dip = .true.
112  END TYPE dipole_moment_type
113 
114  TYPE dipole_analysis_type
115  REAL(kind=dp) :: conf_counter = 0
116  INTEGER :: ana_type = -1
117  LOGICAL :: print_diel_const_traj = .true.
118  ! squared dipoles per volume
119  REAL(kind=dp) :: mu2_pv_s = 0.0_dp
120  ! dipole per square root ov volume per direction
121  REAL(kind=dp), DIMENSION(:), POINTER :: mu_psv => null(), mu_pv => null(), mu2_pv => null()
122  ! dipole dipole correlation matrix (per volume)
123  REAL(kind=dp), DIMENSION(:, :), POINTER :: mu2_pv_mat => null()
124 
125  END TYPE dipole_analysis_type
126 
127  TYPE displacement_type
128  INTEGER :: conf_counter = 0
129  REAL(kind=dp) :: disp = 0.0_dp
130  LOGICAL :: print_disp = .true.
131  END TYPE displacement_type
132 
133 CONTAINS
134 
135 ! **************************************************************************************************
136 !> \brief creates a new structure environment for TMC analysis
137 !> \param tmc_ana structure with parameters for TMC analysis
138 !> \author Mandes 02.2013
139 ! **************************************************************************************************
140  SUBROUTINE tmc_ana_env_create(tmc_ana)
141  TYPE(tmc_analysis_env), POINTER :: tmc_ana
142 
143  cpassert(.NOT. ASSOCIATED(tmc_ana))
144 
145  ALLOCATE (tmc_ana)
146 
147  END SUBROUTINE tmc_ana_env_create
148 
149 ! **************************************************************************************************
150 !> \brief releases the structure environment for TMC analysis
151 !> \param tmc_ana structure with parameters for TMC analysis
152 !> \author Mandes 02.2013
153 ! **************************************************************************************************
154  SUBROUTINE tmc_ana_env_release(tmc_ana)
155  TYPE(tmc_analysis_env), POINTER :: tmc_ana
156 
157  cpassert(ASSOCIATED(tmc_ana))
158 
159  IF (ASSOCIATED(tmc_ana%dirs)) &
160  DEALLOCATE (tmc_ana%dirs)
161 
162  IF (ASSOCIATED(tmc_ana%density_3d)) &
163  CALL tmc_ana_dens_release(tmc_ana%density_3d)
164  IF (ASSOCIATED(tmc_ana%pair_correl)) &
165  CALL tmc_ana_pair_correl_release(tmc_ana%pair_correl)
166 
167  IF (ASSOCIATED(tmc_ana%dip_mom)) &
168  CALL tmc_ana_dipole_moment_release(tmc_ana%dip_mom)
169 
170  IF (ASSOCIATED(tmc_ana%dip_ana)) &
171  CALL tmc_ana_dipole_analysis_release(tmc_ana%dip_ana)
172 
173  IF (ASSOCIATED(tmc_ana%displace)) &
174  CALL tmc_ana_displacement_release(ana_disp=tmc_ana%displace)
175 
176  DEALLOCATE (tmc_ana)
177 
178  END SUBROUTINE tmc_ana_env_release
179 
180  !============================================================================
181  ! density calculations
182  !============================================================================
183 
184 ! **************************************************************************************************
185 !> \brief creates a new structure environment for TMC analysis
186 !> \param ana_dens structure with parameters for TMC density analysis
187 !> \param nr_bins ...
188 !> \author Mandes 02.2013
189 ! **************************************************************************************************
190  SUBROUTINE tmc_ana_density_create(ana_dens, nr_bins)
191  TYPE(density_3d_type), POINTER :: ana_dens
192  INTEGER, DIMENSION(3) :: nr_bins
193 
194  cpassert(.NOT. ASSOCIATED(ana_dens))
195 
196  ALLOCATE (ana_dens)
197 
198  ana_dens%nr_bins(:) = nr_bins(:)
199 
200  ALLOCATE (ana_dens%sum_density(nr_bins(1), nr_bins(2), nr_bins(3)))
201  ALLOCATE (ana_dens%sum_dens2(nr_bins(1), nr_bins(2), nr_bins(3)))
202  ana_dens%sum_density = 0.0_dp
203  ana_dens%sum_dens2 = 0.0_dp
204  END SUBROUTINE tmc_ana_density_create
205 
206 ! **************************************************************************************************
207 !> \brief releases the structure environment for TMC analysis
208 !> \param ana_dens structure with parameters for TMC analysis
209 !> \author Mandes 02.2013
210 ! **************************************************************************************************
211  SUBROUTINE tmc_ana_dens_release(ana_dens)
212  TYPE(density_3d_type), POINTER :: ana_dens
213 
214  cpassert(ASSOCIATED(ana_dens))
215 
216  DEALLOCATE (ana_dens%sum_density)
217  DEALLOCATE (ana_dens%sum_dens2)
218  DEALLOCATE (ana_dens)
219  END SUBROUTINE tmc_ana_dens_release
220 
221  !============================================================================
222  ! radial distribution function
223  !============================================================================
224 
225 ! **************************************************************************************************
226 !> \brief creates a new structure environment for TMC analysis
227 !> \param ana_pair_correl ...
228 !> \param nr_bins ...
229 !> \param
230 !> \author Mandes 02.2013
231 ! **************************************************************************************************
232  SUBROUTINE tmc_ana_pair_correl_create(ana_pair_correl, nr_bins)
233  TYPE(pair_correl_type), POINTER :: ana_pair_correl
234  INTEGER :: nr_bins
235 
236  cpassert(.NOT. ASSOCIATED(ana_pair_correl))
237  ALLOCATE (ana_pair_correl)
238 
239  ana_pair_correl%nr_bins = nr_bins
240  END SUBROUTINE tmc_ana_pair_correl_create
241 
242 ! **************************************************************************************************
243 !> \brief releases the structure environment for TMC analysis
244 !> \param ana_pair_correl ...
245 !> \param
246 !> \author Mandes 02.2013
247 ! **************************************************************************************************
248  SUBROUTINE tmc_ana_pair_correl_release(ana_pair_correl)
249  TYPE(pair_correl_type), POINTER :: ana_pair_correl
250 
251  cpassert(ASSOCIATED(ana_pair_correl))
252 
253  DEALLOCATE (ana_pair_correl%g_r)
254  DEALLOCATE (ana_pair_correl%pairs)
255  DEALLOCATE (ana_pair_correl)
256  END SUBROUTINE tmc_ana_pair_correl_release
257 
258 ! **************************************************************************************************
259 !> \brief search the pair of two atom types in list
260 !> \param pair_list ...
261 !> \param n1 atom names
262 !> \param n2 atom names
263 !> \param list_end ...
264 !> \return ...
265 !> \author Mandes 02.2013
266 ! **************************************************************************************************
267  FUNCTION search_pair_in_list(pair_list, n1, n2, list_end) RESULT(ind)
268  TYPE(atom_pairs_type), DIMENSION(:), POINTER :: pair_list
269  CHARACTER(LEN=default_string_length) :: n1, n2
270  INTEGER, OPTIONAL :: list_end
271  INTEGER :: ind
272 
273  INTEGER :: last, list_nr
274 
275  cpassert(ASSOCIATED(pair_list))
276  IF (PRESENT(list_end)) THEN
277  cpassert(list_end .LE. SIZE(pair_list))
278  last = list_end
279  ELSE
280  last = SIZE(pair_list)
281  END IF
282 
283  ind = -1
284 
285  list_search: DO list_nr = 1, last
286  IF ((pair_list(list_nr)%f_n .EQ. n1 .AND. &
287  pair_list(list_nr)%s_n .EQ. n2) .OR. &
288  (pair_list(list_nr)%f_n .EQ. n2 .AND. &
289  pair_list(list_nr)%s_n .EQ. n1)) THEN
290  ind = list_nr
291  EXIT list_search
292  END IF
293  END DO list_search
294  END FUNCTION search_pair_in_list
295 
296  !============================================================================
297  ! classical cell dipole moment
298  !============================================================================
299 
300 ! **************************************************************************************************
301 !> \brief creates a new structure environment for TMC analysis
302 !> \param ana_dip_mom ...
303 !> \param charge_atm ...
304 !> \param charge ...
305 !> \param dim_per_elem ...
306 !> \param
307 !> \author Mandes 02.2013
308 ! **************************************************************************************************
309  SUBROUTINE tmc_ana_dipole_moment_create(ana_dip_mom, charge_atm, charge, &
310  dim_per_elem)
311  TYPE(dipole_moment_type), POINTER :: ana_dip_mom
312  CHARACTER(LEN=default_string_length), POINTER :: charge_atm(:)
313  REAL(kind=dp), POINTER :: charge(:)
314  INTEGER :: dim_per_elem
315 
316  INTEGER :: i
317 
318  cpassert(.NOT. ASSOCIATED(ana_dip_mom))
319  ALLOCATE (ana_dip_mom)
320 
321  ALLOCATE (ana_dip_mom%charges_inp(SIZE(charge)))
322  DO i = 1, SIZE(charge)
323  ana_dip_mom%charges_inp(i)%name = charge_atm(i)
324  ana_dip_mom%charges_inp(i)%mass = charge(i)
325  END DO
326 
327  ALLOCATE (ana_dip_mom%last_dip_cl(dim_per_elem))
328  ! still the initialization routine has to be called
329 
330  END SUBROUTINE tmc_ana_dipole_moment_create
331 
332 ! **************************************************************************************************
333 !> \brief releases the structure environment for TMC analysis
334 !> \param ana_dip_mom ...
335 !> \param
336 !> \author Mandes 02.2013
337 ! **************************************************************************************************
338  SUBROUTINE tmc_ana_dipole_moment_release(ana_dip_mom)
339  TYPE(dipole_moment_type), POINTER :: ana_dip_mom
340 
341  cpassert(ASSOCIATED(ana_dip_mom))
342 
343  IF (ASSOCIATED(ana_dip_mom%charges_inp)) DEALLOCATE (ana_dip_mom%charges_inp)
344  IF (ASSOCIATED(ana_dip_mom%charges)) DEALLOCATE (ana_dip_mom%charges)
345  DEALLOCATE (ana_dip_mom%last_dip_cl)
346  DEALLOCATE (ana_dip_mom)
347  END SUBROUTINE tmc_ana_dipole_moment_release
348 
349 ! **************************************************************************************************
350 !> \brief creates a new structure environment for TMC analysis
351 !> \param ana_dip_ana ...
352 !> \param
353 !> \author Mandes 02.2013
354 ! **************************************************************************************************
355  SUBROUTINE tmc_ana_dipole_analysis_create(ana_dip_ana)
356  TYPE(dipole_analysis_type), POINTER :: ana_dip_ana
357 
358  cpassert(.NOT. ASSOCIATED(ana_dip_ana))
359  ALLOCATE (ana_dip_ana)
360 
361  ALLOCATE (ana_dip_ana%mu_psv(3))
362  ana_dip_ana%mu_psv = 0.0_dp
363  ALLOCATE (ana_dip_ana%mu_pv(3))
364  ana_dip_ana%mu_pv = 0.0_dp
365  ALLOCATE (ana_dip_ana%mu2_pv(3))
366  ana_dip_ana%mu2_pv = 0.0_dp
367  ALLOCATE (ana_dip_ana%mu2_pv_mat(3, 3))
368  ana_dip_ana%mu2_pv_mat = 0.0_dp
369  END SUBROUTINE tmc_ana_dipole_analysis_create
370 
371 ! **************************************************************************************************
372 !> \brief releases the structure environment for TMC analysis
373 !> \param ana_dip_ana ...
374 !> \param
375 !> \author Mandes 02.2013
376 ! **************************************************************************************************
377  SUBROUTINE tmc_ana_dipole_analysis_release(ana_dip_ana)
378  TYPE(dipole_analysis_type), POINTER :: ana_dip_ana
379 
380  cpassert(ASSOCIATED(ana_dip_ana))
381 
382  DEALLOCATE (ana_dip_ana%mu_psv)
383  DEALLOCATE (ana_dip_ana%mu_pv)
384  DEALLOCATE (ana_dip_ana%mu2_pv)
385  DEALLOCATE (ana_dip_ana%mu2_pv_mat)
386 
387  DEALLOCATE (ana_dip_ana)
388  END SUBROUTINE tmc_ana_dipole_analysis_release
389 
390  !============================================================================
391  ! particle displacement in cell (from one configuration to the next)
392  !============================================================================
393 
394 ! **************************************************************************************************
395 !> \brief creates a new structure environment for TMC analysis
396 !> \param ana_disp ...
397 !> \param dim_per_elem ...
398 !> \param
399 !> \author Mandes 02.2013
400 ! **************************************************************************************************
401  SUBROUTINE tmc_ana_displacement_create(ana_disp, dim_per_elem)
402  TYPE(displacement_type), POINTER :: ana_disp
403  INTEGER :: dim_per_elem
404 
405  cpassert(.NOT. ASSOCIATED(ana_disp))
406  cpassert(dim_per_elem .GT. 0)
407  mark_used(dim_per_elem)
408 
409  ALLOCATE (ana_disp)
410 
411  END SUBROUTINE tmc_ana_displacement_create
412 
413 ! **************************************************************************************************
414 !> \brief releases a structure environment for TMC analysis
415 !> \param ana_disp ...
416 !> \param
417 !> \author Mandes 02.2013
418 ! **************************************************************************************************
419  SUBROUTINE tmc_ana_displacement_release(ana_disp)
420  TYPE(displacement_type), POINTER :: ana_disp
421 
422  cpassert(ASSOCIATED(ana_disp))
423 
424  DEALLOCATE (ana_disp)
425  END SUBROUTINE tmc_ana_displacement_release
426 END MODULE tmc_analysis_types
Handles all functions related to the CELL.
Definition: cell_types.F:15
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
integer, parameter, public default_string_length
Definition: kinds.F:57
integer, parameter, public default_path_length
Definition: kinds.F:58
module provides variables for the TMC analysis tool
integer function, public search_pair_in_list(pair_list, n1, n2, list_end)
search the pair of two atom types in list
subroutine, public tmc_ana_displacement_create(ana_disp, dim_per_elem)
creates a new structure environment for TMC analysis
subroutine, public tmc_ana_dipole_analysis_create(ana_dip_ana)
creates a new structure environment for TMC analysis
subroutine, public tmc_ana_dipole_moment_create(ana_dip_mom, charge_atm, charge, dim_per_elem)
creates a new structure environment for TMC analysis
subroutine, public tmc_ana_env_create(tmc_ana)
creates a new structure environment for TMC analysis
subroutine, public tmc_ana_env_release(tmc_ana)
releases the structure environment for TMC analysis
integer, parameter, public ana_type_default
integer, parameter, public ana_type_ice
character(len=default_path_length), parameter, public tmc_ana_pair_correl_file_name
character(len=default_path_length), parameter, public tmc_ana_density_file_name
integer, parameter, public ana_type_sym_xyz
subroutine, public tmc_ana_density_create(ana_dens, nr_bins)
creates a new structure environment for TMC analysis
subroutine, public tmc_ana_pair_correl_create(ana_pair_correl, nr_bins)
creates a new structure environment for TMC analysis
module handles definition of the tree nodes for the global and the subtrees binary tree parent elemen...
module handles definition of the tree nodes for the global and the subtrees binary tree parent elemen...
Definition: tmc_types.F:32