(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_voronoi.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 function that build the dft section of the input
10!> \par History
11!> 10.2005 moved out of input_cp2k [fawzi]
12!> \author fawzi
13! **************************************************************************************************
15 USE bibliography, ONLY: brehm2018,&
16 brehm2020,&
17 brehm2021,&
31 USE input_val_types, ONLY: integer_t,&
32 lchar_t,&
33 real_t
34 USE kinds, ONLY: dp
35 USE physcon, ONLY: bohr
36 USE string_utilities, ONLY: s2a
37#include "./base/base_uses.f90"
38
39 IMPLICIT NONE
40 PRIVATE
41
42 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_voronoi'
43
45
46CONTAINS
47
48! **************************************************************************************************
49!> \brief Create the print voronoi section
50!> \param print_key ...
51!> \author Martin Brehm
52! **************************************************************************************************
53 SUBROUTINE create_print_voronoi_section(print_key)
54 TYPE(section_type), POINTER :: print_key
55
56 TYPE(keyword_type), POINTER :: keyword
57
58 cpassert(.NOT. ASSOCIATED(print_key))
59
60 ! Voronoi Integration via LibVori
61 CALL cp_print_key_section_create(print_key, __location__, name="VORONOI", &
62 description="Controls the Voronoi integration of the total electron density"// &
63 " for the computation of electromagnetic moments, see [Thomas2015],"// &
64 " [Brehm2020], and [Brehm2021]"// &
65 " (via LibVori see <https://brehm-research.de/voronoi>).", &
66 print_level=debug_print_level + 1, filename="", &
68
69 NULLIFY (keyword)
70 CALL keyword_create(keyword, __location__, name="APPEND", &
71 description="Appends frames to already existing .voronoi file.", &
72 default_l_val=.false., lone_keyword_l_val=.true.)
73 CALL section_add_keyword(print_key, keyword)
74 CALL keyword_release(keyword)
75
76 CALL keyword_create(keyword, __location__, name="SANITY_CHECK", &
77 description="Performs a sanity check before each Voronoi integration, i.e.,"// &
78 " checks if every grid point is located in exactly one Voronoi cell.", &
79 usage="SANITY_CHECK T", default_l_val=.false., lone_keyword_l_val=.true.)
80 CALL section_add_keyword(print_key, keyword)
81 CALL keyword_release(keyword)
82
83 CALL keyword_create(keyword, __location__, name="OVERWRITE", &
84 description="Specify this keyword to overwrite any existing ""properties.emp"" file if"// &
85 " it already exists. By default, the data is appended to an existing .emp file.", &
86 usage="OVERWRITE T", default_l_val=.false., lone_keyword_l_val=.true.)
87 CALL section_add_keyword(print_key, keyword)
88 CALL keyword_release(keyword)
89
90 CALL keyword_create(keyword, __location__, name="SKIP_FIRST", &
91 description="Skips the first step of a MD run (avoids duplicate step if restarted).", &
92 usage="SKIP_FIRST T", default_l_val=.false., lone_keyword_l_val=.true.)
93 CALL section_add_keyword(print_key, keyword)
94 CALL keyword_release(keyword)
95
96 CALL keyword_create(keyword, __location__, name="VERBOSE", &
97 description="Switches on verbose screen output of the Voronoi integration.", &
98 usage="VERBOSE T", default_l_val=.false., lone_keyword_l_val=.true.)
99 CALL section_add_keyword(print_key, keyword)
100 CALL keyword_release(keyword)
101
102 CALL keyword_create(keyword, __location__, name="OUTPUT_EMP", &
103 description="Writes the resulting electromagnetic moments to a binary file ""properties.emp""."// &
104 " The file name cannot be changed.", &
105 usage="OUTPUT_EMP T", default_l_val=.false., lone_keyword_l_val=.true.)
106 CALL section_add_keyword(print_key, keyword)
107 CALL keyword_release(keyword)
108
109 CALL keyword_create(keyword, __location__, name="OUTPUT_TEXT", &
110 description="Writes the resulting electromagnetic moments to text files (*.voronoi)."// &
111 " The file name is specified via FILENAME.", &
112 usage="OUTPUT_TEXT T", default_l_val=.true., lone_keyword_l_val=.true.)
113 CALL section_add_keyword(print_key, keyword)
114 CALL keyword_release(keyword)
115
116 CALL keyword_create(keyword, __location__, name="REFINEMENT_FACTOR", &
117 description="Sets the refinement factor for the Voronoi integration.", &
118 usage="REFINEMENT 2", n_var=1, default_i_val=1, type_of_var=integer_t)
119 CALL section_add_keyword(print_key, keyword)
120 CALL keyword_release(keyword)
121
122 CALL keyword_create(keyword, __location__, name="VORONOI_RADII", &
123 description="Which atomic radii to use for the radical Voronoi tessellation.", &
124 usage="VORONOI_RADII {UNITY,VDW,COVALENT,USER}", repeats=.false., n_var=1, &
125 default_i_val=voro_radii_vdw, &
126 enum_c_vals=s2a("UNITY", "VDW", "COVALENT", "USER"), &
127 enum_desc=s2a("Use unity radii (non-radical Voronoi tessellation)", "Use VdW atom radii", &
128 "Use covalent atom radii", "Use user-specified atom radii"), &
130 CALL section_add_keyword(print_key, keyword)
131 CALL keyword_release(keyword)
132
133 CALL keyword_create(keyword, __location__, name="USER_RADII", &
134 description="Defines user atom radii for the radical Voronoi tessellation (one per atom).", &
135 usage="USER_RADII {real} {real} {real}", repeats=.false., &
136 unit_str="angstrom", &
137 type_of_var=real_t, n_var=-1)
138 CALL section_add_keyword(print_key, keyword)
139 CALL keyword_release(keyword)
140
141 CALL keyword_create(keyword, __location__, name="MOLECULAR_PROPERTIES", &
142 description="Calculation of molecular properties from Voronoi integration.", &
143 usage="MOLECULAR_PROPERTIES T", default_l_val=.false., lone_keyword_l_val=.true.)
144 CALL section_add_keyword(print_key, keyword)
145 CALL keyword_release(keyword)
146
147 CALL keyword_create(keyword, __location__, name="MOLPROP_FILE_NAME", &
148 description="Root of the file name where to print molecular properties."// &
149 " filename.molprop is used.", &
150 usage="MOLPROP_FILE_NAME <FILENAME>", &
151 default_lc_val="__STD_OUT__", type_of_var=lchar_t)
152 CALL section_add_keyword(print_key, keyword)
153 CALL keyword_release(keyword)
154
155 CALL keyword_create(keyword, __location__, name="JITTER", &
156 description="The Voronoi tessellation can have issues with highly symmetric structures."// &
157 " This keyword displaces all atoms pseudo-randomly by a tiny amount (see JITTER_AMPLITUDE)"// &
158 " to break symmetry. The displacement is constant over time, so that no temporal noise is"// &
159 " introduced. The displacement is not visible to other CP2k routines (FORCE_EVAL, output)."// &
160 " It is only applied internally in the library for the Voronoi tessellation.", &
161 usage="JITTER T", default_l_val=.true., lone_keyword_l_val=.true.)
162 CALL section_add_keyword(print_key, keyword)
163 CALL keyword_release(keyword)
164
165 CALL keyword_create(keyword, __location__, name="JITTER_SEED", &
166 description="Sets the random seed for the jitter. The pseudo-random number generator"// &
167 " is re-initialized for each Voronoi tessellation so that the jitter is constant over"// &
168 " simulation time (no temporal noise).", &
169 usage="JITTER_SEED 1234", n_var=1, default_i_val=0, type_of_var=integer_t)
170 CALL section_add_keyword(print_key, keyword)
171 CALL keyword_release(keyword)
172
173 CALL keyword_create(keyword, __location__, name="JITTER_AMPLITUDE", &
174 description="Sets the maximum displacement amplitude for the jitter.", &
175 usage="JITTER_AMPLITUDE 0.01", unit_str="angstrom", n_var=1, default_r_val=1.e-3_dp*bohr, &
176 type_of_var=real_t)
177 CALL section_add_keyword(print_key, keyword)
178 CALL keyword_release(keyword)
179
180 END SUBROUTINE create_print_voronoi_section
181
182END MODULE input_cp2k_voronoi
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public brehm2021
integer, save, public brehm2020
integer, save, public thomas2015
integer, save, public brehm2018
integer, save, public rycroft2009
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public debug_print_level
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public voro_radii_user
integer, parameter, public voro_radii_vdw
integer, parameter, public voro_radii_unity
integer, parameter, public voro_radii_cov
function that build the dft section of the input
subroutine, public create_print_voronoi_section(print_key)
Create the print voronoi section.
represents keywords in an input
subroutine, public keyword_release(keyword)
releases the given keyword (see doc/ReferenceCounting.html)
subroutine, public keyword_create(keyword, location, name, description, usage, type_of_var, n_var, repeats, variants, default_val, default_l_val, default_r_val, default_lc_val, default_c_val, default_i_val, default_l_vals, default_r_vals, default_c_vals, default_i_vals, lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
creates a keyword object
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_add_keyword(section, keyword)
adds a keyword to the given section
a wrapper for basic fortran types.
integer, parameter, public real_t
integer, parameter, public lchar_t
integer, parameter, public integer_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Definition of physical constants:
Definition physcon.F:68
real(kind=dp), parameter, public bohr
Definition physcon.F:147
Utilities for string manipulations.
represent a keyword in the input
represent a section of the input file