(git:b279b6b)
input_cp2k_loc.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 !--------------------------------------------------------------------------------------------------!
8  USE bibliography, ONLY: hunt2003
14  USE input_constants, ONLY: &
23  keyword_type
28  section_type
29  USE input_val_types, ONLY: integer_t,&
30  lchar_t,&
31  real_t
32  USE kinds, ONLY: dp
33  USE string_utilities, ONLY: s2a
34 #include "./base/base_uses.f90"
35 
36  IMPLICIT NONE
37  PRIVATE
38 
39  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_loc'
40 
42 
43 CONTAINS
44 
45 ! **************************************************************************************************
46 !> \brief parameters fo the localization of wavefunctions
47 !> \param section ...
48 !> \par History
49 !> 03.2005 created [MI]
50 ! **************************************************************************************************
51 
52  SUBROUTINE create_localize_section(section)
53 
54  TYPE(section_type), POINTER :: section
55 
56  TYPE(keyword_type), POINTER :: keyword
57  TYPE(section_type), POINTER :: print_key, print_section, subsection
58 
59  cpassert(.NOT. ASSOCIATED(section))
60 
61  NULLIFY (keyword, print_key)
62  CALL section_create(section, __location__, name="LOCALIZE", &
63  description="Use one of the available methods to define the localization"// &
64  " and possibly to optimize it to a minimum or a maximum.", &
65  n_keywords=8, n_subsections=0, repeats=.false.)
66 
67  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
68  description="controls the activation of the MOS localization procedure", &
69  usage="&LOCALIZE T", default_l_val=.false., lone_keyword_l_val=.true.)
70  CALL section_add_keyword(section, keyword)
71  CALL keyword_release(keyword)
72 
73  CALL keyword_create(keyword, __location__, name="MAX_ITER", &
74  description="Maximum number of iterations used for localization methods", &
75  usage="MAX_ITER 2000", default_i_val=10000)
76  CALL section_add_keyword(section, keyword)
77  CALL keyword_release(keyword)
78 
79  CALL keyword_create( &
80  keyword, __location__, name="MAX_CRAZY_ANGLE", &
81  description="Largest allowed angle for the crazy rotations algorithm (smaller is slower but more stable).", &
82  usage="MAX_CRAZY_ANGLE 0.1", unit_str="rad", default_r_val=0.2_dp)
83  CALL section_add_keyword(section, keyword)
84  CALL keyword_release(keyword)
85 
86  CALL keyword_create(keyword, __location__, name="CRAZY_SCALE", &
87  description="scale angles", &
88  usage="CRAZY_SCALE 0.9", default_r_val=1.0_dp)
89  CALL section_add_keyword(section, keyword)
90  CALL keyword_release(keyword)
91 
92  CALL keyword_create(keyword, __location__, name="CRAZY_USE_DIAG", &
93  description="Use diagonalization (slow) or pade based calculation of matrix exponentials.", &
94  usage="CRAZY_USE_DIAG ", default_l_val=.false., lone_keyword_l_val=.true.)
95  CALL section_add_keyword(section, keyword)
96  CALL keyword_release(keyword)
97 
98  CALL keyword_create( &
99  keyword, __location__, name="USE_HISTORY", &
100  description="Generate an improved initial guess based on a history of results, which is useful during MD. "// &
101  "Will only work if the number of states to be localized remains constant.", &
102  usage="USE_HISTORY ", default_l_val=.false., lone_keyword_l_val=.true.)
103  CALL section_add_keyword(section, keyword)
104  CALL keyword_release(keyword)
105 
106  CALL keyword_create( &
107  keyword, __location__, name="EPS_OCCUPATION", &
108  description="Tolerance in the occupation number to select only fully occupied orbitals for the rotation", &
109  usage="EPS_OCCUPATION 1.E-5", default_r_val=1.0e-8_dp)
110  CALL section_add_keyword(section, keyword)
111  CALL keyword_release(keyword)
112 
113  CALL keyword_create(keyword, __location__, name="OUT_ITER_EACH", &
114  description="Every how many iterations of the localization algorithm "// &
115  "(Jacobi) the tolerance value is printed out", &
116  usage="OUT_ITER_EACH 100", default_i_val=100)
117  CALL section_add_keyword(section, keyword)
118  CALL keyword_release(keyword)
119 
120  CALL keyword_create(keyword, __location__, name="EPS_LOCALIZATION", &
121  description="Tolerance used in the convergence criterion of the localization methods.", &
122  usage="EPS_LOCALIZATION 1.0E-2", default_r_val=1.0e-4_dp)
123  CALL section_add_keyword(section, keyword)
124  CALL keyword_release(keyword)
125 
126  CALL keyword_create(keyword, __location__, name="MIN_OR_MAX", &
127  description="Requires the maximization of the spread of the wfn", &
128  usage="MIN_OR_MAX (SPREADMIN|SPREADMAX)", &
129  enum_c_vals=(/"SPREADMIN", "SPREADMAX"/), &
130  enum_i_vals=(/do_loc_min, do_loc_max/), &
131  default_i_val=do_loc_min)
132  CALL section_add_keyword(section, keyword)
133  CALL keyword_release(keyword)
134 
135  CALL keyword_create( &
136  keyword, __location__, name="METHOD", &
137  description="Method of optimization if any", &
138  usage="METHOD (JACOBI|CRAZY|DIRECT|GAPO|L1SD|SCDM|NONE)", &
139  enum_c_vals=s2a("NONE", "JACOBI", "CRAZY", "GAPO", "L1SD", "DIRECT", "SCDM"), &
140  enum_i_vals=(/do_loc_none, &
141  do_loc_jacobi, &
142  do_loc_crazy, &
143  do_loc_gapo, &
146  enum_desc=s2a("No localization is applied", &
147  "Using 2 x 2 rotations of the orbitals, slow but robust", &
148  "A new fast method is applied, might be slightly less robust than jacobi, but usually much faster", &
149  "Gradient ascent for partially occupied wannier functions", &
150  "Steepest descent minimization of an approximate l1 norm", &
151  "Using a direct minimisation approacha", "Use QR factorization"), &
152  default_i_val=do_loc_jacobi)
153  CALL section_add_keyword(section, keyword)
154  CALL keyword_release(keyword)
155 
156  CALL keyword_create(keyword, __location__, name="CPO_GUESS", &
157  description="Initial guess for coefficients if METHOD GAPO is used", &
158  usage="CPO_GUESS (ATOMIC|RESTART|RANDOM)", &
159  enum_c_vals=s2a("ATOMIC", "RESTART", "RANDOM"), &
161  default_i_val=do_loc_cpo_atomic)
162  CALL section_add_keyword(section, keyword)
163  CALL keyword_release(keyword)
164 
165  CALL keyword_create(keyword, __location__, name="CPO_GUESS_SPACE", &
166  description="Orbital space from which initial guess for coefficients is determined "// &
167  "if METHOD GAPO and CPO_GUESS ATOMIC are employed", &
168  usage="CPO_GUESS_SPACE (WAN|ALL)", &
169  enum_c_vals=s2a("WAN", "ALL"), &
170  enum_i_vals=(/do_loc_cpo_space_wan, do_loc_cpo_space_nmo/), &
171  default_i_val=do_loc_cpo_space_wan)
172  CALL section_add_keyword(section, keyword)
173  CALL keyword_release(keyword)
174 
175  CALL keyword_create(keyword, __location__, name="CG_PO", &
176  description="Use conjugate gradient in conjunction with METHOD GAPO. If FALSE, "// &
177  "steepest descent is used instead.", &
178  usage="CG_PO", default_l_val=.true., &
179  lone_keyword_l_val=.true.)
180  CALL section_add_keyword(section, keyword)
181  CALL keyword_release(keyword)
182 
183  CALL keyword_create(keyword, __location__, name="JACOBI_FALLBACK", &
184  description="Use Jacobi method in case no convergence was achieved"// &
185  " by using the crazy rotations method.", &
186  usage="JACOBI_FALLBACK", default_l_val=.true., &
187  lone_keyword_l_val=.true.)
188  CALL section_add_keyword(section, keyword)
189  CALL keyword_release(keyword)
190 
191  CALL keyword_create(keyword, __location__, name="JACOBI_REFINEMENT", &
192  description="Use Jacobi method to refine the localisation obtained by SCDM", &
193  usage="JACOBI_REFINEMENT", default_l_val=.false., &
194  lone_keyword_l_val=.true.)
195  CALL section_add_keyword(section, keyword)
196  CALL keyword_release(keyword)
197 
198  CALL keyword_create(keyword, __location__, name="RESTART", &
199  description="Restart the localization from a set of orbitals"// &
200  " read from a localization restart file.", &
201  usage="RESTART", default_l_val=.false., &
202  lone_keyword_l_val=.true.)
203  CALL section_add_keyword(section, keyword)
204  CALL keyword_release(keyword)
205 
206  CALL keyword_create(keyword, __location__, name="LOCHOMO_RESTART_FILE_NAME", &
207  description="File name where to read the MOS from "// &
208  "which to restart the localization procedure for occupied states", &
209  usage="LOCHOMO_RESTART_FILE_NAME <FILENAME>", &
210  type_of_var=lchar_t)
211  CALL section_add_keyword(section, keyword)
212  CALL keyword_release(keyword)
213 
214  CALL keyword_create(keyword, __location__, name="LOCMIXD_RESTART_FILE_NAME", &
215  description="File name where to read the MOS from "// &
216  "which to restart the localization procedure for MIXED states", &
217  usage="LOCMIXD_RESTART_FILE_NAME <FILENAME>", &
218  type_of_var=lchar_t)
219  CALL section_add_keyword(section, keyword)
220  CALL keyword_release(keyword)
221 
222  CALL keyword_create(keyword, __location__, name="LOCLUMO_RESTART_FILE_NAME", &
223  description="File name where to read the MOS from "// &
224  "which to restart the localization procedure for unoccupied states", &
225  usage="LOCLUMO_RESTART_FILE_NAME <FILENAME>", &
226  type_of_var=lchar_t)
227  CALL section_add_keyword(section, keyword)
228  CALL keyword_release(keyword)
229 
230  CALL keyword_create(keyword, __location__, name="OPERATOR", &
231  description="Type of opertator which defines the spread functional", &
232  usage=OPERATOR" (BERRY|BOYS|PIPEK)", &
233  enum_c_vals=s2a("BERRY", "BOYS", "PIPEK"), &
234  enum_i_vals=(/op_loc_berry, op_loc_boys, op_loc_pipek/), &
235  default_i_val=op_loc_berry)
236  CALL section_add_keyword(section, keyword)
237  CALL keyword_release(keyword)
238 
239  CALL keyword_create(keyword, __location__, name="LIST", &
240  description="Indexes of the occupied wfn to be localized "// &
241  "This keyword can be repeated several times "// &
242  "(useful if you have to specify many indexes).", &
243  usage="LIST 1 2", &
244  n_var=-1, type_of_var=integer_t, repeats=.true.)
245  CALL section_add_keyword(section, keyword)
246  CALL keyword_release(keyword)
247 
248  CALL keyword_create(keyword, __location__, name="LIST_UNOCCUPIED", &
249  description="Indexes of the unoccupied states to be localized, "// &
250  "up to now only valid in combination with GPW. "// &
251  "This keyword has to be present if unoccupied states should be localized. "// &
252  "This keyword can be repeated several times "// &
253  "(useful if you have to specify many indexes).", &
254  usage="LIST 1 2", &
255  n_var=-1, type_of_var=integer_t, repeats=.true.)
256  CALL section_add_keyword(section, keyword)
257  CALL keyword_release(keyword)
258 
259  CALL keyword_create(keyword, __location__, name="NEXTRA", &
260  description="Number of orbitals above fully occupied MOs to be localized, "// &
261  "up to now only valid in combination with GPW. "// &
262  "This keyword has to be present for STATES MIXED option. "// &
263  "Otherwise, only the fully occupied MOs are localized.", &
264  usage="NEXTRA 5", default_i_val=0)
265  CALL section_add_keyword(section, keyword)
266  CALL keyword_release(keyword)
267 
268  CALL keyword_create(keyword, __location__, name="STATES", &
269  description="Which states to localize, LUMO up to now only available in GPW", &
270  usage="STATES (HOMO|LUMO|MIXED|ALL)", &
271  enum_c_vals=s2a("OCCUPIED", "UNOCCUPIED", "MIXED", "ALL"), &
272  enum_i_vals=(/do_loc_homo, do_loc_lumo, do_loc_mixed, do_loc_both/), &
273  default_i_val=do_loc_homo)
274  CALL section_add_keyword(section, keyword)
275  CALL keyword_release(keyword)
276 
277  CALL keyword_create( &
278  keyword, __location__, &
279  name="ENERGY_RANGE", &
280  description="Select the orbitals to be localized within the given energy range."// &
281  " This type of selection cannot be added on top of the selection through a LIST. It reads to reals that are"// &
282  " lower and higher boundaries of the energy range.", &
283  usage=" ENERGY_RANGE lower_bound {real}, higher_bound {real}", &
284  repeats=.false., &
285  n_var=2, default_r_vals=(/0._dp, 0._dp/), unit_str='eV', &
286  type_of_var=real_t)
287  CALL section_add_keyword(section, keyword)
288  CALL keyword_release(keyword)
289 
290  NULLIFY (print_section)
291  CALL section_create(print_section, __location__, name="PRINT", &
292  description="Collects all printing options related to the Wannier centers and "// &
293  "properties computed with Wannier centers.", &
294  n_keywords=0, n_subsections=1, repeats=.false.)
295  NULLIFY (print_key)
296  CALL cp_print_key_section_create(print_key, __location__, "program_run_info", &
297  description="Controls the printing basic info about the method", &
298  print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
299  CALL section_add_subsection(print_section, print_key)
300  CALL section_release(print_key)
301  ! Add printing of wannier infos
302  CALL print_wanniers(print_section)
303  NULLIFY (subsection)
304  ! Total Dipoles with wannier
305  CALL create_dipoles_section(subsection, "TOTAL_DIPOLE", debug_print_level + 1)
306  CALL section_add_subsection(print_section, subsection)
307  CALL section_release(subsection)
308  ! Molecular Dipoles with wannier
309  CALL create_dipoles_section(subsection, "MOLECULAR_DIPOLES", debug_print_level + 1)
310  CALL section_add_subsection(print_section, subsection)
311  CALL section_release(subsection)
312  ! Molecular Mulipole Moments with wannier
313  CALL cp_print_key_section_create(subsection, __location__, name="MOLECULAR_MOMENTS", &
314  description="Section controlling the calculation of molecular multipole moments.", &
315  print_level=debug_print_level + 1, filename="__STD_OUT__")
316  CALL keyword_create(keyword, __location__, name="ORDER", &
317  description="Maximum order of mulitpoles to be calculated.", &
318  usage=" ORDER {integer}", default_i_val=2, type_of_var=integer_t)
319  CALL section_add_keyword(subsection, keyword)
320  CALL keyword_release(keyword)
321  !
322  CALL section_add_subsection(print_section, subsection)
323  CALL section_release(subsection)
324  ! Molecular States with wannier
325  CALL create_molecular_states_section(subsection)
326  CALL section_add_subsection(print_section, subsection)
327  CALL section_release(subsection)
328  ! Wannier States with wannier
329  CALL create_wannier_states_section(subsection)
330  CALL section_add_subsection(print_section, subsection)
331  CALL section_release(subsection)
332  CALL section_add_subsection(section, print_section)
333  CALL section_release(print_section)
334 
335  END SUBROUTINE create_localize_section
336 
337 ! **************************************************************************************************
338 !> \brief Controls the printing of the basic info coming from the LOCALIZE
339 !> section
340 !> \param section ...
341 !> \author teo
342 ! **************************************************************************************************
343  SUBROUTINE print_wanniers(section)
344  TYPE(section_type), POINTER :: section
345 
346  TYPE(keyword_type), POINTER :: keyword
347  TYPE(section_type), POINTER :: print_key
348 
349  cpassert(ASSOCIATED(section))
350  NULLIFY (print_key, keyword)
351  CALL cp_print_key_section_create(print_key, __location__, "WANNIER_CUBES", &
352  description="Controls the printing of the wannier functions ", &
353  print_level=high_print_level, add_last=add_last_numeric, filename="")
354  CALL keyword_create(keyword, __location__, name="stride", &
355  description="The stride (X,Y,Z) used to write the cube file "// &
356  "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
357  " 1 number valid for all components.", &
358  usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
359  CALL section_add_keyword(print_key, keyword)
360  CALL keyword_release(keyword)
361 
362  CALL keyword_create(keyword, __location__, name="CUBES_LU_BOUNDS", &
363  variants=(/"CUBES_LU"/), &
364  description="The lower and upper index of the states to be printed as cube", &
365  usage="CUBES_LU_BOUNDS integer integer", &
366  n_var=2, default_i_vals=(/0, -2/), type_of_var=integer_t)
367  CALL section_add_keyword(print_key, keyword)
368  CALL keyword_release(keyword)
369 
370  CALL keyword_create(keyword, __location__, name="CUBES_LIST", &
371  description="Indexes of the states to be printed as cube files"// &
372  " This keyword can be repeated several times"// &
373  " (useful if you have to specify many indexes).", &
374  usage="CUBES_LIST 1 2", &
375  n_var=-1, type_of_var=integer_t, repeats=.true.)
376  CALL section_add_keyword(print_key, keyword)
377  CALL keyword_release(keyword)
378  CALL keyword_create(keyword, __location__, name="APPEND", &
379  description="append the cube files when they already exist", &
380  default_l_val=.false., lone_keyword_l_val=.true.)
381  CALL section_add_keyword(print_key, keyword)
382  CALL keyword_release(keyword)
383 
384  CALL section_add_subsection(section, print_key)
385  CALL section_release(print_key)
386 
387  NULLIFY (print_key)
388  CALL cp_print_key_section_create(print_key, __location__, "WANNIER_CENTERS", &
389  description="Controls the printing of the wannier functions", &
390  print_level=high_print_level, add_last=add_last_numeric, filename="", &
391  unit_str="angstrom")
392 
393  CALL keyword_create(keyword, __location__, name="IONS+CENTERS", &
394  description="prints out the wannier centers together with the particles", &
395  usage="IONS+CENTERS", default_l_val=.false., &
396  lone_keyword_l_val=.true.)
397  CALL section_add_keyword(print_key, keyword)
398  CALL keyword_release(keyword)
399 
400  CALL add_format_keyword(keyword, print_key, pos=.true., &
401  description="Specifies the format of the output file when IONS+CENTERS is enabled.")
402  CALL section_add_subsection(section, print_key)
403  CALL section_release(print_key)
404 
405  NULLIFY (print_key)
406  CALL cp_print_key_section_create(print_key, __location__, "WANNIER_SPREADS", &
407  description="Controls the printing of the wannier functions", &
408  print_level=high_print_level, add_last=add_last_numeric, filename="")
409 
410  CALL keyword_create(keyword, __location__, name="SECOND_MOMENTS", &
411  description="Prints out the upper triangular part of the position covariance matrix. "// &
412  "Default is to use a non-periodic position operator. ", &
413  usage="SECOND_MOMENTS", default_l_val=.false., &
414  lone_keyword_l_val=.true.)
415  CALL section_add_keyword(print_key, keyword)
416  CALL keyword_release(keyword)
417 
418  CALL keyword_create(keyword, __location__, name="PERIODIC", &
419  description="For the covariance matrix, use the periodic position operator."// &
420  " Requires setting LMAXN1 in QS section to 6 or higher.", &
421  usage="PERIODIC", default_l_val=.false., &
422  lone_keyword_l_val=.true.)
423  CALL section_add_keyword(print_key, keyword)
424  CALL keyword_release(keyword)
425 
426  CALL section_add_subsection(section, print_key)
427  CALL section_release(print_key)
428 
429  NULLIFY (print_key)
430  CALL cp_print_key_section_create(print_key, __location__, "LOC_RESTART", &
431  description="Controls the printing of restart file for localized MOS", &
432  print_level=high_print_level, add_last=add_last_numeric, filename="")
433  CALL section_add_subsection(section, print_key)
434  CALL section_release(print_key)
435 
436  END SUBROUTINE print_wanniers
437 
438 ! **************************************************************************************************
439 !> \brief creates the input section for the molecular states
440 !> \param print_key ...
441 !> \author teo
442 ! **************************************************************************************************
443  SUBROUTINE create_molecular_states_section(print_key)
444  TYPE(section_type), POINTER :: print_key
445 
446  TYPE(keyword_type), POINTER :: keyword
447  TYPE(section_type), POINTER :: print_key2
448 
449  cpassert(.NOT. ASSOCIATED(print_key))
450  NULLIFY (print_key2, keyword)
451  CALL cp_print_key_section_create(print_key, __location__, "MOLECULAR_STATES", &
452  description="Controls printing of molecular states ", &
453  print_level=high_print_level, filename=" ", citations=(/hunt2003/))
454 
455  CALL keyword_create( &
456  keyword, __location__, name="CUBE_EVAL_RANGE", &
457  description="only write cubes if the eigenvalues of the corresponding molecular states lie in the given interval. "// &
458  "Default is all states.", &
459  usage="CUBE_EVAL_RANGE -1.0 1.0", unit_str="hartree", n_var=2, type_of_var=real_t)
460  CALL section_add_keyword(print_key, keyword)
461  CALL keyword_release(keyword)
462 
463  CALL keyword_create(keyword, __location__, name="MARK_STATES", &
464  description="Can be used to mark given molecular states."// &
465  " Sets a mark to both, occupied and unoccupied states. "// &
466  "Occupied states are counted beginning with HOMO=1, "// &
467  "unoccupied states are counted beginning with LUMO=1, "// &
468  "This is only meaningful in combination with WFN_MIX. "// &
469  "First integer specifies the molecule, second integer specifies the state.", &
470  usage="MARK_STATES integer integer", &
471  n_var=2, default_i_vals=(/-1, -1/), type_of_var=integer_t, repeats=.true.)
472  CALL section_add_keyword(print_key, keyword)
473  CALL keyword_release(keyword)
474 
475  CALL cp_print_key_section_create(print_key2, __location__, "cubes", &
476  description="Controls the printing of cube files", &
477  print_level=high_print_level, filename="")
478  CALL keyword_create(keyword, __location__, name="stride", &
479  description="The stride (X,Y,Z) used to write the cube file "// &
480  "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
481  " 1 number valid for all components.", &
482  usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
483  CALL section_add_keyword(print_key2, keyword)
484  CALL keyword_release(keyword)
485  CALL section_add_subsection(print_key, print_key2)
486  CALL section_release(print_key2)
487  END SUBROUTINE create_molecular_states_section
488 
489 ! **************************************************************************************************
490 !> \brief ...
491 !> \param print_key ...
492 ! **************************************************************************************************
493  SUBROUTINE create_wannier_states_section(print_key)
494  TYPE(section_type), POINTER :: print_key
495 
496  TYPE(keyword_type), POINTER :: keyword
497  TYPE(section_type), POINTER :: print_key2
498 
499  cpassert(.NOT. ASSOCIATED(print_key))
500  NULLIFY (print_key2, keyword)
501  CALL cp_print_key_section_create(print_key, __location__, "WANNIER_STATES", &
502  description="Controls printing of molecular states ", &
503  print_level=high_print_level, filename=" ")
504 
505  CALL keyword_create( &
506  keyword, __location__, name="CUBE_EVAL_RANGE", &
507  description="only write cubes if the eigenvalues of the corresponding molecular states lie in the given interval. "// &
508  "Default is all states.", &
509  usage="CUBE_EVAL_RANGE -1.0 1.0", unit_str="hartree", n_var=2, type_of_var=real_t)
510  CALL section_add_keyword(print_key, keyword)
511  CALL keyword_release(keyword)
512 
513  CALL keyword_create(keyword, __location__, name="MARK_STATES", &
514  description="Can be used to mark given molecular states."// &
515  " Sets a mark to both, occupied and unoccupied states. "// &
516  "Occupied states are counted beginning with HOMO=1, "// &
517  "unoccupied states are counted beginning with LUMO=1, "// &
518  "This is only meaningful in combination with WFN_MIX. "// &
519  "First integer specifies the molecule, second integer specifies the state.", &
520  usage="MARK_STATES integer integer", &
521  n_var=2, default_i_vals=(/-1, -1/), type_of_var=integer_t, repeats=.true.)
522  CALL section_add_keyword(print_key, keyword)
523  CALL keyword_release(keyword)
524 
525  CALL cp_print_key_section_create(print_key2, __location__, "cubes", &
526  description="Controls the printing of cube files", &
527  print_level=high_print_level, filename="")
528  CALL keyword_create(keyword, __location__, name="stride", &
529  description="The stride (X,Y,Z) used to write the cube file "// &
530  "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
531  " 1 number valid for all components.", &
532  usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
533  CALL section_add_keyword(print_key2, keyword)
534  CALL keyword_release(keyword)
535  CALL section_add_subsection(print_key, print_key2)
536  CALL section_release(print_key2)
537  END SUBROUTINE create_wannier_states_section
538 
539 END MODULE
collects all references to literature in CP2K as new algorithms / method are included from literature...
Definition: bibliography.F:28
integer, save, public hunt2003
Definition: bibliography.F:43
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 high_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 op_loc_pipek
integer, parameter, public do_loc_jacobi
integer, parameter, public do_loc_l1_norm_sd
integer, parameter, public do_loc_mixed
integer, parameter, public do_loc_cpo_space_nmo
integer, parameter, public do_loc_none
integer, parameter, public do_loc_scdm
integer, parameter, public op_loc_berry
integer, parameter, public do_loc_crazy
integer, parameter, public do_loc_gapo
integer, parameter, public op_loc_boys
integer, parameter, public do_loc_cpo_random
integer, parameter, public do_loc_lumo
integer, parameter, public do_loc_min
integer, parameter, public do_loc_cpo_restart
integer, parameter, public do_loc_homo
integer, parameter, public do_loc_cpo_space_wan
integer, parameter, public do_loc_max
integer, parameter, public do_loc_direct
integer, parameter, public do_loc_cpo_atomic
integer, parameter, public do_loc_both
subroutine, public create_localize_section(section)
parameters fo the localization of wavefunctions
subroutine, public print_wanniers(section)
Controls the printing of the basic info coming from the LOCALIZE section.
creates the mm section of the input
Definition: input_cp2k_mm.F:16
subroutine, public create_dipoles_section(print_key, label, print_level)
creates the input section for the qs part
subroutine, public add_format_keyword(keyword, section, pos, description)
creates the FORMAT keyword
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 integer_t
Defines the basic variable types.
Definition: kinds.F:23
integer, parameter, public dp
Definition: kinds.F:34
Utilities for string manipulations.