(git:b279b6b)
input_cp2k_ls.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 input for the linear scaling (LS) section
10 !> \author Joost VandeVondele
11 ! **************************************************************************************************
13  USE bibliography, ONLY: lin2009,&
14  lin2013,&
16  shao2003,&
20  USE cp_units, ONLY: cp_unit_to_cp2k
21  USE input_constants, ONLY: &
31  keyword_type
36  section_type
37  USE input_val_types, ONLY: integer_t,&
38  real_t
39  USE kinds, ONLY: dp
40  USE pao_input, ONLY: create_pao_section
42  USE string_utilities, ONLY: s2a
43 #include "./base/base_uses.f90"
44 
45  IMPLICIT NONE
46  PRIVATE
47 
48  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_ls'
49 
50  PUBLIC :: create_ls_scf_section
51 
52 CONTAINS
53 ! **************************************************************************************************
54 !> \brief creates the linear scaling scf section
55 !> \param section ...
56 !> \author Joost VandeVondele [2010-10]
57 ! **************************************************************************************************
58  SUBROUTINE create_ls_scf_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(section, __location__, name="LS_SCF", &
66  description="Specifies the parameters of the linear scaling SCF routines", &
67  n_keywords=24, n_subsections=3, repeats=.false., &
68  citations=(/vandevondele2012/))
69 
70  NULLIFY (keyword, subsection)
71 
72  CALL keyword_create(keyword, __location__, name="LS_DIIS", &
73  description="Perform DIIS within linear scaling SCF", &
74  usage="LS_DIIS", lone_keyword_l_val=.true., &
75  default_l_val=.false.)
76  CALL section_add_keyword(section, keyword)
77  CALL keyword_release(keyword)
78 
79  CALL keyword_create(keyword, __location__, name="INI_DIIS", &
80  description="Iteration cycle to start DIIS Kohn-Sham matrix update", &
81  usage="INI_DIIS 2", default_i_val=2)
82  CALL section_add_keyword(section, keyword)
83  CALL keyword_release(keyword)
84 
85  CALL keyword_create(keyword, __location__, name="MAX_DIIS", &
86  description="Size of LS_DIIS buffer", &
87  usage="MAX_DIIS 4", default_i_val=4)
88  CALL section_add_keyword(section, keyword)
89  CALL keyword_release(keyword)
90 
91  CALL keyword_create(keyword, __location__, name="NMIXING", &
92  description="Minimal number of density mixing before start DIIS", &
93  usage="NMIXING 2", default_i_val=2)
94  CALL section_add_keyword(section, keyword)
95  CALL keyword_release(keyword)
96 
97  CALL keyword_create(keyword, __location__, name="EPS_DIIS", &
98  description="Threshold on the convergence to start using DIIS", &
99  usage="EPS_DIIS 1.e-1", default_r_val=1.e-1_dp)
100  CALL section_add_keyword(section, keyword)
101  CALL keyword_release(keyword)
102 
103  CALL keyword_create(keyword, __location__, name="MAX_SCF", &
104  description="Maximum number of SCF iteration to be performed for one optimization", &
105  usage="MAX_SCF 200", default_i_val=20)
106  CALL section_add_keyword(section, keyword)
107  CALL keyword_release(keyword)
108 
109  CALL keyword_create( &
110  keyword, __location__, name="EPS_SCF", &
111  description="Target accuracy for the SCF convergence in terms of change of the total energy per electron.", &
112  usage="EPS_SCF 1.e-6", default_r_val=1.e-7_dp)
113  CALL section_add_keyword(section, keyword)
114  CALL keyword_release(keyword)
115 
116  CALL keyword_create(keyword, __location__, name="MIXING_FRACTION", &
117  description="Mixing density matrices uses the specified fraction in the SCF procedure.", &
118  usage="MIXING_FRACTION 0.4", default_r_val=0.45_dp)
119  CALL section_add_keyword(section, keyword)
120  CALL keyword_release(keyword)
121 
122  CALL keyword_create(keyword, __location__, name="EPS_FILTER", &
123  description="Threshold used for filtering matrix operations.", &
124  usage="EPS_FILTER 1.0E-7", default_r_val=1.0e-6_dp)
125  CALL section_add_keyword(section, keyword)
126  CALL keyword_release(keyword)
127 
128  CALL keyword_create(keyword, __location__, name="EPS_LANCZOS", &
129  description="Threshold used for lanczos estimates.", &
130  usage="EPS_LANCZOS 1.0E-4", default_r_val=1.0e-3_dp)
131  CALL section_add_keyword(section, keyword)
132  CALL keyword_release(keyword)
133 
134  CALL keyword_create(keyword, __location__, name="MAX_ITER_LANCZOS", &
135  description="Maximum number of lanczos iterations.", &
136  usage="MAX_ITER_LANCZOS ", default_i_val=128)
137  CALL section_add_keyword(section, keyword)
138  CALL keyword_release(keyword)
139 
140  CALL keyword_create(keyword, __location__, name="MU", &
141  description="Value (or initial guess) for the chemical potential,"// &
142  " i.e. some suitable energy between HOMO and LUMO energy.", &
143  usage="MU 0.0", default_r_val=-0.1_dp)
144  CALL section_add_keyword(section, keyword)
145  CALL keyword_release(keyword)
146 
147  CALL keyword_create(keyword, __location__, name="FIXED_MU", &
148  description="Should the calculation be performed at fixed chemical potential,"// &
149  " or should it be found fixing the number of electrons", &
150  usage="FIXED_MU .TRUE.", default_l_val=.false., lone_keyword_l_val=.true.)
151  CALL section_add_keyword(section, keyword)
152  CALL keyword_release(keyword)
153 
154  CALL keyword_create(keyword, __location__, name="EXTRAPOLATION_ORDER", &
155  description="Number of previous matrices used for the ASPC extrapolation of the initial guess. "// &
156  "0 implies that an atomic guess is used at each step. "// &
157  "low (1-2) will result in a drift of the constant of motion during MD. "// &
158  "high (>5) might be somewhat unstable, leading to more SCF iterations.", &
159  usage="EXTRAPOLATION_ORDER 3", default_i_val=4)
160  CALL section_add_keyword(section, keyword)
161  CALL keyword_release(keyword)
162 
163  CALL keyword_create(keyword, __location__, name="S_PRECONDITIONER", &
164  description="Preconditions S with some appropriate form.", &
165  usage="S_PRECONDITIONER MOLECULAR", &
166  default_i_val=ls_s_preconditioner_atomic, &
167  enum_c_vals=s2a("NONE", "ATOMIC", "MOLECULAR"), &
168  enum_desc=s2a("No preconditioner", &
169  "Using atomic blocks", &
170  "Using molecular sub-blocks. Recommended if molecules are defined and not too large."), &
172  CALL section_add_keyword(section, keyword)
173  CALL keyword_release(keyword)
174 
175  CALL keyword_create(keyword, __location__, name="S_SQRT_METHOD", &
176  description="Method for the caclulation of the sqrt of S.", &
177  usage="S_SQRT_METHOD NEWTONSCHULZ", &
178  default_i_val=ls_s_sqrt_ns, &
179  enum_c_vals=s2a("NEWTONSCHULZ", "PROOT"), &
180  enum_desc=s2a("Using a Newton-Schulz-like iteration", &
181  "Using the p-th root method."), &
182  enum_i_vals=(/ls_s_sqrt_ns, ls_s_sqrt_proot/))
183  CALL section_add_keyword(section, keyword)
184  CALL keyword_release(keyword)
185 
186  CALL keyword_create(keyword, __location__, name="S_SQRT_ORDER", &
187  variants=s2a("SIGN_SQRT_ORDER"), &
188  description="Order of the iteration method for the calculation of the sqrt of S.", &
189  usage="S_SQRT_ORDER 3", default_i_val=3)
190  CALL section_add_keyword(section, keyword)
191  CALL keyword_release(keyword)
192 
193  CALL keyword_create(keyword, __location__, name="PURIFICATION_METHOD", &
194  description="Scheme used to purify the Kohn-Sham matrix into the density matrix.", &
195  usage="PURIFICATION_METHOD TRS4", &
196  default_i_val=ls_scf_sign, &
197  citations=(/vandevondele2012, niklasson2003/), &
198  enum_c_vals=s2a("SIGN", "TRS4", "TC2", "PEXSI"), &
199  enum_desc=s2a("Sign matrix iteration.", &
200  "Trace resetting 4th order scheme", &
201  "Trace conserving 2nd order scheme", &
202  "PEXSI method"), &
203  enum_i_vals=(/ls_scf_sign, ls_scf_trs4, ls_scf_tc2, ls_scf_pexsi/))
204  CALL section_add_keyword(section, keyword)
205  CALL keyword_release(keyword)
206 
207  CALL keyword_create(keyword, __location__, name="SIGN_METHOD", &
208  description="Method used for the computation of the sign matrix.", &
209  usage="SIGN_METHOD NEWTONSCHULZ", &
210  default_i_val=ls_scf_sign_ns, &
211  citations=(/vandevondele2012, niklasson2003/), &
212  enum_c_vals=s2a("NEWTONSCHULZ", "PROOT", "SUBMATRIX"), &
213  enum_desc=s2a("Newton-Schulz iteration.", &
214  "p-th order root iteration", &
215  "Submatrix method"), &
217  CALL section_add_keyword(section, keyword)
218  CALL keyword_release(keyword)
219 
220  CALL keyword_create(keyword, __location__, name="SUBMATRIX_SIGN_METHOD", &
221  description="Method used for the computation of the sign matrix of all submatrices.", &
222  usage="SUBMATRIX_SIGN_METHOD NEWTONSCHULZ", &
223  default_i_val=ls_scf_submatrix_sign_ns, &
224  enum_c_vals=s2a("NEWTONSCHULZ", "DIRECT", "DIRECT_MUADJ", "DIRECT_MUADJ_LOWMEM"), &
225  enum_desc=s2a("Newton-Schulz iteration.", &
226  "Direct method calculating all eigenvalues.", &
227  "Direct method with internal adjustment of mu", &
228  "Direct method with internal adjustment of mu, using two passes to save memory"), &
231  CALL section_add_keyword(section, keyword)
232  CALL keyword_release(keyword)
233 
234  CALL keyword_create(keyword, __location__, name="SIGN_ORDER", &
235  description="Order of the method used for the computation of the sign matrix.", &
236  usage="SIGN_ORDER 2", &
237  default_i_val=2)
238  CALL section_add_keyword(section, keyword)
239  CALL keyword_release(keyword)
240 
241  CALL keyword_create(keyword, __location__, name="SIGN_SYMMETRIC", &
242  description="Use symmetric orthogonalization when generating the input for the sign function.", &
243  usage="SIGN_SYMMETRIC .TRUE.", default_l_val=.false., lone_keyword_l_val=.true.)
244  CALL section_add_keyword(section, keyword)
245  CALL keyword_release(keyword)
246 
247  CALL keyword_create(keyword, __location__, name="DYNAMIC_THRESHOLD", &
248  description="Should the threshold for the purification be chosen dynamically", &
249  usage="DYNAMIC_THRESHOLD .TRUE.", default_l_val=.false., lone_keyword_l_val=.true.)
250  CALL section_add_keyword(section, keyword)
251  CALL keyword_release(keyword)
252 
253  CALL keyword_create(keyword, __location__, name="NON_MONOTONIC", &
254  description="Should the purification be performed non-monotonically. Relevant for TC2 only.", &
255  usage="NON_MONOTONIC .TRUE.", default_l_val=.true., lone_keyword_l_val=.true.)
256  CALL section_add_keyword(section, keyword)
257  CALL keyword_release(keyword)
258 
259  CALL keyword_create( &
260  keyword, __location__, name="MATRIX_CLUSTER_TYPE", &
261  description="Specify how atomic blocks should be clustered in the used matrices, in order to improve flop rate, "// &
262  "and possibly speedup the matrix multiply. Note that the atomic s_preconditioner can not be used. "// &
263  "Furthermore, since screening is on matrix blocks, "// &
264  "slightly more accurate results can be expected with molecular.", &
265  usage="MATRIX_CLUSTER_TYPE MOLECULAR", &
266  default_i_val=ls_cluster_atomic, &
267  enum_c_vals=s2a("ATOMIC", "MOLECULAR"), &
268  enum_desc=s2a("Using atomic blocks", &
269  "Using molecular blocks."), &
270  enum_i_vals=(/ls_cluster_atomic, ls_cluster_molecular/))
271  CALL section_add_keyword(section, keyword)
272  CALL keyword_release(keyword)
273 
274  CALL keyword_create( &
275  keyword, __location__, name="RESTART_WRITE", &
276  description="Write the density matrix at the end of the SCF (currently requires EXTRAPOLATION_ORDER>0). "// &
277  "Files might be rather large.", &
278  usage="RESTART_READ", default_l_val=.false., lone_keyword_l_val=.true.)
279  CALL section_add_keyword(section, keyword)
280  CALL keyword_release(keyword)
281 
282  CALL keyword_create(keyword, __location__, name="RESTART_READ", &
283  description="Read the density matrix before the (first) SCF.", &
284  usage="RESTART_READ", default_l_val=.false., lone_keyword_l_val=.true.)
285  CALL section_add_keyword(section, keyword)
286  CALL keyword_release(keyword)
287 
288  CALL keyword_create(keyword, __location__, name="S_INVERSION", &
289  description="Method used to compute the inverse of S.", &
290  usage="S_PRECONDITIONER MOLECULAR", &
291  default_i_val=ls_s_inversion_sign_sqrt, &
292  enum_c_vals=s2a("SIGN_SQRT", "HOTELLING"), &
293  enum_desc=s2a("Using the inverse sqrt as obtained from sign function iterations.", &
294  "Using the Hotellign iteration."), &
296  CALL section_add_keyword(section, keyword)
297  CALL keyword_release(keyword)
298 
299  CALL keyword_create(keyword, __location__, name="REPORT_ALL_SPARSITIES", &
300  description="Run the sparsity report at the end of the SCF", &
301  usage="REPORT_ALL_SPARSITIES", default_l_val=.true., lone_keyword_l_val=.true.)
302  CALL section_add_keyword(section, keyword)
303  CALL keyword_release(keyword)
304 
305  CALL keyword_create(keyword, __location__, name="PERFORM_MU_SCAN", &
306  description="Do a scan of the chemical potential after the SCF", &
307  usage="PERFORM_MU_SCAN", default_l_val=.false., lone_keyword_l_val=.true.)
308  CALL section_add_keyword(section, keyword)
309  CALL keyword_release(keyword)
310 
311  CALL keyword_create(keyword, __location__, name="CHECK_S_INV", &
312  description="Perform an accuracy check on the inverse/sqrt of the s matrix.", &
313  usage="CHECK_S_INV", default_l_val=.false., lone_keyword_l_val=.true.)
314  CALL section_add_keyword(section, keyword)
315  CALL keyword_release(keyword)
316 
317  CALL create_ls_curvy_section(subsection)
318  CALL section_add_subsection(section, subsection)
319  CALL section_release(subsection)
320 
321  CALL create_chebyshev_section(subsection)
322  CALL section_add_subsection(section, subsection)
323  CALL section_release(subsection)
324 
325  CALL create_mixing_section(subsection, ls_scf=.true.)
326  CALL section_add_subsection(section, subsection)
327  CALL section_release(subsection)
328 
329  CALL create_pexsi_section(subsection)
330  CALL section_add_subsection(section, subsection)
331  CALL section_release(subsection)
332 
333  CALL create_pao_section(subsection)
334  CALL section_add_subsection(section, subsection)
335  CALL section_release(subsection)
336 
337  END SUBROUTINE create_ls_scf_section
338 
339 ! **************************************************************************************************
340 !> \brief creates the DOS section
341 !> \param section ...
342 !> \author Joost VandeVondele, Jinwoong Cha [2012-10]
343 ! **************************************************************************************************
344  SUBROUTINE create_chebyshev_section(section)
345  TYPE(section_type), POINTER :: section
346 
347  TYPE(keyword_type), POINTER :: keyword
348  TYPE(section_type), POINTER :: print_key
349 
350  cpassert(.NOT. ASSOCIATED(section))
351 
352  CALL section_create(section, __location__, name="CHEBYSHEV", &
353  description="Specifies the parameters needed for the chebyshev expansion based properties.", &
354  n_keywords=24, n_subsections=3, repeats=.false.)
355 
356  NULLIFY (keyword)
357  NULLIFY (print_key)
358 
359  CALL keyword_create(keyword, __location__, name="N_CHEBYSHEV", &
360  description="Order of the polynomial expansion.", &
361  usage="N_CHEBYSHEV 2000", default_i_val=500)
362  CALL section_add_keyword(section, keyword)
363  CALL keyword_release(keyword)
364 
365  ! A DOS print key
366  CALL cp_print_key_section_create(print_key, __location__, "DOS", &
367  description="Controls the printing of the Density of States (DOS).", &
368  print_level=high_print_level, filename="")
369  CALL keyword_create(keyword, __location__, name="N_GRIDPOINTS", &
370  description="Number of points in the computed DOS", &
371  usage="N_GRIDPOINTS 10000", default_i_val=2000)
372  CALL section_add_keyword(print_key, keyword)
373  CALL keyword_release(keyword)
374  CALL section_add_subsection(section, print_key)
375  CALL section_release(print_key)
376 
377  ! Energy specific electron density cubes
379  print_key, __location__, &
380  name="PRINT_SPECIFIC_E_DENSITY_CUBE", &
381  description="Controls the printing of cube files with "// &
382  "the electronic density (states) "// &
383  "contributing to the density of states within "// &
384  "the specific energy range "// &
385  "(MIN_ENERGY &le; E &le; MAX_ENERGY). MIN_ENERGY and MAX_ENERGY need to be specified explicitly.", &
386  print_level=high_print_level, filename="")
387 
388  CALL keyword_create(keyword, __location__, name="stride", &
389  description="The stride (X,Y,Z) used to write the cube file "// &
390  "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
391  " 1 number valid for all components.", &
392  usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
393  CALL section_add_keyword(print_key, keyword)
394  CALL keyword_release(keyword)
395 
396  CALL keyword_create(keyword, __location__, name="MIN_ENERGY", &
397  description="Lower bounds of the energy ranges of interest.", &
398  usage="MIN_ENERGY -1.01 -0.62 0.10 .. ", &
399  type_of_var=real_t, n_var=-1)
400  CALL section_add_keyword(print_key, keyword)
401  CALL keyword_release(keyword)
402 
403  CALL keyword_create(keyword, __location__, name="MAX_ENERGY", &
404  description="Upper bounds of the energy ranges of interest.", &
405  usage="MAX_ENERGY -0.81 -0.43 0.22 .. ", &
406  type_of_var=real_t, n_var=-1)
407  CALL section_add_keyword(print_key, keyword)
408  CALL keyword_release(keyword)
409 
410  CALL section_add_subsection(section, print_key)
411  CALL section_release(print_key)
412 
413  END SUBROUTINE create_chebyshev_section
414 
415 ! **************************************************************************************************
416 !> \brief creates the curvy_steps section in linear scaling scf
417 !> \param section ...
418 !> \author Florian Schiffmann [2012-10]
419 ! **************************************************************************************************
420  SUBROUTINE create_ls_curvy_section(section)
421  TYPE(section_type), POINTER :: section
422 
423  TYPE(keyword_type), POINTER :: keyword
424 
425  cpassert(.NOT. ASSOCIATED(section))
426  CALL section_create(section, __location__, name="CURVY_STEPS", &
427  description="Specifies the parameters of the linear scaling SCF routines", &
428  n_keywords=24, n_subsections=3, repeats=.false., &
429  citations=(/shao2003/))
430 
431  NULLIFY (keyword)
432 
433  CALL keyword_create(keyword, __location__, name="LINE_SEARCH", &
434  description="Line serch type used in the curvy_setp optimization.", &
435  usage="LINE Search 3POINT", default_i_val=ls_scf_line_search_3point, &
436  enum_c_vals=s2a("3POINT", "3POINT_2D"), &
437  enum_desc=s2a("Performs a three point line search", &
438  "Only for spin unrestricted calcualtions. Separate step sizes for alpha and beta spin"// &
439  " using a fit to a 2D parabolic function"), &
441  CALL section_add_keyword(section, keyword)
442  CALL keyword_release(keyword)
443 
444  CALL keyword_create(keyword, __location__, name="N_BCH_HISTORY", &
445  description="Number of stored matrices in the Baker-Campbell-Hausdorff series. "// &
446  "Reduces the BCH evaluation during line search but can be memory intense. ", &
447  usage="N_BCH_HISTORY 5", &
448  default_i_val=7)
449  CALL section_add_keyword(section, keyword)
450  CALL keyword_release(keyword)
451 
452  CALL keyword_create(keyword, __location__, name="MIN_HESSIAN_SHIFT", &
453  description="Minimal eigenvalue shift for the Hessian in the Newton iteration."// &
454  " Useful for small band gap systems (0.5-1.0 recommended). ", &
455  usage="MIN_HESSIAN_SHIFT 0.0", default_r_val=0.0_dp)
456  CALL section_add_keyword(section, keyword)
457  CALL keyword_release(keyword)
458 
459  CALL keyword_create(keyword, __location__, name="FILTER_FACTOR", &
460  description="Allows to set a separate EPS_FILTER in the newton iterations."// &
461  " The new EPS is EPS_FILTER*FILTER_FACTOR.", &
462  usage="FILTER_FACTOR 10.0", default_r_val=1.0_dp)
463  CALL section_add_keyword(section, keyword)
464  CALL keyword_release(keyword)
465 
466  CALL keyword_create(keyword, __location__, name="FILTER_FACTOR_SCALE", &
467  description="Allows for dynamic EPS_FILTER. Updates the filter factor every SCF-Newton "// &
468  "step by FILTER_FACTOR=FILTER_FACTOR*FILTER_FACTOR_SCALE", &
469  usage="FILTER_FACTOR_SCALE 0.5", default_r_val=1.0_dp)
470  CALL section_add_keyword(section, keyword)
471  CALL keyword_release(keyword)
472 
473  CALL keyword_create(keyword, __location__, name="MIN_FILTER", &
474  description="Lowest EPS_FILTER in dynamic filtering. Given as multiple of EPS_FILTER:"// &
475  " EPS_FILTER_MIN=EPS_FILTER*MIN_FILTER", &
476  usage="FILTER_FACTOR 1.0", default_r_val=1.0_dp)
477  CALL section_add_keyword(section, keyword)
478  CALL keyword_release(keyword)
479 
480  END SUBROUTINE create_ls_curvy_section
481 
482 ! **************************************************************************************************
483 !> \brief creates the PEXSI library subsection of the linear scaling section.
484 !> \param section ...
485 !> \par History
486 !> 11.2014 created [Patrick Seewald]
487 !> \author Patrick Seewald
488 ! **************************************************************************************************
489  SUBROUTINE create_pexsi_section(section)
490  TYPE(section_type), POINTER :: section
491 
492  TYPE(keyword_type), POINTER :: keyword
493 
494  cpassert(.NOT. ASSOCIATED(section))
495 
496  CALL section_create(section, __location__, name="PEXSI", &
497  description="Specifies the parameters of the PEXSI library. The density matrix is calculated "// &
498  "with PEXSI if PURIFICATION_METHOD (in LS_SCF section) is set to PEXSI. "// &
499  "The computational cost of PEXSI is at most quadratically scaling w.r.t. the system size "// &
500  "and PEXSI is applicable to insulating and metallic systems. The value of EPS_PGF_ORB "// &
501  "(in QS input section) defines the sparsity of the matrices sent to PEXSI and EPS_FILTER "// &
502  "is overwritten with 0.", &
503  n_keywords=17, repeats=.false., citations=(/lin2009, lin2013/))
504  NULLIFY (keyword)
505 
506  CALL keyword_create(keyword, __location__, name="TEMPERATURE", &
507  description="Electronic temperature", &
508  default_r_val=cp_unit_to_cp2k(value=300.0_dp, unit_str="K"), &
509  unit_str="K")
510  CALL section_add_keyword(section, keyword)
511  CALL keyword_release(keyword)
512 
513  CALL keyword_create(keyword, __location__, name="GAP", &
514  description="Spectral gap. Note: This can be set to be 0 in most cases.", &
515  default_r_val=0.0_dp, unit_str="hartree")
516  CALL section_add_keyword(section, keyword)
517  CALL keyword_release(keyword)
518 
519  CALL keyword_create(keyword, __location__, name="NUM_POLE", &
520  description="Number of terms in the pole expansion (should be even).", &
521  default_i_val=64)
522  CALL section_add_keyword(section, keyword)
523  CALL keyword_release(keyword)
524 
525  CALL keyword_create(keyword, __location__, name="IS_INERTIA_COUNT", &
526  description="Whether inertia counting is used each time the DFT driver "// &
527  "of PEXSI is invoked. If FALSE, inertia counting is still used in the "// &
528  "first SCF iteration.", &
529  default_l_val=.false., lone_keyword_l_val=.true.)
530  CALL section_add_keyword(section, keyword)
531  CALL keyword_release(keyword)
532 
533  CALL keyword_create(keyword, __location__, name="MAX_PEXSI_ITER", &
534  description="Maximum number of PEXSI iterations after each inertia counting procedure.", &
535  default_i_val=5)
536  CALL section_add_keyword(section, keyword)
537  CALL keyword_release(keyword)
538 
539  CALL keyword_create(keyword, __location__, name="MU_MIN_0", &
540  description="Initial guess of lower bound for mu.", &
541  default_r_val=-5.0_dp, unit_str="hartree")
542  CALL section_add_keyword(section, keyword)
543  CALL keyword_release(keyword)
544 
545  CALL keyword_create(keyword, __location__, name="MU_MAX_0", &
546  description="Initial guess of upper bound for mu.", &
547  default_r_val=5.0_dp, unit_str="hartree")
548  CALL section_add_keyword(section, keyword)
549  CALL keyword_release(keyword)
550 
551  CALL keyword_create(keyword, __location__, name="MU_INERTIA_TOLERANCE", &
552  description="Stopping criterion in terms of the chemical potential for the "// &
553  "inertia counting procedure.", &
554  default_r_val=0.01_dp, unit_str="hartree")
555  CALL section_add_keyword(section, keyword)
556  CALL keyword_release(keyword)
557 
558  CALL keyword_create(keyword, __location__, name="MU_INERTIA_EXPANSION", &
559  description="If the chemical potential is not in the initial interval, "// &
560  "the interval is expanded by MU_INERTIA_EXPANSION.", &
561  default_r_val=0.15_dp, unit_str="hartree")
562  CALL section_add_keyword(section, keyword)
563  CALL keyword_release(keyword)
564 
565  CALL keyword_create(keyword, __location__, name="MU_PEXSI_SAFE_GUARD", &
566  description="Safe guard criterion in terms of the chemical potential to "// &
567  "reinvoke the inertia counting procedure.", &
568  default_r_val=0.01_dp, unit_str="hartree")
569  CALL section_add_keyword(section, keyword)
570  CALL keyword_release(keyword)
571 
572  CALL keyword_create(keyword, __location__, name="NUM_ELECTRON_PEXSI_TOLERANCE", &
573  description="Stopping criterion of the PEXSI iteration in terms of "// &
574  "The number of electrons compared to the exact number of electrons. "// &
575  "This threshold is the target tolerance applied at convergence of SCF.", &
576  default_r_val=0.1_dp)
577  CALL section_add_keyword(section, keyword)
578  CALL keyword_release(keyword)
579 
580  CALL keyword_create(keyword, __location__, name="NUM_ELECTRON_INITIAL_TOLERANCE", &
581  description="The same as NUM_ELECTRON_PEXSI_TOLERANCE but applied in the first SCF steps. "// &
582  "If set to a value smaller than NUM_ELECTRON_PEXSI_TOLERANCE, it is overwritten with "// &
583  "NUM_ELECTRON_PEXSI_TOLERANCE (default). If set to a value larger than "// &
584  "NUM_ELECTRON_PEXSI_TOLERANCE, the PEXSI tolerance in number of electrons is set adaptively "// &
585  "according to the SCF convergence error of the previous SCF step. This reduces the number "// &
586  "of PEXSI iterations in the first SCF steps but leads to at least one more SCF step.", &
587  default_r_val=0.0_dp)
588  CALL section_add_keyword(section, keyword)
589  CALL keyword_release(keyword)
590 
591  CALL keyword_create(keyword, __location__, name="ORDERING", &
592  description="Ordering strategy for factorization and selected inversion.", &
593  enum_c_vals=s2a("PARALLEL", "SEQUENTIAL", "MULTIPLE_MINIMUM_DEGREE"), &
594  enum_desc=s2a("Parallel ordering using ParMETIS/PT-SCOTCH (PARMETIS option in SuperLU_DIST)", &
595  "Sequential ordering using METIS (METIS_AT_PLUS_A option in SuperLU_DIST)", &
596  "Multiple minimum degree ordering (MMD_AT_PLUS_A option in SuperLU_DIST)"), &
597  enum_i_vals=(/0, 1, 2/), default_i_val=0)
598  CALL section_add_keyword(section, keyword)
599  CALL keyword_release(keyword)
600 
601  CALL keyword_create(keyword, __location__, name="ROW_ORDERING", &
602  description="row permutation strategy for factorization and selected inversion.", &
603  enum_c_vals=s2a("NOROWPERM", "LARGEDIAG"), &
604  enum_desc=s2a("No row permutation (NOROWPERM option in SuperLU_DIST)", &
605  "Make diagonal entry larger than off diagonal (LargeDiag option in SuperLU_DIST)"), &
606  enum_i_vals=(/0, 1/), default_i_val=0)
607  CALL section_add_keyword(section, keyword)
608  CALL keyword_release(keyword)
609 
610  CALL keyword_create(keyword, __location__, name="NP_SYMB_FACT", &
611  description="Number of processors for PARMETIS/PT-SCOTCH. Only used if ORDERING is set to PARALLEL. "// &
612  "If 0, the number of processors for PARMETIS/PT-SCOTCH will be set equal to the number of "// &
613  "MPI ranks per pole. Note: if more than one processor is used, a segmentation fault may occur in the "// &
614  "symbolic factorization phase.", &
615  default_i_val=1)
616  CALL section_add_keyword(section, keyword)
617  CALL keyword_release(keyword)
618 
619  CALL keyword_create(keyword, __location__, name="VERBOSITY", &
620  description="The level of output information.", &
621  enum_c_vals=s2a("SILENT", "BASIC", "DETAILED"), &
622  enum_i_vals=(/0, 1, 2/), default_i_val=1)
623  CALL section_add_keyword(section, keyword)
624  CALL keyword_release(keyword)
625 
626  CALL keyword_create(keyword, __location__, name="MIN_RANKS_PER_POLE", &
627  description="The minimum number of processors used for each pole. The real "// &
628  "number of processors per pole is the smallest number greater or equal to "// &
629  "MIN_RANKS_PER_POLE that divides MPI size without remainder. For efficiency, MIN_RANKS_PER_POLE "// &
630  "should be a small numbers (limited by the available memory).", &
631  default_i_val=64)
632  CALL section_add_keyword(section, keyword)
633  CALL keyword_release(keyword)
634 
635  CALL keyword_create(keyword, __location__, name="CSR_SCREENING", &
636  description="Whether distance screening should be applied to improve sparsity of CSR matrices.", &
637  default_l_val=.true., lone_keyword_l_val=.true.)
638  CALL section_add_keyword(section, keyword)
639  CALL keyword_release(keyword)
640 
641  END SUBROUTINE create_pexsi_section
642 
643 END MODULE input_cp2k_ls
collects all references to literature in CP2K as new algorithms / method are included from literature...
Definition: bibliography.F:28
integer, save, public lin2009
Definition: bibliography.F:43
integer, save, public vandevondele2012
Definition: bibliography.F:43
integer, save, public lin2013
Definition: bibliography.F:43
integer, save, public shao2003
Definition: bibliography.F:43
integer, save, public niklasson2003
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 high_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 ls_scf_line_search_3point
integer, parameter, public ls_scf_submatrix_sign_direct_muadj
integer, parameter, public ls_s_preconditioner_molecular
integer, parameter, public ls_s_inversion_hotelling
integer, parameter, public ls_cluster_molecular
integer, parameter, public ls_scf_pexsi
integer, parameter, public ls_s_preconditioner_atomic
integer, parameter, public ls_scf_sign_submatrix
integer, parameter, public ls_scf_line_search_3point_2d
integer, parameter, public ls_s_sqrt_proot
integer, parameter, public ls_s_sqrt_ns
integer, parameter, public ls_s_preconditioner_none
integer, parameter, public ls_scf_sign_proot
integer, parameter, public ls_scf_trs4
integer, parameter, public ls_scf_sign
integer, parameter, public ls_scf_tc2
integer, parameter, public ls_scf_submatrix_sign_ns
integer, parameter, public ls_scf_sign_ns
integer, parameter, public ls_s_inversion_sign_sqrt
integer, parameter, public ls_scf_submatrix_sign_direct_muadj_lowmem
integer, parameter, public ls_scf_submatrix_sign_direct
integer, parameter, public ls_cluster_atomic
input for the linear scaling (LS) section
Definition: input_cp2k_ls.F:12
subroutine, public create_ls_scf_section(section)
creates the linear scaling scf section
Definition: input_cp2k_ls.F:59
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
subroutine, public create_pao_section(section)
Creates the PAO subsection of the linear scaling section.
Definition: pao_input.F:262
module that contains the definitions of the scf types
subroutine, public create_mixing_section(section, ls_scf)
Create CP2K input section for the mixing of the density matrix to be used only with diagonalization m...
Utilities for string manipulations.