(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_mixed.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 MIXED environment
10!> \par History
11!> 10.2008 created [tlaino]
12!> \author Teodoro Laino [tlaino] - University of Zurich
13! **************************************************************************************************
15 USE bibliography, ONLY: holmberg2017,&
23 USE input_constants, ONLY: mix_cdft,&
37 USE input_val_types, ONLY: char_t,&
38 integer_t,&
39 lchar_t,&
40 logical_t,&
41 real_t
42 USE kinds, ONLY: dp
43 USE string_utilities, ONLY: s2a
44#include "./base/base_uses.f90"
45
46 IMPLICIT NONE
47 PRIVATE
48
49 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
50 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_mixed'
51
52 PUBLIC :: create_mix_section
53
54CONTAINS
55
56! **************************************************************************************************
57!> \brief Create the input section for MIXED.
58!> \param section the section to create
59!> \author fschiff
60! **************************************************************************************************
61 SUBROUTINE create_mix_section(section)
62 TYPE(section_type), POINTER :: section
63
64 TYPE(keyword_type), POINTER :: keyword
65 TYPE(section_type), POINTER :: sub2section, sub3section, subsection
66
67 cpassert(.NOT. ASSOCIATED(section))
68 CALL section_create(section, __location__, name="MIXED", &
69 description="This section contains all information to run with a hamiltonian "// &
70 "defined by a mixing of force_evals", &
71 n_keywords=1, n_subsections=0, repeats=.false.)
72 NULLIFY (keyword, subsection)
73
74 CALL keyword_create( &
75 keyword, __location__, name="MIXING_TYPE", &
76 description="The type of mixing to be employed", &
77 usage="MIXING_TYPE LINEAR_COMBINATION", &
78 default_i_val=mix_linear_combination, &
79 enum_c_vals=s2a("LINEAR_COMBINATION", &
80 "MINIMUM", &
81 "COUPLED", &
82 "RESTRAINT", &
83 "GENMIX", &
84 "MIXED_CDFT"), &
85 enum_desc=s2a("Linear combination of force envs (support only 2 force_evals)", &
86 "Use the force env with the minimum energy (support only 2 force_evals)", &
87 "Consider the force envs as a two state system with a given"// &
88 " coupling matrix element (support only 2 force_evals)", &
89 "Use the difference between the energy of the force envs as a"// &
90 " restraint on the first (support only 2 force_evals)", &
91 "Defines a user-driven generica coupling (support for an unlimited number of force_eval)", &
92 "Consider each force env as a CDFT state (supports an unlimited number of force_eval "// &
93 "for calculation of CDFT properties, but only two states can be mixed for forces)."), &
95 mix_cdft/))
96 CALL section_add_keyword(section, keyword)
97 CALL keyword_release(keyword)
98
99 CALL keyword_create(keyword, __location__, name="GROUP_PARTITION", &
100 description="gives the exact number of processors for each group."// &
101 " If not specified processors allocated will be equally distributed for"// &
102 " the specified subforce_eval, trying to build a number of groups equal to the"// &
103 " number of subforce_eval specified.", &
104 usage="group_partition 2 2 4 2 4 ", type_of_var=integer_t, n_var=-1)
105 CALL section_add_keyword(section, keyword)
106 CALL keyword_release(keyword)
107
108 CALL keyword_create(keyword, __location__, name="NGROUPS", variants=(/"NGROUP"/), &
109 description="Gives the wanted number of groups. If not specified the number"// &
110 " of groups is set to the number of subforce_eval defined.", &
111 usage="ngroups 4", type_of_var=integer_t)
112 CALL section_add_keyword(section, keyword)
113 CALL keyword_release(keyword)
114
115 ! Double force_eval
116 CALL section_create(subsection, __location__, name="LINEAR", &
117 description="Linear combination between two force_eval: F= lambda F1 + (1-lambda) F2", &
118 n_keywords=1, n_subsections=0, repeats=.false.)
119
120 CALL keyword_create(keyword, __location__, name="LAMBDA", &
121 description="Specify the mixing parameter lambda in the formula.", &
122 usage="lambda <REAL>", type_of_var=real_t)
123 CALL section_add_keyword(subsection, keyword)
124 CALL keyword_release(keyword)
125
126 CALL section_add_subsection(section, subsection)
127 CALL section_release(subsection)
128 ! Mixed CDFT section
129 CALL section_create(subsection, __location__, name="MIXED_CDFT", &
130 description="Calculate properties involving multiple constrained states. "// &
131 "Each repetition of the FORCE_EVAL section defines a new CDFT state that is "// &
132 "included in the simulation. The DFT&QS&CDFT section must be active in each "// &
133 "FORCE_EVAL and it must be consistently defined. When the keyword "// &
134 "MIXED&NGROUPS is set to a value 2 or larger, the CDFT states are solved in "// &
135 "parallel, whereas when it is set to 1, the states are solved in serial. "// &
136 "During MD, the system can be translated using only two of the CDFT states, "// &
137 "which are selected with the keyword FORCE_STATES. The forces are determined "// &
138 "by the linear combination F= lambda F1 + (1-lambda) F2.", &
139 n_keywords=11, n_subsections=2, repeats=.false., citations=(/holmberg2017, holmberg2018/))
140
141 CALL keyword_create(keyword, __location__, name="LAMBDA", &
142 description="Specify the mixing parameter lambda in the formula.", &
143 usage="lambda <REAL>", type_of_var=real_t)
144 CALL section_add_keyword(subsection, keyword)
145 CALL keyword_release(keyword)
146
147 CALL keyword_create(keyword, __location__, name="FORCE_STATES", &
148 description="Defines the CDFT states used to translate the system. ", &
149 usage="FORCE_STATES 1 1", n_var=2, &
150 default_i_vals=(/1, 2/), type_of_var=integer_t)
151 CALL section_add_keyword(subsection, keyword)
152 CALL keyword_release(keyword)
153
154 CALL keyword_create(keyword, __location__, name="COUPLING", &
155 description="Parameter determining how often the CDFT electronic coupling element "// &
156 "is calculated. Use a negative number to disable and 0 means every step. By default, "// &
157 "the coupling is calculated by rotating the CDFT states to eigenstates of the weight "// &
158 "function matrix when a single constraint is active and the constraint definitions are "// &
159 "identical in both CDFT states. Otherwise uses Lowdin orthogonalization. For more than "// &
160 "two CDFT states, the couplings are not computed pairwise and the values might "// &
161 "deviate from values computed separately for each unique CDFT state pair.", &
162 usage="COUPLING <INT>", &
163 default_i_val=-1, &
164 type_of_var=integer_t, n_var=1)
165 CALL section_add_keyword(subsection, keyword)
166 CALL keyword_release(keyword)
167
168 CALL keyword_create(keyword, __location__, name="PARALLEL_BUILD", &
169 description="Build CDFT weight function and gradients in parallel on all "// &
170 "N MPI processors before starting the CDFT SCF calculations of the 2 "// &
171 "involved CDFT states in parallel on N/2 processors. Supports only Becke "// &
172 "constraints that are identical in both states. Limited to 1 "// &
173 "charge constraint per state (different target values). "// &
174 "The keyword MIXED&NGROUPS must be set to 2.", &
175 usage="PARALLEL_BUILD TRUE", type_of_var=logical_t, &
176 default_l_val=.false., lone_keyword_l_val=.true.)
177 CALL section_add_keyword(subsection, keyword)
178 CALL keyword_release(keyword)
179
180 CALL keyword_create(keyword, __location__, name="DLB", &
181 description="Controls the activation of dynamic load balancing during a mixed CDFT calculation."// &
182 " Requires Gaussian cavity confinement. Works only in conjunction with keyword PARALLEL_BUILD.", &
183 usage="DLB", type_of_var=logical_t, &
184 default_l_val=.false., lone_keyword_l_val=.true.)
185 CALL section_add_keyword(subsection, keyword)
186 CALL keyword_release(keyword)
187
188 CALL keyword_create(keyword, __location__, name="METRIC", variants=(/"COUPLING_METRIC"/), &
189 description="Compute reliability metric for the CDFT electronic coupling element by "// &
190 "diagonalizing the difference density matrix.", &
191 usage="METRIC", type_of_var=logical_t, &
192 default_l_val=.false., lone_keyword_l_val=.true., &
193 citations=(/mavros2015/))
194 CALL section_add_keyword(subsection, keyword)
195 CALL keyword_release(keyword)
196
197 CALL keyword_create(keyword, __location__, name="WFN_OVERLAP", &
198 description="Compute the CDFT electronic coupling element using the wavefunction overlap "// &
199 "method in addition to the standard method defined by the keyword COUPLING. "// &
200 "In this method, the unconstrained KS ground state wavefunction (WFN_RESTART_FILE_NAME) "// &
201 "is represented as a linear combination of the CDFT states. For more than two CDFT states, "// &
202 "the coupling is computed pairwise for every state pair (contrary to other coupling methods).", &
203 usage="WFN_OVERLAP", type_of_var=logical_t, &
204 default_l_val=.false., lone_keyword_l_val=.true., &
205 citations=(/migliore2009/))
206 CALL section_add_keyword(subsection, keyword)
207 CALL keyword_release(keyword)
208
209 CALL keyword_create(keyword, __location__, name="LOWDIN", &
210 description="Compute the CDFT electronic coupling element using Lowdin orthogonalization. "// &
211 "This is the default behavior with multiple constraints and nonidentical constraints. "// &
212 "By activating this keyword, this method is also used to compute the coupling "// &
213 "when a single constraint is active in addition to the standard method.", &
214 usage="LOWDIN", type_of_var=logical_t, &
215 default_l_val=.false., lone_keyword_l_val=.true.)
216 CALL section_add_keyword(subsection, keyword)
217 CALL keyword_release(keyword)
218
219 CALL keyword_create(keyword, __location__, name="CI", variants=(/"CONFIGURATION_INTERACTION"/), &
220 description="Perform a CDFT configuration interaction calculation (CDFT-CI). "// &
221 "The CI vector is expanded in the basis of the CDFT states. Diagonalizes the "// &
222 "nonorthogonal diabatic CDFT Hamiltonian. The energies and expansion coefficients "// &
223 "of the CDFT-CI states are outputted. Keyword COUPLING must be active "// &
224 "to use this feature.", &
225 usage="LOWDIN", type_of_var=logical_t, &
226 default_l_val=.false., lone_keyword_l_val=.true.)
227 CALL section_add_keyword(subsection, keyword)
228 CALL keyword_release(keyword)
229
230 CALL keyword_create(keyword, __location__, name="NONORTHOGONAL_COUPLING", &
231 variants=(/"NONORTHO_COUPLING"/), &
232 description="Print out the nonorthogonal diabatic CDFT coupling between states, "// &
233 "as it appears in the mixed CDFT Hamiltonian before orthogonalization (coupling "// &
234 "calculations) and CDFT-CI. Useful for (re)constructing the Hamiltonian for additional "// &
235 "analysis. This is the CDFT interaction energy between states.", &
236 usage="NONORTHOGONAL_COUPLING", type_of_var=logical_t, &
237 default_l_val=.false., lone_keyword_l_val=.true.)
238 CALL section_add_keyword(subsection, keyword)
239 CALL keyword_release(keyword)
240
241 CALL keyword_create(keyword, __location__, name="SCALE_WITH_OCCUPATION_NUMBERS", &
242 description="Scale molecular orbitals with occupation numbers before calculating "// &
243 "the electronic coupling. Affects only simulations which employ MO smearing. "// &
244 "Disabling this keyword in conjunction with a properly selected EPS_OCCUPIED "// &
245 "threshold might be useful in systems with a large number of fractionally "// &
246 "occupied orbitals.", &
247 usage="SCALE_WITH_OCCUPATION_NUMBERS FALSE", type_of_var=logical_t, &
248 default_l_val=.true., lone_keyword_l_val=.true.)
249 CALL section_add_keyword(subsection, keyword)
250 CALL keyword_release(keyword)
251
252 CALL keyword_create(keyword, __location__, name="WFN_RESTART_FILE_NAME", &
253 description="Name of the wavefunction restart file that defines the unconstrained"// &
254 " KS ground state, which is used to compute the electronic coupling with"// &
255 " the wavefunction overlap method. May include a path.", &
256 usage="WFN_RESTART_FILE_NAME <FILENAME>", &
257 type_of_var=lchar_t)
258 CALL section_add_keyword(subsection, keyword)
259 CALL keyword_release(keyword)
260
261 CALL keyword_create(keyword, __location__, name="EPS_SVD", &
262 description="Determines the matrix inversion solver needed to compute the coupling."// &
263 " Default value implies LU decomposition, while values between 0.0 and 1.0"// &
264 " imply SVD decomposition. For SVD, the value acts as a threshold"// &
265 " for screening singular values so that only values above it are included"// &
266 " in the matrix pseudoinverse.", &
267 usage="EPS_SVD <REAL>", type_of_var=real_t, &
268 default_r_val=0.0_dp, repeats=.false.)
269 CALL section_add_keyword(subsection, keyword)
270 CALL keyword_release(keyword)
271
272 CALL keyword_create(keyword, __location__, name="EPS_OCCUPIED", &
273 description="Threshold for determining which molecular orbitals are considered occupied"// &
274 " when fractional and/or empty orbitals are employed. Can and usually should be less than"// &
275 " the threshold EPS_FERMI_DIRAC defined in section SCF&SMEAR. Note that the number occupied"// &
276 " MOs should be constant in each CDFT state, since the CDFT coupling is only defined between"// &
277 " states in the same spin state. Fractionally occupied MOs might exhibit linear dependencies"// &
278 " and a singular value decomposition (EPS_SVD) can be used for removing these.", &
279 usage="EPS_OCCUPIED <REAL>", type_of_var=real_t, &
280 default_r_val=1.0e-6_dp, repeats=.false.)
281 CALL section_add_keyword(subsection, keyword)
282 CALL keyword_release(keyword)
283
284 CALL keyword_create(keyword, __location__, name="LOAD_SCALE", &
285 description="Control parameter for dynamic load balancing during a mixed CDFT calculation."// &
286 " See code for details. Works only in conjunction with keyword PARALLEL_BUILD.", &
287 usage="LOAD_SCALE <REAL>", type_of_var=real_t, &
288 default_r_val=2.0_dp)
289 CALL section_add_keyword(subsection, keyword)
290 CALL keyword_release(keyword)
291
292 CALL keyword_create(keyword, __location__, name="MORE_WORK", &
293 description="Control parameter for dynamic load balancing during a mixed CDFT calculation."// &
294 " See code for details. Works only in conjunction with keyword PARALLEL_BUILD.", &
295 usage="MORE_WORK <INT>", type_of_var=integer_t, &
296 default_i_val=0, repeats=.false.)
297 CALL section_add_keyword(subsection, keyword)
298 CALL keyword_release(keyword)
299
300 CALL keyword_create(keyword, __location__, name="VERY_OVERLOADED", &
301 description="Control parameter for dynamic load balancing during a mixed CDFT calculation."// &
302 " See code for details. Works only in conjunction with keyword PARALLEL_BUILD.", &
303 usage="VERY_OVERLOADED <REAL>", type_of_var=real_t, &
304 default_r_val=0.0_dp, repeats=.false.)
305 CALL section_add_keyword(subsection, keyword)
306 CALL keyword_release(keyword)
307
308 CALL keyword_create(keyword, __location__, name="BLOCK_DIAGONALIZE", &
309 description="Block diagonalize the CDFT Hamiltonian. Control settings should be given in "// &
310 "section &BLOCK_DIAGONALIZE. All requested electronic couplings are printed out after "// &
311 "block diagonalization. When CDFT-CI and block diagonalization are both requested, "// &
312 "the CI calculation is performed using the block diagonalized Hamiltonian.", &
313 usage="BLOCK_DIAGONALIZE", type_of_var=logical_t, &
314 default_l_val=.false., lone_keyword_l_val=.true.)
315 CALL section_add_keyword(subsection, keyword)
316 CALL keyword_release(keyword)
317
318 NULLIFY (sub2section)
319 CALL create_mixed_cdft_block_section(sub2section)
320 CALL section_add_subsection(subsection, sub2section)
321 CALL section_release(sub2section)
322
323 CALL create_print_mixed_cdft_section(sub2section)
324 CALL section_add_subsection(subsection, sub2section)
325 CALL section_release(sub2section)
326
327 CALL section_add_subsection(section, subsection)
328 CALL section_release(subsection)
329 !
330 CALL section_create(subsection, __location__, name="COUPLING", &
331 description="Coupling between two force_eval: E=(E1+E2 - sqrt((E1-E2)**2+4*H12**2))/2", &
332 n_keywords=1, n_subsections=0, repeats=.false.)
333 CALL keyword_create(keyword, __location__, name="COUPLING_PARAMETER", &
334 description="Coupling parameter H12 used in the coupling", &
335 usage="COUPLING_PARAMETER <REAL>", type_of_var=real_t)
336 CALL section_add_keyword(subsection, keyword)
337 CALL keyword_release(keyword)
338 CALL section_add_subsection(section, subsection)
339 CALL section_release(subsection)
340
341 CALL section_create(subsection, __location__, name="RESTRAINT", &
342 description="Restraint between two force_eval: E = E1 + k*(E1-E2-t)**2", &
343 n_keywords=1, n_subsections=0, repeats=.false.)
344 CALL keyword_create(keyword, __location__, name="RESTRAINT_TARGET", &
345 description="Target value of the restraint (t) ", &
346 usage="RESTRAINT_TARGET <REAL>", type_of_var=real_t)
347 CALL section_add_keyword(subsection, keyword)
348 CALL keyword_release(keyword)
349
350 CALL keyword_create(keyword, __location__, name="RESTRAINT_STRENGTH", &
351 description="Strength of the restraint (k) in "// &
352 "k*(E1-E2-t)**2", &
353 usage="RESTRAINT_STRENGTH <REAL>", type_of_var=real_t)
354 CALL section_add_keyword(subsection, keyword)
355 CALL keyword_release(keyword)
356 CALL section_add_subsection(section, subsection)
357 CALL section_release(subsection)
358
359 ! Multiple force_eval
360 CALL section_create(subsection, __location__, name="GENERIC", &
361 description="User driven coupling between two or more force_eval.", &
362 n_keywords=1, n_subsections=0, repeats=.false.)
363 CALL keyword_create(keyword, __location__, name="MIXING_FUNCTION", &
364 description="Specifies the mixing functional form in mathematical notation.", &
365 usage="MIXING_FUNCTION (E1+E2-LOG(E1/E2))", type_of_var=lchar_t, &
366 n_var=1)
367 CALL section_add_keyword(subsection, keyword)
368 CALL keyword_release(keyword)
369
370 CALL keyword_create(keyword, __location__, name="VARIABLES", &
371 description="Defines the variables of the functional form. To allow an efficient"// &
372 " mapping the order of the energy variables will be considered identical to the"// &
373 " order of the force_eval in the force_eval_order list.", &
374 usage="VARIABLES x", type_of_var=char_t, &
375 n_var=-1)
376 CALL section_add_keyword(subsection, keyword)
377 CALL keyword_release(keyword)
378
379 CALL keyword_create(keyword, __location__, name="PARAMETERS", &
380 description="Defines the parameters of the functional form", &
381 usage="PARAMETERS a b D", type_of_var=char_t, &
382 n_var=-1, repeats=.true.)
383 CALL section_add_keyword(subsection, keyword)
384 CALL keyword_release(keyword)
385
386 CALL keyword_create(keyword, __location__, name="VALUES", &
387 description="Defines the values of parameter of the functional form", &
388 usage="VALUES ", type_of_var=real_t, &
389 n_var=-1, repeats=.true., unit_str="internal_cp2k")
390 CALL section_add_keyword(subsection, keyword)
391 CALL keyword_release(keyword)
392
393 CALL keyword_create(keyword, __location__, name="UNITS", &
394 description="Optionally, allows to define valid CP2K unit strings for each parameter value. "// &
395 "It is assumed that the corresponding parameter value is specified in this unit.", &
396 usage="UNITS angstrom eV*angstrom^-1 angstrom^1 K", type_of_var=char_t, &
397 n_var=-1, repeats=.true.)
398 CALL section_add_keyword(subsection, keyword)
399 CALL keyword_release(keyword)
400
401 CALL keyword_create(keyword, __location__, name="DX", &
402 description="Parameter used for computing the derivative with the Ridders' method.", &
403 usage="DX <REAL>", default_r_val=0.1_dp, unit_str="bohr")
404 CALL section_add_keyword(subsection, keyword)
405 CALL keyword_release(keyword)
406
407 CALL keyword_create(keyword, __location__, name="ERROR_LIMIT", &
408 description="Checks that the error in computing the derivative is not larger than "// &
409 "the value set; in case error is larger a warning message is printed.", &
410 usage="ERROR_LIMIT <REAL>", default_r_val=1.0e-12_dp)
411 CALL section_add_keyword(subsection, keyword)
412 CALL keyword_release(keyword)
413 CALL section_add_subsection(section, subsection)
414 CALL section_release(subsection)
415
416 ! Mapping of atoms
417 NULLIFY (sub2section, sub3section)
418 CALL section_create(subsection, __location__, name="MAPPING", &
419 description="Defines the mapping of atoms for the different force_eval with the mixed force_eval."// &
420 " The default is to have a mapping 1-1 between atom index (i.e. all force_eval share the same"// &
421 " geometrical structure). The mapping is based on defining fragments and the mapping the"// &
422 " fragments between the several force_eval and the mixed force_eval", &
423 n_keywords=1, n_subsections=0, repeats=.true.)
424
425 ! Mixed force_eval
426 CALL section_create(sub2section, __location__, name="FORCE_EVAL_MIXED", &
427 description="Defines the fragments for the mixed force_eval (reference)", &
428 n_keywords=1, n_subsections=0, repeats=.true.)
429
430 CALL section_create(sub3section, __location__, name="FRAGMENT", &
431 description="Fragment definition", &
432 n_keywords=1, n_subsections=0, repeats=.true.)
433
434 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
435 description="Defines the index of the fragment defined", &
436 usage="<INTEGER>", type_of_var=integer_t, n_var=1)
437 CALL section_add_keyword(sub3section, keyword)
438 CALL keyword_release(keyword)
439
440 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
441 description="Starting and ending atomic index defining one fragment must be provided", &
442 usage="{Integer} {Integer}", type_of_var=integer_t, n_var=2, repeats=.true.)
443 CALL section_add_keyword(sub3section, keyword)
444 CALL keyword_release(keyword)
445
446 CALL section_add_subsection(sub2section, sub3section)
447 CALL section_release(sub3section)
448 CALL section_add_subsection(subsection, sub2section)
449 CALL section_release(sub2section)
450
451 ! All other force_eval
452 CALL section_create(sub2section, __location__, name="FORCE_EVAL", &
453 description="Defines the fragments and the mapping for each force_eval (an integer index (ID) "// &
454 "needs to be provided as parameter)", &
455 n_keywords=1, n_subsections=0, repeats=.true.)
456
457 CALL keyword_create( &
458 keyword, __location__, name="DEFINE_FRAGMENTS", &
459 description="Specify the fragments definition of the force_eval through the fragments of the"// &
460 " force_eval_mixed. This avoids the pedantic definition of the fragments for the force_eval,"// &
461 " assuming the order of the fragments for the specified force_eval is the same as the sequence"// &
462 " of integers provided. Easier to USE should be preferred to the specification of the single fragments.", &
463 usage="DEFINE_FRAGMENTS <INTEGER> .. <INTEGER>", type_of_var=integer_t, n_var=-1)
464 CALL section_add_keyword(sub2section, keyword)
465 CALL keyword_release(keyword)
466
467 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
468 description="Defines the index of the force_eval for which fragments and mappings are provided", &
469 usage="<INTEGER>", type_of_var=integer_t, n_var=1)
470 CALL section_add_keyword(sub2section, keyword)
471 CALL keyword_release(keyword)
472
473 CALL section_create(sub3section, __location__, name="FRAGMENT", &
474 description="Fragment definition", &
475 n_keywords=1, n_subsections=0, repeats=.true.)
476
477 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
478 description="Defines the index of the fragment defined", &
479 usage="<INTEGER>", type_of_var=integer_t, n_var=1)
480 CALL section_add_keyword(sub3section, keyword)
481 CALL keyword_release(keyword)
482
483 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
484 description="Starting and ending atomic index defining one fragment must be provided", &
485 usage="{Integer} {Integer}", type_of_var=integer_t, n_var=2, repeats=.false.)
486 CALL section_add_keyword(sub3section, keyword)
487 CALL keyword_release(keyword)
488
489 CALL keyword_create(keyword, __location__, name="MAP", &
490 description="Provides the index of the fragment of the MIXED force_eval mapped on the"// &
491 " locally defined fragment.", &
492 usage="MAP <INTEGER>", type_of_var=integer_t, n_var=1, repeats=.false.)
493 CALL section_add_keyword(sub3section, keyword)
494 CALL keyword_release(keyword)
495
496 CALL section_add_subsection(sub2section, sub3section)
497 CALL section_release(sub3section)
498 CALL section_add_subsection(subsection, sub2section)
499 CALL section_release(sub2section)
500
501 CALL section_add_subsection(section, subsection)
502 CALL section_release(subsection)
503
504 CALL create_print_mix_section(subsection)
505 CALL section_add_subsection(section, subsection)
506 CALL section_release(subsection)
507 END SUBROUTINE create_mix_section
508
509! **************************************************************************************************
510!> \brief Create the print section for mixed
511!> \param section the section to create
512!> \author teo
513! **************************************************************************************************
514 SUBROUTINE create_print_mix_section(section)
515 TYPE(section_type), POINTER :: section
516
517 TYPE(section_type), POINTER :: print_key
518
519 cpassert(.NOT. ASSOCIATED(section))
520 CALL section_create(section, __location__, name="print", &
521 description="Section of possible print options in MIXED env.", &
522 n_keywords=0, n_subsections=1, repeats=.false.)
523
524 NULLIFY (print_key)
525
526 CALL cp_print_key_section_create(print_key, __location__, "PROGRAM_RUN_INFO", &
527 description="Controls the printing of information during the evaluation of "// &
528 "the mixed environment. ", &
529 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
530 CALL section_add_subsection(section, print_key)
531 CALL section_release(print_key)
532
533 CALL cp_print_key_section_create(print_key, __location__, "DIPOLE", &
534 description="Controls the printing of dipole information. "// &
535 "Requires the DIPOLE calculation be active for all subforce_eval.", &
536 print_level=medium_print_level, filename="__STD_OUT__")
537 CALL section_add_subsection(section, print_key)
538 CALL section_release(print_key)
539 END SUBROUTINE create_print_mix_section
540
541! **************************************************************************************************
542!> \brief Create the print section specific to mixed CDFT (forked from print_mix_section)
543!> \param section the section to create
544!> \author Nico Holmberg [06.2017]
545! **************************************************************************************************
546 SUBROUTINE create_print_mixed_cdft_section(section)
547 TYPE(section_type), POINTER :: section
548
549 TYPE(keyword_type), POINTER :: keyword
550 TYPE(section_type), POINTER :: print_key
551
552 cpassert(.NOT. ASSOCIATED(section))
553 CALL section_create(section, __location__, name="print", &
554 description="Section of possible print options for the mixed CDFT environment.", &
555 n_keywords=0, n_subsections=1, repeats=.false.)
556
557 NULLIFY (print_key, keyword)
558
559 CALL cp_print_key_section_create(print_key, __location__, "PROGRAM_RUN_INFO", &
560 description="Controls the printing of information during the evaluation of "// &
561 "the mixed CDFT environment. ", &
562 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
563
564 CALL keyword_create(keyword, __location__, name="MO_OVERLAP_MATRIX", &
565 description="Controls the printing of the MO overlap matrices between CDFT states. "// &
566 "The matrices are printed out in plain text.", &
567 usage="MO_OVERLAP_MATRIX TRUE", type_of_var=logical_t, &
568 default_l_val=.false., lone_keyword_l_val=.true.)
569 CALL section_add_keyword(print_key, keyword)
570 CALL keyword_release(keyword)
571
572 CALL keyword_create(keyword, __location__, name="MO_OVERLAP_EIGENVALUES", &
573 description="Controls the printing of the eigenvalues/singular values of the CDFT MO overlap "// &
574 "matrices. The product of the eigenvalues/singular values is the CDFT MO overlap. "// &
575 "Useful mainly for checking which singular values will get screened for a particular EPS_SVD.", &
576 usage="MO_OVERLAP_EIGENVALUES TRUE", type_of_var=logical_t, &
577 default_l_val=.false., lone_keyword_l_val=.true.)
578 CALL section_add_keyword(print_key, keyword)
579 CALL keyword_release(keyword)
580
581 CALL section_add_subsection(section, print_key)
582 CALL section_release(print_key)
583
584 END SUBROUTINE create_print_mixed_cdft_section
585! **************************************************************************************************
586!> \brief Creates the control section used to setup block diagonalization of the mixed
587!> CDFT Hamiltonian matrix
588!> \param section the section to create
589!> \author Nico Holmberg [11.2017]
590! **************************************************************************************************
591 SUBROUTINE create_mixed_cdft_block_section(section)
592 TYPE(section_type), POINTER :: section
593
594 TYPE(keyword_type), POINTER :: keyword
595
596 cpassert(.NOT. ASSOCIATED(section))
597 CALL section_create(section, __location__, name="BLOCK_DIAGONALIZE", &
598 description="Control section to setup block diagonalization of the mixed CDFT Hamiltonian. "// &
599 "Constructs a new Hamiltonian by diagonalizing the initial matrix within each block and "// &
600 "by rotating the off-diagonal blocks (which represent the interactions between different "// &
601 "blocks) by the eigenvectors of diagonal blocks.", &
602 n_keywords=2, n_subsections=0, repeats=.false.)
603
604 NULLIFY (keyword)
605 CALL keyword_create(keyword, __location__, name="BLOCK", &
606 description="Defines which CDFT states are included in a block. Each repetition of this keyword "// &
607 "defines a new block. The Hamiltonian matrix elements of the requested states are collected "// &
608 "into a new matrix and subsequently diagonalized. The eigenvectors of this matrix are used to "// &
609 "rotate the matrix blocks describing the interactions between blocks.", &
610 usage="BLOCK 1 2", repeats=.true., &
611 type_of_var=integer_t, n_var=-1)
612 CALL section_add_keyword(section, keyword)
613 CALL keyword_release(keyword)
614
615 CALL keyword_create(keyword, __location__, name="IGNORE_EXCITED", &
616 description="Ignore excited states related to each block when constructing the new mixed "// &
617 "CDFT Hamiltonian. This reduces the dimensionality of the Hamiltonian.", &
618 usage="IGNORE_EXCITED FALSE", type_of_var=logical_t, &
619 default_l_val=.true., lone_keyword_l_val=.true.)
620 CALL section_add_keyword(section, keyword)
621 CALL keyword_release(keyword)
622
623 CALL keyword_create(keyword, __location__, name="RECURSIVE_DIAGONALIZATION", &
624 description="Perform block diagonalization recursively until only two blocks remain. "// &
625 "For example, if the elements of a 8x8 matrix are first collected into 4 blocks "// &
626 "(using keyword BLOCK), this keyword will transform the matrix to a 2x2 matrix "// &
627 "(8x8 -> 4x4 -> 2x2). In this example, the blocks of the 2x2 matrix would be "// &
628 "assembled from the first and last 2 blocks of the 4x4 matrix.", &
629 usage="RECURSIVE_DIAGONALIZATION TRUE", type_of_var=logical_t, &
630 default_l_val=.false., lone_keyword_l_val=.true.)
631 CALL section_add_keyword(section, keyword)
632 CALL keyword_release(keyword)
633
634 END SUBROUTINE create_mixed_cdft_block_section
635
636END MODULE input_cp2k_mixed
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public holmberg2017
integer, save, public migliore2009
integer, save, public holmberg2018
integer, save, public mavros2015
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 medium_print_level
integer, parameter, public add_last_numeric
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 mix_cdft
integer, parameter, public mix_linear_combination
integer, parameter, public mix_coupled
integer, parameter, public mix_restrained
integer, parameter, public mix_generic
integer, parameter, public mix_minimum
builds the input structure for the MIXED environment
subroutine, public create_mix_section(section)
Create the input section for MIXED.
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 lchar_t
integer, parameter, public logical_t
integer, parameter, public char_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