(git:c23c79b)
Loading...
Searching...
No Matches
input_cp2k_motion_print.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \par History
10!> - taken out of input_cp2k_motion
11!> \author Ole Schuett
12! **************************************************************************************************
19 USE input_constants, ONLY: dump_atomic,&
20 dump_dcd,&
23 dump_pdb,&
34 USE string_utilities, ONLY: s2a
35#include "./base/base_uses.f90"
36
37 IMPLICIT NONE
38 PRIVATE
39
40 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
41 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_motion_print'
42
44
45CONTAINS
46
47! **************************************************************************************************
48!> \brief creates the motion%print section
49!> \param section the section to be created
50!> \author teo
51! **************************************************************************************************
52 SUBROUTINE create_motion_print_section(section)
53 TYPE(section_type), POINTER :: section
54
55 TYPE(keyword_type), POINTER :: keyword
56 TYPE(section_type), POINTER :: print_key
57
58 NULLIFY (keyword, section, print_key)
59
60 CALL section_create(section, __location__, name="print", &
61 description="Controls the printing properties during an MD/Optimization run", &
62 n_keywords=1, n_subsections=1, repeats=.true.)
63
64 CALL keyword_create(keyword, __location__, name="MEMORY_INFO", &
65 variants=["MEMORY"], &
66 description="Whether overall memory usage should be sampled and printed "// &
67 "at each MD/Optimization step.", &
68 usage="MEMORY_INFO LOGICAL", &
69 default_l_val=.true., lone_keyword_l_val=.true.)
70 CALL section_add_keyword(section, keyword)
71 CALL keyword_release(keyword)
72
73 CALL cp_print_key_section_create(print_key, __location__, "TRAJECTORY", &
74 description="Controls the output of the trajectory", &
75 print_level=low_print_level, common_iter_levels=1, &
76 filename="", unit_str="angstrom")
77 CALL add_format_keyword(keyword, print_key, pos=.true., &
78 description="Specifies the format of the output file for the trajectory.")
79 CALL section_add_subsection(section, print_key)
80 CALL section_release(print_key)
81
83 print_key, __location__, "SHELL_TRAJECTORY", &
84 description="Controls the output of the trajectory of shells when the shell-model is used ", &
85 print_level=high_print_level, common_iter_levels=1, &
86 filename="", unit_str="angstrom")
87 CALL add_format_keyword(keyword, print_key, pos=.true., &
88 description="Specifies the format of the output file for the trajectory of shells.")
89 CALL section_add_subsection(section, print_key)
90 CALL section_release(print_key)
91
92 CALL cp_print_key_section_create(print_key, __location__, "CORE_TRAJECTORY", &
93 description="Controls the output of the trajectory of cores when the shell-model is used ", &
94 print_level=high_print_level, common_iter_levels=1, &
95 filename="", unit_str="angstrom")
96 CALL add_format_keyword(keyword, print_key, pos=.true., &
97 description="Specifies the format of the output file for the trajectory of cores.")
98 CALL section_add_subsection(section, print_key)
99 CALL section_release(print_key)
100
101 CALL cp_print_key_section_create(print_key, __location__, "CELL", &
102 description="Controls the output of the simulation cell. "// &
103 "For later analysis of the trajectory it is recommendable that the "// &
104 "frequency of printing is the same as the one used for the trajectory file.", &
105 print_level=high_print_level, common_iter_levels=1, &
106 filename="")
107 CALL section_add_subsection(section, print_key)
108 CALL section_release(print_key)
109
110 CALL cp_print_key_section_create(print_key, __location__, "VELOCITIES", &
111 description="Controls the output of the atomic velocities. "// &
112 "The default unit for the atomic velocities $v$ is bohr/au_time. "// &
113 "The kinetic energy $K_i$ in [hartree] of an atom $i$ with mass $m_i$ in "// &
114 "atomic mass units [amu] (or just [u]) and velocity $v_i$ can be obtained by "// &
115 "$K_i = \frac{1}{2}f_u\,m_i\,v_i^2$ with $f_u = 1822.888$ as conversion factor "// &
116 "from [u] to [a.u.]. $f_u$ is printed in full precision in the top of the CP2K "// &
117 "output for print level MEDIUM or higher.", &
118 print_level=high_print_level, common_iter_levels=1, &
119 filename="", unit_str="bohr*au_t^-1")
120 CALL add_format_keyword(keyword, print_key, pos=.false., &
121 description="Specifies the format of the output file for the velocities.")
122 CALL section_add_subsection(section, print_key)
123 CALL section_release(print_key)
124
125 CALL cp_print_key_section_create(print_key, __location__, "SHELL_VELOCITIES", &
126 description="Controls the output of the velocities of shells when the shell model is used", &
127 print_level=high_print_level, common_iter_levels=1, &
128 filename="", unit_str="bohr*au_t^-1")
129 CALL add_format_keyword(keyword, print_key, pos=.false., &
130 description="Specifies the format of the output file for the velocities of shells.")
131 CALL section_add_subsection(section, print_key)
132 CALL section_release(print_key)
133
134 CALL cp_print_key_section_create(print_key, __location__, "CORE_VELOCITIES", &
135 description="controls the output of the velocities of cores when the shell model is used", &
136 print_level=high_print_level, common_iter_levels=1, &
137 filename="", unit_str="bohr*au_t^-1")
138 CALL add_format_keyword(keyword, print_key, pos=.false., &
139 description="Specifies the format of the output file for the velocities of cores.")
140 CALL section_add_subsection(section, print_key)
141 CALL section_release(print_key)
142
143 CALL create_structure_data_section(print_key)
144 CALL section_add_subsection(section, print_key)
145 CALL section_release(print_key)
146
148 print_key, __location__, "FORCE_MIXING_LABELS", &
149 description="Controls the output of the force mixing (FORCE_EVAL&QMMM&FORCE_MIXING) labels", &
150 print_level=high_print_level, common_iter_levels=1, &
151 filename="")
152 CALL add_format_keyword(keyword, print_key, pos=.false., &
153 description="Specifies the format of the output file for the force mixing labels.")
154 CALL section_add_subsection(section, print_key)
155 CALL section_release(print_key)
156
157 CALL cp_print_key_section_create(print_key, __location__, "FORCES", &
158 description="Controls the output of the forces", &
159 print_level=high_print_level, common_iter_levels=1, &
160 filename="", unit_str="hartree*bohr^-1")
161 CALL add_format_keyword(keyword, print_key, pos=.false., &
162 description="Specifies the format of the output file for the forces.")
163 CALL section_add_subsection(section, print_key)
164 CALL section_release(print_key)
165
166 CALL cp_print_key_section_create(print_key, __location__, "SHELL_FORCES", &
167 description="Controls the output of the forces on shells when shell-model is used", &
168 print_level=high_print_level, common_iter_levels=1, &
169 filename="", unit_str="hartree*bohr^-1")
170 CALL add_format_keyword(keyword, print_key, pos=.false., &
171 description="Specifies the format of the output file for the forces on shells.")
172 CALL section_add_subsection(section, print_key)
173 CALL section_release(print_key)
174
175 CALL cp_print_key_section_create(print_key, __location__, "CORE_FORCES", &
176 description="Controls the output of the forces on cores when shell-model is used", &
177 print_level=high_print_level, common_iter_levels=1, &
178 filename="", unit_str="hartree*bohr^-1")
179 CALL add_format_keyword(keyword, print_key, pos=.false., &
180 description="Specifies the format of the output file for the forces on cores.")
181 CALL section_add_subsection(section, print_key)
182 CALL section_release(print_key)
183
184 CALL cp_print_key_section_create(print_key, __location__, "MIXED_ENERGIES", &
185 description="Controls the output of the energies of the two "// &
186 "regular FORCE_EVALS in the MIXED method "// &
187 "printed is step,time,Etot,E_F1,E_F2,CONS_QNT", &
188 print_level=low_print_level, common_iter_levels=1, &
189 filename="")
190 CALL section_add_subsection(section, print_key)
191 CALL section_release(print_key)
192
193 CALL cp_print_key_section_create(print_key, __location__, "STRESS", &
194 description="Controls the output of the stress tensor", &
195 print_level=high_print_level, common_iter_levels=1, &
196 filename="")
197 CALL section_add_subsection(section, print_key)
198 CALL section_release(print_key)
199
200 CALL cp_print_key_section_create(print_key, __location__, "POLAR_MATRIX", &
201 description="Controls the output of the polarisability tensor during an MD run", &
202 print_level=low_print_level, common_iter_levels=1, &
203 filename="")
204 CALL section_add_subsection(section, print_key)
205 CALL section_release(print_key)
206
207 CALL cp_print_key_section_create(print_key, __location__, "RESTART", &
208 description="Controls the dumping of the restart file during runs. "// &
209 "By default keeps a short history of three restarts. See also RESTART_HISTORY", &
210 each_iter_names=s2a("MD"), each_iter_values=[20], &
211 print_level=silent_print_level, common_iter_levels=1, &
212 add_last=add_last_numeric, filename="")
213
214 CALL keyword_create(keyword, __location__, name="BACKUP_COPIES", &
215 description="Specifies the maximum number of backup copies.", &
216 usage="BACKUP_COPIES {int}", &
217 default_i_val=1)
218 CALL section_add_keyword(print_key, keyword)
219 CALL keyword_release(keyword)
220
221 CALL keyword_create(keyword, __location__, name="SPLIT_RESTART_FILE", &
222 description="If specified selected input sections, which are growing with the "// &
223 "number of atoms in the system, are written to another restart file "// &
224 "in binary format instead of the default restart file in human "// &
225 "readable ASCII format. This split of the restart file may "// &
226 "provide significant memory savings and an accelerated I/O for "// &
227 "systems with a very large number of atoms", &
228 usage="SPLIT_RESTART_FILE yes", &
229 default_l_val=.false., &
230 lone_keyword_l_val=.true.)
231 CALL section_add_keyword(print_key, keyword)
232 CALL keyword_release(keyword)
233
234 CALL section_add_subsection(section, print_key)
235 CALL section_release(print_key)
236
237 CALL cp_print_key_section_create(print_key, __location__, "RESTART_HISTORY", &
238 description="Dumps unique restart files during the run keeping all of them. "// &
239 "Most useful if recovery is needed at a later point.", &
240 print_level=low_print_level, common_iter_levels=0, &
241 each_iter_names=s2a("MD", "GEO_OPT", "ROT_OPT"), each_iter_values=[500, 500, 500], &
242 filename="")
243 CALL section_add_subsection(section, print_key)
244 CALL section_release(print_key)
245
246 CALL cp_print_key_section_create(print_key, __location__, "TRANSLATION_VECTOR", &
247 description="Dumps the translation vector applied along an MD (if any). Useful"// &
248 " for postprocessing of QMMM trajectories in which the QM fragment is continuously"// &
249 " centered in the QM box", &
250 print_level=high_print_level, common_iter_levels=1, &
251 filename="")
252 CALL section_add_subsection(section, print_key)
253 CALL section_release(print_key)
254
255 END SUBROUTINE create_motion_print_section
256
257! **************************************************************************************************
258!> \brief creates the FORMAT keyword
259!> \param keyword ...
260!> \param section will contain the pint section
261!> \param pos ...
262!> \param description ...
263!> \author Teodoro Laino 10.2008 [tlaino]
264! **************************************************************************************************
265 SUBROUTINE add_format_keyword(keyword, section, pos, description)
266 TYPE(keyword_type), POINTER :: keyword
267 TYPE(section_type), POINTER :: section
268 LOGICAL, INTENT(IN) :: pos
269 CHARACTER(LEN=*), INTENT(IN) :: description
270
271 cpassert(ASSOCIATED(section))
272 cpassert(.NOT. ASSOCIATED(keyword))
273
274 IF (pos) THEN
275
276 CALL keyword_create( &
277 keyword, __location__, name="FORMAT", &
278 description=description, usage="FORMAT (ATOMIC|DCD|PDB|XMOL|XYZ|EXTXYZ)", &
279 default_i_val=dump_xmol, &
280 enum_c_vals=s2a("ATOMIC", "DCD", "DCD_ALIGNED_CELL", "PDB", "XMOL", "XYZ", "EXTXYZ"), &
282 enum_desc=s2a("Write only the coordinates X,Y,Z without element symbols to a formatted file", &
283 "Write the coordinates (no element labels) and the cell information to a binary file", &
284 "Like DCD, but the dumped coordinates refer to an aligned cell following the common convention: "// &
285 "the cell vector **a** is aligned with the *x* axis and the cell vector **b** lies in "// &
286 "the *xy* plane. This allows the reconstruction of scaled coordinates from the DCD data only.", &
287 "Write the atomic information in PDB format to a formatted file", &
288 "Mostly known as XYZ format, provides in a formatted file: element_symbol X Y Z", &
289 "Alias name for XMOL", &
290 "Extended XYZ format including cell information. "// &
291 "For details see [ASE](https://ase-lib.org/ase/io/formatoptions.html#extxyz) "// &
292 "and [OVITO](https://www.ovito.org/manual/reference/file_formats/input/xyz.html)."))
293 CALL section_add_keyword(section, keyword)
294 CALL keyword_release(keyword)
295
296 CALL keyword_create(keyword, __location__, name="CHARGE_OCCUP", &
297 variants=["CHARGE_O"], &
298 description="Write the MM charges to the OCCUP field of the PDB file", &
299 usage="CHARGE_OCCUP logical", &
300 default_l_val=.false., lone_keyword_l_val=.true.)
301 CALL section_add_keyword(section, keyword)
302 CALL keyword_release(keyword)
303
304 CALL keyword_create(keyword, __location__, name="CHARGE_BETA", &
305 variants=["CHARGE_B"], &
306 description="Write the MM charges to the BETA field of the PDB file", &
307 usage="CHARGE_BETA logical", &
308 default_l_val=.false., lone_keyword_l_val=.true.)
309 CALL section_add_keyword(section, keyword)
310 CALL keyword_release(keyword)
311
312 CALL keyword_create(keyword, __location__, name="CHARGE_EXTENDED", &
313 description="Write the MM charges to the very last field of the PDB file (starting from column 81)", &
314 usage="CHARGE_EXTENDED logical", &
315 default_l_val=.false., lone_keyword_l_val=.true.)
316 CALL section_add_keyword(section, keyword)
317 CALL keyword_release(keyword)
318
319 ELSE
320
321 CALL keyword_create(keyword, __location__, name="FORMAT", &
322 description=description, usage="FORMAT (ATOMIC|DCD|XMOL|XYZ|EXTXYZ)", &
323 default_i_val=dump_xmol, &
324 enum_c_vals=s2a("ATOMIC", "DCD", "XMOL", "XYZ", "EXTXYZ"), &
326 enum_desc=s2a("Write only the coordinates X,Y,Z without element symbols to a formatted file", &
327 "Write the coordinates (no element labels) and the cell information to a binary file", &
328 "Mostly known as XYZ format, provides in a formatted file: element_symbol X Y Z", &
329 "Alias name for XMOL", &
330 "Extended XYZ format including cell information. "// &
331 "For details see [ASE](https://ase-lib.org/ase/io/formatoptions.html#extxyz) "// &
332 "and [OVITO](https://www.ovito.org/manual/reference/file_formats/input/xyz.html)."))
333 CALL section_add_keyword(section, keyword)
334 CALL keyword_release(keyword)
335
336 END IF
337
338 CALL keyword_create(keyword, __location__, name="PRINT_ATOM_KIND", &
339 description="Write the atom kind given in the subsys section instead of the element symbol. "// &
340 "Only valid for the XMOL and EXTXYZ format.", &
341 usage="PRINT_ATOM_KIND logical", &
342 default_l_val=.false., lone_keyword_l_val=.true.)
343 CALL section_add_keyword(section, keyword)
344 CALL keyword_release(keyword)
345
346 END SUBROUTINE add_format_keyword
347
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public low_print_level
integer, parameter, public high_print_level
integer, parameter, public add_last_numeric
integer, parameter, public silent_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 dump_xmol
integer, parameter, public dump_pdb
integer, parameter, public dump_extxyz
integer, parameter, public dump_atomic
integer, parameter, public dump_dcd_aligned_cell
integer, parameter, public dump_dcd
subroutine, public add_format_keyword(keyword, section, pos, description)
creates the FORMAT keyword
subroutine, public create_motion_print_section(section)
creates the motionprint section
builds the subsystem section of the input
subroutine, public create_structure_data_section(print_key)
creates structure data section for output.. both subsys (for initialization) and motion 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_create(section, location, name, description, n_keywords, n_subsections, repeats, citations, deprecation_notice)
creates a list of keywords
subroutine, public section_add_keyword(section, keyword)
adds a keyword to the given section
subroutine, public section_add_subsection(section, subsection)
adds a subsection to the given section
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
Utilities for string manipulations.
represent a keyword in the input
represent a section of the input file