(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_vib.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 builds the input structure for the VIBRATIONAL_ANALYSIS module
10!> \par History
11!> 01.2008 [tlaino] Teodoro Laino - University of Zurich
12!> Creating an own module for vibrational analysis
13!> \author [tlaino]
14! **************************************************************************************************
22 USE cp_units, ONLY: cp_unit_to_cp2k
38 USE input_val_types, ONLY: integer_t,&
39 real_t
40 USE kinds, ONLY: dp
41 USE string_utilities, ONLY: s2a
42#include "../base/base_uses.f90"
43
44 IMPLICIT NONE
45 PRIVATE
46
47 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
48 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_vib'
49
50 PUBLIC :: create_vib_section
51CONTAINS
52
53! **************************************************************************************************
54!> \brief Creates the exteranal restart section
55!> \param section the section to create
56!> \author tlaino
57! **************************************************************************************************
58 SUBROUTINE create_vib_section(section)
59 TYPE(section_type), POINTER :: section
60
61 TYPE(keyword_type), POINTER :: keyword
62 TYPE(section_type), POINTER :: subsection
63
64 cpassert(.NOT. ASSOCIATED(section))
65 CALL section_create( &
66 section, __location__, name="VIBRATIONAL_ANALYSIS", &
67 description="Section to setup parameters to perform a Normal Modes, vibrational, or phonon analysis. "// &
68 "Vibrations are computed using finite differences, "// &
69 "which implies a very tight (e.g. 1E-8) threshold is needed for EPS_SCF to get accurate low frequencies. "// &
70 "The analysis assumes a stationary state (minimum or TS),"// &
71 " i.e. tight geometry optimization (MAX_FORCE) is needed as well.", &
72 n_keywords=1, n_subsections=0, repeats=.false.)
73 NULLIFY (keyword, subsection)
74
75 CALL keyword_create(keyword, __location__, name="DX", &
76 description="Specify the increment to be used to construct the HESSIAN with "// &
77 "finite difference method", &
78 default_r_val=1.0e-2_dp, unit_str="bohr")
79 CALL section_add_keyword(section, keyword)
80 CALL keyword_release(keyword)
81
82 CALL keyword_create(keyword, __location__, name="NPROC_REP", &
83 description="Specify the number of processors to be used per replica "// &
84 "environment (for parallel runs). "// &
85 "In case of mode selective calculations more than one replica will start"// &
86 " a block Davidson algorithm to track more than only one frequency", &
87 default_i_val=1)
88 CALL section_add_keyword(section, keyword)
89 CALL keyword_release(keyword)
90
91 CALL keyword_create(keyword, __location__, name="PROC_DIST_TYPE", &
92 description="Specify the topology of the mapping of processors into replicas.", &
93 usage="PROC_DIST_TYPE (INTERLEAVED|BLOCKED)", &
94 enum_c_vals=s2a("INTERLEAVED", &
95 "BLOCKED"), &
96 enum_desc=s2a("Interleaved distribution", &
97 "Blocked distribution"), &
98 enum_i_vals=(/do_rep_interleaved, do_rep_blocked/), &
99 default_i_val=do_rep_blocked)
100 CALL section_add_keyword(section, keyword)
101 CALL keyword_release(keyword)
102
103 CALL keyword_create(keyword, __location__, name="FULLY_PERIODIC", &
104 description="Avoids to clean rotations from the Hessian matrix.", &
105 default_l_val=.false., lone_keyword_l_val=.true.)
106 CALL section_add_keyword(section, keyword)
107 CALL keyword_release(keyword)
108
109 CALL keyword_create(keyword, __location__, name="INTENSITIES", &
110 description="Calculation of the IR/Raman-Intensities. "// &
111 "Calculation of dipoles and/or polarizabilities have to be "// &
112 "specified explicitly in DFT/PRINT/MOMENTS and/or "// &
113 "PROPERTIES/LINRES/POLAR", &
114 default_l_val=.false., lone_keyword_l_val=.true.)
115 CALL section_add_keyword(section, keyword)
116 CALL keyword_release(keyword)
117
118 CALL keyword_create(keyword, __location__, name="THERMOCHEMISTRY", &
119 description="Calculation of the thermochemical data. Valid for molecules in the gas phase. ", &
120 default_l_val=.false., lone_keyword_l_val=.true.)
121 CALL section_add_keyword(section, keyword)
122 CALL keyword_release(keyword)
123
124 CALL keyword_create(keyword, __location__, name="TC_TEMPERATURE", &
125 description="Temperature for the calculation of the thermochemical data ", &
126 usage="tc_temperature 325.0", default_r_val=cp_unit_to_cp2k(value=273.150_dp, unit_str="K"), &
127 unit_str="K")
128 CALL section_add_keyword(section, keyword)
129 CALL keyword_release(keyword)
130
131 CALL keyword_create(keyword, __location__, name="TC_PRESSURE", &
132 description="Pressure for the calculation of the thermochemical data ", &
133 default_r_val=cp_unit_to_cp2k(value=101325.0_dp, unit_str="Pa"), unit_str="Pa")
134 CALL section_add_keyword(section, keyword)
135 CALL keyword_release(keyword)
136
137 CALL create_mode_selective_section(subsection)
138 CALL section_add_subsection(section, subsection)
139 CALL section_release(subsection)
140
141 CALL create_print_vib_section(subsection)
142 CALL section_add_subsection(section, subsection)
143 CALL section_release(subsection)
144 END SUBROUTINE create_vib_section
145
146! **************************************************************************************************
147!> \brief Create the print section for VIB
148!> \param section the section to create
149!> \author Teodoro Laino [tlaino] - 10.2008
150! **************************************************************************************************
151 SUBROUTINE create_print_vib_section(section)
152 TYPE(section_type), POINTER :: section
153
154 TYPE(keyword_type), POINTER :: keyword
155 TYPE(section_type), POINTER :: print_key
156
157 cpassert(.NOT. ASSOCIATED(section))
158 CALL section_create(section, __location__, name="PRINT", &
159 description="Section controlling the print information during a vibrational "// &
160 "analysis.", n_keywords=1, n_subsections=0, repeats=.false.)
161 NULLIFY (keyword, print_key)
162
163 CALL cp_print_key_section_create(print_key, __location__, "BANNER", &
164 description="Controls the printing of the vibrational analysis banner", &
165 print_level=low_print_level, common_iter_levels=1, &
166 filename="__STD_OUT__")
167 CALL section_add_subsection(section, print_key)
168 CALL section_release(print_key)
169
170 CALL cp_print_key_section_create(print_key, __location__, "PROGRAM_RUN_INFO", &
171 description="Controls the printing basic info about the vibrational method", &
172 print_level=medium_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
173 CALL section_add_subsection(section, print_key)
174 CALL section_release(print_key)
175
176 CALL cp_print_key_section_create(print_key, __location__, "MOLDEN_VIB", &
177 description="Controls the printing for visualization in molden format", &
178 print_level=low_print_level, add_last=add_last_numeric, filename="VIBRATIONS")
179 CALL section_add_subsection(section, print_key)
180 CALL section_release(print_key)
181
182 CALL cp_print_key_section_create(print_key, __location__, "ROTATIONAL_INFO", &
183 description="Controls the printing basic info during the cleaning of the "// &
184 "rotational degrees of freedom.", &
185 print_level=debug_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
186 ! Print_key keywords
187 CALL keyword_create(keyword, __location__, name="COORDINATES", &
188 description="Prints atomic coordinates after rotation", &
189 default_l_val=.false., lone_keyword_l_val=.true.)
190 CALL section_add_keyword(print_key, keyword)
191 CALL keyword_release(keyword)
192 CALL section_add_subsection(section, print_key)
193 CALL section_release(print_key)
194
195 CALL cp_print_key_section_create(print_key, __location__, "CARTESIAN_EIGS", &
196 description="Controls the printing of Cartesian "// &
197 "frequencies and eigenvectors of the Hessian used "// &
198 "for initializing ensemble for MD calculations. "// &
199 "This should always print to a file, and will not "// &
200 "effect the same frequencies and eigenvectors printed "// &
201 "in the main vibrational analysis output", &
202 print_level=low_print_level, &
203 add_last=add_last_numeric, &
204 filename="VIBRATIONS")
205 CALL keyword_create(keyword, __location__, name="BACKUP_COPIES", &
206 description="Specifies the maximum number of backup copies.", &
207 usage="BACKUP_COPIES {int}", &
208 default_i_val=1)
209 CALL section_add_keyword(print_key, keyword)
210 CALL keyword_release(keyword)
211 CALL section_add_subsection(section, print_key)
212 CALL section_release(print_key)
213
214 CALL cp_print_key_section_create(print_key, __location__, name="NAMD_PRINT", &
215 description="Adjust cartesian eigenvalues / vectors to NewtonX format.", &
216 print_level=debug_print_level + 1, add_last=add_last_numeric, &
217 filename="FullNormalizedCartesian")
218 CALL keyword_create(keyword, __location__, name="BACKUP_COPIES", &
219 description="Specifies the maximum number of backup copies.", &
220 usage="BACKUP_COPIES {int}", &
221 default_i_val=1)
222 CALL section_add_keyword(print_key, keyword)
223 CALL keyword_release(keyword)
224 CALL section_add_subsection(section, print_key)
225 CALL section_release(print_key)
226
227 CALL cp_print_key_section_create(print_key, __location__, "HESSIAN", &
228 description="Write the Hessian matrix from a vibrational analysis calculation "// &
229 "into a binary file.", &
230 print_level=low_print_level, add_last=add_last_numeric, filename="Hessian")
231 CALL section_add_subsection(section, print_key)
232 CALL section_release(print_key)
233
234 END SUBROUTINE create_print_vib_section
235
236! **************************************************************************************************
237!> \brief Create the input section for MODE selective
238!> \param section the section to create
239!> \author fschiff
240! **************************************************************************************************
241 SUBROUTINE create_mode_selective_section(section)
242 TYPE(section_type), POINTER :: section
243
244 TYPE(keyword_type), POINTER :: keyword
245 TYPE(section_type), POINTER :: print_key, subsection
246
247 NULLIFY (keyword, subsection, print_key)
248 cpassert(.NOT. ASSOCIATED(section))
249 CALL section_create(section, __location__, name="MODE_SELECTIVE", &
250 description="All parameters needed for to run a mode selective vibrational analysis. "// &
251 "The keywords FREQUENCY, RANGE, and the subsection INVOLVED_ATOMS are mutually exclusive.", &
252 n_keywords=8, n_subsections=1, repeats=.false.)
253
254 CALL keyword_create(keyword, __location__, name="FREQUENCY", &
255 description="value close to the expected value of the frequency to look for. "// &
256 "If the block Davidson algorithm is applied, the nrep closest frequencies are tracked. ", &
257 usage="FREQUENCY {REAL}", default_r_val=-1._dp)
258 CALL section_add_keyword(section, keyword)
259 CALL keyword_release(keyword)
260
261 CALL keyword_create(keyword, __location__, name="RANGE", &
262 description="Track modes in a given range of frequencies. "// &
263 "No warranty that the set of frequencies is complete.", &
264 usage="RANGE {REAL} {REAL}", &
265 n_var=-1, type_of_var=real_t)
266 CALL section_add_keyword(section, keyword)
267 CALL keyword_release(keyword)
268
269 CALL keyword_create(keyword, __location__, name="LOWEST_FREQUENCY", &
270 description="Lowest frequency mode to include when writing output. "// &
271 "Use a negative value to print imaginary frequencies. "// &
272 "Useful for visualizing the imaginary frequency along a reaction path coordinate "// &
273 "Depending on accuracy settings, the output might include spurious low frequency "// &
274 "imaginary modes which should be visually checked (see MOLDEN_VIB).", &
275 usage="LOWEST_FREQUENCY <REAL>", default_r_val=0.0_dp)
276 CALL section_add_keyword(section, keyword)
277 CALL keyword_release(keyword)
278
279 CALL keyword_create(keyword, __location__, name="ATOMS", &
280 description="Specifies the list of atoms which should be displaced for the Initial guess", &
281 usage="ATOMS {integer} {integer} .. {integer}", &
282 n_var=-1, type_of_var=integer_t)
283 CALL section_add_keyword(section, keyword)
284 CALL keyword_release(keyword)
285
286 CALL keyword_create(keyword, __location__, name="EPS_MAX_VAL", &
287 description="Convergence criterion for the davidson algorithm. Specifies the maximal value in the "// &
288 "residuum vectors ", &
289 usage="EPS_MAX_VAL {REAL}", default_r_val=5.0e-7_dp)
290 CALL section_add_keyword(section, keyword)
291 CALL keyword_release(keyword)
292
293 CALL keyword_create( &
294 keyword, __location__, name="EPS_NORM", &
295 description="Convergence criterion for the davidson algorithm. Specifies the maximal value of the norm "// &
296 "of the residuum vectors ", &
297 usage="EPS_NORM {REAL}", default_r_val=2.0e-6_dp)
298 CALL section_add_keyword(section, keyword)
299 CALL keyword_release(keyword)
300
301 CALL keyword_create( &
302 keyword, __location__, name="INITIAL_GUESS", &
303 description="The type of initial guess for the normal modes", &
304 usage="INITIAL_GUESS BFGS_HESS", &
305 default_i_val=ms_guess_atomic, &
306 enum_c_vals=s2a("BFGS_HESS", "ATOMIC", "RESTART", "RESTART_VEC", "MOLDEN_RESTART"), &
307 enum_desc=s2a("get the first displacement vector out of the BFGS approximate Hessian", &
308 "use random displacements for a set of atoms specified", &
309 "use data from MS_RESTART as initial guess", &
310 "use a vector from MS_RESTART, useful if you want to increase accurcy by changing functionals or basis", &
311 "use the .mol file of a former run, to restart a vector"// &
312 " (similar to Restart_vec, but a different file FORMAT is used)"), &
314 CALL section_add_keyword(section, keyword)
315 CALL keyword_release(keyword)
316
317 CALL keyword_create(keyword, __location__, name="RESTART_FILE_NAME", &
318 description="Specifies the name of the file used to create the restarted vectors", &
319 usage="RESTART_FILE_NAME {filename}", &
320 default_lc_val="")
321 CALL section_add_keyword(section, keyword)
322 CALL keyword_release(keyword)
323
324 CALL create_involved_atoms_section(subsection)
325 CALL section_add_subsection(section, subsection)
326 CALL section_release(subsection)
327
328 CALL section_create(subsection, __location__, name="PRINT", &
329 description="Controls the printing mode selective vibrational analysis", &
330 n_keywords=0, n_subsections=1, repeats=.true.)
331
332 CALL cp_print_key_section_create(print_key, __location__, "MS_RESTART", &
333 description="Controls the printing of the Mode Selective Restart file.", &
334 print_level=silent_print_level, common_iter_levels=1, &
335 add_last=add_last_numeric, filename="")
336 CALL section_add_subsection(subsection, print_key)
337 CALL section_release(print_key)
338
339 CALL section_add_subsection(section, subsection)
340 CALL section_release(subsection)
341
342 END SUBROUTINE create_mode_selective_section
343
344! **************************************************************************************************
345!> \brief Create the input section for Ivolved_atoms keyword in mode selective
346!> \param section the section to create
347!> \author fschiff
348! **************************************************************************************************
349 SUBROUTINE create_involved_atoms_section(section)
350 TYPE(section_type), POINTER :: section
351
352 TYPE(keyword_type), POINTER :: keyword
353
354 NULLIFY (keyword)
355 cpassert(.NOT. ASSOCIATED(section))
356 CALL section_create( &
357 section, __location__, name="INVOLVED_ATOMS", &
358 description="All parameters needed for the tracking of modes dominated by the motion of selected atoms. "// &
359 "Warning, if many atoms are involved, only low frequency modes are detected, "// &
360 "since they are more delocalized and match the tracked eigenvector.", &
361 n_keywords=2, n_subsections=0, repeats=.false.)
362
363 CALL keyword_create( &
364 keyword, __location__, name="RANGE", &
365 description=" Specifies the range of wavenumbers in which the modes related to the ATOMS have to be tracked."// &
366 " If not specified frequencies >400cm-1 will be used to avoid tracking of translational or rotational modes", &
367 usage="RANGE {REAL} {REAL}", &
368 n_var=-1, type_of_var=real_t)
369 CALL section_add_keyword(section, keyword)
370 CALL keyword_release(keyword)
371
372 CALL keyword_create( &
373 keyword, __location__, name="INVOLVED_ATOMS", &
374 description="Specifies the list of atoms on which the tracked eigenvector should have the highest value "// &
375 "similar to looking for the vibration of a set of atoms", &
376 usage="INVOLVED_ATOMS {integer} {integer} .. {integer}", &
377 n_var=-1, type_of_var=integer_t)
378 CALL section_add_keyword(section, keyword)
379 CALL keyword_release(keyword)
380
381 END SUBROUTINE create_involved_atoms_section
382
383END MODULE input_cp2k_vib
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
integer, parameter, public low_print_level
integer, parameter, public medium_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
unit conversion facility
Definition cp_units.F:30
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
Definition cp_units.F:1150
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_rep_interleaved
integer, parameter, public do_rep_blocked
integer, parameter, public ms_guess_restart
integer, parameter, public ms_guess_restart_vec
integer, parameter, public ms_guess_molden
integer, parameter, public ms_guess_atomic
integer, parameter, public ms_guess_bfgs
builds the input structure for the VIBRATIONAL_ANALYSIS module
subroutine, public create_vib_section(section)
Creates the exteranal restart 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)
a wrapper for basic fortran types.
integer, parameter, public real_t
integer, parameter, public integer_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Utilities for string manipulations.
represent a keyword in the input
represent a section of the input file