(git:b279b6b)
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-2024 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,&
22  dump_pdb,&
23  dump_xmol
27  keyword_type
32  section_type
33  USE string_utilities, ONLY: newline,&
34  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 
45 CONTAINS
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 velocities."//newline// &
112  "The default unit for velocities is bohr/au_time. The au_time is derived from the "// &
113  "hbar value (1.054e-34 J*sec) and the value of the hartree unit of energy "// &
114  "(27.21 eV or 4.359e-18 J) as hbar/Ehartree = 2.42e-17 sec = 0.0242 fs. "// &
115  "Having an atom with a mass m in AMU the kinetic energy 1/2mv^2 will be obtained "// &
116  "in Hartree (i.e. au) multiplying by 911.447 .", &
117  print_level=high_print_level, common_iter_levels=1, &
118  filename="", unit_str="bohr*au_t^-1")
119  CALL add_format_keyword(keyword, print_key, pos=.false., &
120  description="Specifies the format of the output file for the velocities.")
121  CALL section_add_subsection(section, print_key)
122  CALL section_release(print_key)
123 
124  CALL cp_print_key_section_create(print_key, __location__, "SHELL_VELOCITIES", &
125  description="Controls the output of the velocities of shells when the shell model is used", &
126  print_level=high_print_level, common_iter_levels=1, &
127  filename="", unit_str="bohr*au_t^-1")
128  CALL add_format_keyword(keyword, print_key, pos=.false., &
129  description="Specifies the format of the output file for the velocities of shells.")
130  CALL section_add_subsection(section, print_key)
131  CALL section_release(print_key)
132 
133  CALL cp_print_key_section_create(print_key, __location__, "CORE_VELOCITIES", &
134  description="controls the output of the velocities of cores when the shell model is used", &
135  print_level=high_print_level, common_iter_levels=1, &
136  filename="", unit_str="bohr*au_t^-1")
137  CALL add_format_keyword(keyword, print_key, pos=.false., &
138  description="Specifies the format of the output file for the velocities of cores.")
139  CALL section_add_subsection(section, print_key)
140  CALL section_release(print_key)
141 
142  CALL create_structure_data_section(print_key)
143  CALL section_add_subsection(section, print_key)
144  CALL section_release(print_key)
145 
147  print_key, __location__, "FORCE_MIXING_LABELS", &
148  description="Controls the output of the force mixing (FORCE_EVAL&QMMM&FORCE_MIXING) labels", &
149  print_level=high_print_level, common_iter_levels=1, &
150  filename="")
151  CALL add_format_keyword(keyword, print_key, pos=.false., &
152  description="Specifies the format of the output file for the force mixing labels.")
153  CALL section_add_subsection(section, print_key)
154  CALL section_release(print_key)
155 
156  CALL cp_print_key_section_create(print_key, __location__, "FORCES", &
157  description="Controls the output of the forces", &
158  print_level=high_print_level, common_iter_levels=1, &
159  filename="", unit_str="hartree*bohr^-1")
160  CALL add_format_keyword(keyword, print_key, pos=.false., &
161  description="Specifies the format of the output file for the forces.")
162  CALL section_add_subsection(section, print_key)
163  CALL section_release(print_key)
164 
165  CALL cp_print_key_section_create(print_key, __location__, "SHELL_FORCES", &
166  description="Controls the output of the forces on shells when shell-model is used", &
167  print_level=high_print_level, common_iter_levels=1, &
168  filename="", unit_str="hartree*bohr^-1")
169  CALL add_format_keyword(keyword, print_key, pos=.false., &
170  description="Specifies the format of the output file for the forces on shells.")
171  CALL section_add_subsection(section, print_key)
172  CALL section_release(print_key)
173 
174  CALL cp_print_key_section_create(print_key, __location__, "CORE_FORCES", &
175  description="Controls the output of the forces on cores when shell-model is used", &
176  print_level=high_print_level, common_iter_levels=1, &
177  filename="", unit_str="hartree*bohr^-1")
178  CALL add_format_keyword(keyword, print_key, pos=.false., &
179  description="Specifies the format of the output file for the forces on cores.")
180  CALL section_add_subsection(section, print_key)
181  CALL section_release(print_key)
182 
183  CALL cp_print_key_section_create(print_key, __location__, "MIXED_ENERGIES", &
184  description="Controls the output of the energies of the two "// &
185  "regular FORCE_EVALS in the MIXED method "// &
186  "printed is step,time,Etot,E_F1,E_F2,CONS_QNT", &
187  print_level=low_print_level, common_iter_levels=1, &
188  filename="")
189  CALL section_add_subsection(section, print_key)
190  CALL section_release(print_key)
191 
192  CALL cp_print_key_section_create(print_key, __location__, "STRESS", &
193  description="Controls the output of the stress tensor", &
194  print_level=high_print_level, common_iter_levels=1, &
195  filename="")
196  CALL section_add_subsection(section, print_key)
197  CALL section_release(print_key)
198 
199  CALL cp_print_key_section_create(print_key, __location__, "POLAR_MATRIX", &
200  description="Controls the output of the polarisability tensor during an MD run", &
201  print_level=low_print_level, common_iter_levels=1, &
202  filename="")
203  CALL section_add_subsection(section, print_key)
204  CALL section_release(print_key)
205 
206  CALL cp_print_key_section_create(print_key, __location__, "RESTART", &
207  description="Controls the dumping of the restart file during runs. "// &
208  "By default keeps a short history of three restarts. See also RESTART_HISTORY", &
209  each_iter_names=s2a("MD"), each_iter_values=(/20/), &
210  print_level=silent_print_level, common_iter_levels=1, &
211  add_last=add_last_numeric, filename="")
212 
213  CALL keyword_create(keyword, __location__, name="BACKUP_COPIES", &
214  description="Specifies the maximum number of backup copies.", &
215  usage="BACKUP_COPIES {int}", &
216  default_i_val=1)
217  CALL section_add_keyword(print_key, keyword)
218  CALL keyword_release(keyword)
219 
220  CALL keyword_create(keyword, __location__, name="SPLIT_RESTART_FILE", &
221  description="If specified selected input sections, which are growing with the "// &
222  "number of atoms in the system, are written to another restart file "// &
223  "in binary format instead of the default restart file in human "// &
224  "readable ASCII format. This split of the restart file may "// &
225  "provide significant memory savings and an accelerated I/O for "// &
226  "systems with a very large number of atoms", &
227  usage="SPLIT_RESTART_FILE yes", &
228  default_l_val=.false., &
229  lone_keyword_l_val=.true.)
230  CALL section_add_keyword(print_key, keyword)
231  CALL keyword_release(keyword)
232 
233  CALL section_add_subsection(section, print_key)
234  CALL section_release(print_key)
235 
236  CALL cp_print_key_section_create(print_key, __location__, "RESTART_HISTORY", &
237  description="Dumps unique restart files during the run keeping all of them. "// &
238  "Most useful if recovery is needed at a later point.", &
239  print_level=low_print_level, common_iter_levels=0, &
240  each_iter_names=s2a("MD", "GEO_OPT", "ROT_OPT"), each_iter_values=(/500, 500, 500/), &
241  filename="")
242  CALL section_add_subsection(section, print_key)
243  CALL section_release(print_key)
244 
245  CALL cp_print_key_section_create(print_key, __location__, "TRANSLATION_VECTOR", &
246  description="Dumps the translation vector applied along an MD (if any). Useful"// &
247  " for postprocessing of QMMM trajectories in which the QM fragment is continuously"// &
248  " centered in the QM box", &
249  print_level=high_print_level, common_iter_levels=1, &
250  filename="")
251  CALL section_add_subsection(section, print_key)
252  CALL section_release(print_key)
253 
254  END SUBROUTINE create_motion_print_section
255 
256 ! **************************************************************************************************
257 !> \brief creates the FORMAT keyword
258 !> \param keyword ...
259 !> \param section will contain the pint section
260 !> \param pos ...
261 !> \param description ...
262 !> \author Teodoro Laino 10.2008 [tlaino]
263 ! **************************************************************************************************
264  SUBROUTINE add_format_keyword(keyword, section, pos, description)
265  TYPE(keyword_type), POINTER :: keyword
266  TYPE(section_type), POINTER :: section
267  LOGICAL, INTENT(IN) :: pos
268  CHARACTER(LEN=*), INTENT(IN) :: description
269 
270  cpassert(ASSOCIATED(section))
271  cpassert(.NOT. ASSOCIATED(keyword))
272 
273  IF (pos) THEN
274 
275  CALL keyword_create( &
276  keyword, __location__, name="FORMAT", &
277  description=description, usage="FORMAT (ATOMIC|DCD|PDB|XMOL|XYZ)", &
278  default_i_val=dump_xmol, &
279  enum_c_vals=s2a("ATOMIC", "DCD", "DCD_ALIGNED_CELL", "PDB", "XMOL", "XYZ"), &
281  enum_desc=s2a("Write only the coordinates X,Y,Z without element symbols to a formatted file", &
282  "Write the coordinates (no element labels) and the cell information to a binary file", &
283  "Like DCD, but the dumped coordinates refer to an aligned cell following the common convention: "// &
284  "the cell vector **a** is aligned with the *x* axis and the cell vector **b** lies in "// &
285  "the *xy* plane. This allows the reconstruction of scaled coordinates from the DCD data only.", &
286  "Write the atomic information in PDB format to a formatted file", &
287  "Mostly known as XYZ format, provides in a formatted file: element_symbol X Y Z", &
288  "Alias name for XMOL"))
289  CALL section_add_keyword(section, keyword)
290  CALL keyword_release(keyword)
291 
292  CALL keyword_create(keyword, __location__, name="CHARGE_OCCUP", &
293  variants=(/"CHARGE_O"/), &
294  description="Write the MM charges to the OCCUP field of the PDB file", &
295  usage="CHARGE_OCCUP logical", &
296  default_l_val=.false., lone_keyword_l_val=.true.)
297  CALL section_add_keyword(section, keyword)
298  CALL keyword_release(keyword)
299 
300  CALL keyword_create(keyword, __location__, name="CHARGE_BETA", &
301  variants=(/"CHARGE_B"/), &
302  description="Write the MM charges to the BETA field of the PDB file", &
303  usage="CHARGE_BETA logical", &
304  default_l_val=.false., lone_keyword_l_val=.true.)
305  CALL section_add_keyword(section, keyword)
306  CALL keyword_release(keyword)
307 
308  CALL keyword_create(keyword, __location__, name="CHARGE_EXTENDED", &
309  description="Write the MM charges to the very last field of the PDB file (starting from column 81)", &
310  usage="CHARGE_EXTENDED logical", &
311  default_l_val=.false., lone_keyword_l_val=.true.)
312  CALL section_add_keyword(section, keyword)
313  CALL keyword_release(keyword)
314 
315  ELSE
316 
317  CALL keyword_create(keyword, __location__, name="FORMAT", &
318  description=description, usage="FORMAT (ATOMIC|DCD|XMOL|XYZ)", &
319  default_i_val=dump_xmol, &
320  enum_c_vals=s2a("ATOMIC", "DCD", "XMOL", "XYZ"), &
321  enum_i_vals=(/dump_atomic, dump_dcd, dump_xmol, dump_xmol/), &
322  enum_desc=s2a("Write only the coordinates X,Y,Z without element symbols to a formatted file", &
323  "Write the coordinates (no element labels) and the cell information to a binary file", &
324  "Mostly known as XYZ format, provides in a formatted file: element_symbol X Y Z", &
325  "Alias name for XMOL"))
326  CALL section_add_keyword(section, keyword)
327  CALL keyword_release(keyword)
328 
329  END IF
330 
331  CALL keyword_create(keyword, __location__, name="PRINT_ATOM_KIND", &
332  description="Write the atom kind given in the subsys section instead of the element symbol. "// &
333  "Only valid for the XMOL format.", &
334  usage="PRINT_ELEMENT_NAME logical", &
335  default_l_val=.false., lone_keyword_l_val=.true.)
336  CALL section_add_keyword(section, keyword)
337  CALL keyword_release(keyword)
338 
339  END SUBROUTINE add_format_keyword
340 
341 END MODULE input_cp2k_motion_print
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_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)
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.
character(len=1), parameter, public newline