(git:e7e05ae)
input_cp2k_xc.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 function that build the xc section of the input
10 !> \par History
11 !> 10.2009 moved out of input_cp2k_dft [jgh]
12 !> \author fawzi
13 ! **************************************************************************************************
15  USE bibliography, ONLY: &
22  USE input_constants, ONLY: &
34  keyword_type
39  section_type
40  USE input_val_types, ONLY: char_t,&
41  integer_t,&
42  real_t
43  USE kinds, ONLY: dp
44  USE string_utilities, ONLY: s2a
45  USE xc_input_constants, ONLY: &
54  USE xc_libxc, ONLY: libxc_add_sections
55 #include "./base/base_uses.f90"
56 
57  IMPLICIT NONE
58  PRIVATE
59 
60  LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
61  CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_xc'
62 
64 
65 CONTAINS
66 
67 ! **************************************************************************************************
68 !> \brief creates the structure of the section needed to select the xc functional
69 !> \param section the section that will be created
70 !> \author fawzi
71 ! **************************************************************************************************
72  SUBROUTINE create_xc_fun_section(section)
73  TYPE(section_type), POINTER :: section
74 
75  TYPE(keyword_type), POINTER :: keyword
76  TYPE(section_type), POINTER :: subsection
77 
78  cpassert(.NOT. ASSOCIATED(section))
79  CALL section_create(section, __location__, name="xc_functional", &
80  description="The eXchange-Correlation functional to use.", &
81  n_keywords=0, n_subsections=4, repeats=.false., &
85 
86  NULLIFY (subsection, keyword)
87  CALL keyword_create( &
88  keyword, __location__, name="_SECTION_PARAMETERS_", &
89  description="Shortcut for the most common functional combinations.", &
90  usage="&xc_functional BLYP", &
91  enum_c_vals=s2a("B3LYP", "PBE0", "BLYP", "BP", "PADE", "LDA", "PBE", &
92  "TPSS", "HCTH120", "OLYP", "BEEFVDW", "NO_SHORTCUT", "NONE"), &
95  enum_desc=s2a("B3LYP", &
96  "PBE0 (see note in section XC/XC_FUNCTIONAL/PBE)", &
97  "BLYP", "BP", "PADE", "Alias for PADE", &
98  "PBE (see note in section XC/XC_FUNCTIONAL/PBE)", &
99  "TPSS (not available with LSD, use LIBXC version instead)", "HCTH120", "OLYP", &
100  "BEEFVDW", "NO_SHORTCUT", "NONE"), &
101  default_i_val=xc_funct_no_shortcut, &
102  lone_keyword_i_val=xc_funct_no_shortcut)
103  CALL section_add_keyword(section, keyword)
104  CALL keyword_release(keyword)
105 
106  CALL section_create(subsection, __location__, name="BECKE88", &
107  description="Uses the Becke 88 exchange functional", &
108  n_keywords=0, n_subsections=0, repeats=.false., &
109  citations=(/becke1988/))
110  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
111  description="activates the functional", &
112  lone_keyword_l_val=.true., default_l_val=.false.)
113  CALL section_add_keyword(subsection, keyword)
114  CALL keyword_release(keyword)
115  CALL keyword_create( &
116  keyword, __location__, name="scale_x", &
117  description="scales the exchange part of the functional", &
118  default_r_val=1._dp)
119  CALL section_add_keyword(subsection, keyword)
120  CALL keyword_release(keyword)
121 
122  CALL section_add_subsection(section, subsection)
123  CALL section_release(subsection)
124 
125  CALL section_create(subsection, __location__, name="LYP_ADIABATIC", &
126  description="Uses the LYP correlation functional in an adiabatic fashion", &
127  n_keywords=0, n_subsections=0, repeats=.false., &
128  citations=(/lee1988/))
129  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
130  description="activates the functional", &
131  lone_keyword_l_val=.true., default_l_val=.false.)
132  CALL section_add_keyword(subsection, keyword)
133  CALL keyword_release(keyword)
134  CALL keyword_create(keyword, __location__, name="LAMBDA", &
135  description="Defines the parameter of the adiabatic curve.", &
136  default_r_val=1._dp)
137  CALL section_add_keyword(subsection, keyword)
138  CALL keyword_release(keyword)
139 
140  CALL section_add_subsection(section, subsection)
141  CALL section_release(subsection)
142 
143  CALL section_create(subsection, __location__, name="BECKE88_LR_ADIABATIC", &
144  description="Uses the Becke 88 longrange exchange functional in an adiabatic fashion", &
145  n_keywords=0, n_subsections=0, repeats=.false., &
146  citations=(/becke1988/))
147  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
148  description="activates the functional", &
149  lone_keyword_l_val=.true., default_l_val=.false.)
150  CALL section_add_keyword(subsection, keyword)
151  CALL keyword_release(keyword)
152  CALL keyword_create(keyword, __location__, name="scale_x", &
153  description="scales the exchange part of the functional", &
154  default_r_val=1._dp)
155  CALL section_add_keyword(subsection, keyword)
156  CALL keyword_release(keyword)
157  CALL keyword_create(keyword, __location__, name="OMEGA", &
158  description="Potential parameter in erf(omega*r)/r", &
159  default_r_val=1._dp)
160  CALL section_add_keyword(subsection, keyword)
161  CALL keyword_release(keyword)
162  CALL keyword_create(keyword, __location__, name="LAMBDA", &
163  description="Defines the parameter of the adiabatic curve", &
164  default_r_val=1._dp)
165  CALL section_add_keyword(subsection, keyword)
166  CALL keyword_release(keyword)
167 
168  CALL section_add_subsection(section, subsection)
169  CALL section_release(subsection)
170 
171  CALL section_create(subsection, __location__, name="BECKE88_LR", &
172  description="Uses the Becke 88 longrange exchange functional", &
173  n_keywords=0, n_subsections=0, repeats=.false., &
174  citations=(/becke1988/))
175  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
176  description="activates the functional", &
177  lone_keyword_l_val=.true., default_l_val=.false.)
178  CALL section_add_keyword(subsection, keyword)
179  CALL keyword_release(keyword)
180  CALL keyword_create(keyword, __location__, name="scale_x", &
181  description="scales the exchange part of the functional", &
182  default_r_val=1._dp)
183  CALL section_add_keyword(subsection, keyword)
184  CALL keyword_release(keyword)
185  CALL keyword_create(keyword, __location__, name="OMEGA", &
186  description="Potential parameter in erf(omega*r)/r", &
187  default_r_val=1._dp)
188  CALL section_add_keyword(subsection, keyword)
189  CALL keyword_release(keyword)
190 
191  CALL section_add_subsection(section, subsection)
192  CALL section_release(subsection)
193 
194  CALL section_create(subsection, __location__, name="LYP", &
195  description="Uses the LYP functional", &
196  n_keywords=0, n_subsections=0, repeats=.false., &
197  citations=(/lee1988/))
198  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
199  description="activates the functional", &
200  lone_keyword_l_val=.true., default_l_val=.false.)
201  CALL section_add_keyword(subsection, keyword)
202  CALL keyword_release(keyword)
203  CALL keyword_create(keyword, __location__, name="scale_c", &
204  description="scales the correlation part of the functional", &
205  default_r_val=1._dp)
206  CALL section_add_keyword(subsection, keyword)
207  CALL keyword_release(keyword)
208  CALL section_add_subsection(section, subsection)
209  CALL section_release(subsection)
210 
211  CALL section_create(subsection, __location__, name="PADE", &
212  description="Uses the PADE functional", &
213  n_keywords=0, n_subsections=0, repeats=.false., &
214  citations=(/goedecker1996/))
215  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
216  description="activates the functional", &
217  lone_keyword_l_val=.true., default_l_val=.false.)
218  CALL section_add_keyword(subsection, keyword)
219  CALL keyword_release(keyword)
220  CALL section_add_subsection(section, subsection)
221  CALL section_release(subsection)
222 
223  CALL section_create(subsection, __location__, name="HCTH", &
224  description="Uses the HCTH class of functionals", &
225  n_keywords=0, n_subsections=0, repeats=.false.)
226  CALL keyword_create(keyword, __location__, name="PARAMETER_SET", &
227  description="Which version of the parameters should be used", &
228  usage="PARAMETER_SET 407", &
229  enum_c_vals=(/"93 ", "120", "147", "407", "HLE"/), &
230  enum_i_vals=(/93, 120, 147, 407, 408/), &
231  default_i_val=120)
232  CALL section_add_keyword(subsection, keyword)
233  CALL keyword_release(keyword)
234  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
235  description="activates the functional", &
236  lone_keyword_l_val=.true., default_l_val=.false.)
237  CALL section_add_keyword(subsection, keyword)
238  CALL keyword_release(keyword)
239  CALL section_add_subsection(section, subsection)
240  CALL section_release(subsection)
241 
242  CALL section_create(subsection, __location__, name="OPTX", &
243  description="Uses the OPTX functional", &
244  n_keywords=0, n_subsections=0, repeats=.false.)
245  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
246  description="activates the functional", &
247  lone_keyword_l_val=.true., default_l_val=.false.)
248  CALL section_add_keyword(subsection, keyword)
249  CALL keyword_release(keyword)
250  CALL keyword_create(keyword, __location__, name="scale_x", &
251  description="scales the exchange part of the functional", &
252  default_r_val=1._dp)
253  CALL section_add_keyword(subsection, keyword)
254  CALL keyword_release(keyword)
255  CALL keyword_create(keyword, __location__, name="a1", &
256  description="OPTX a1 coefficient", &
257  default_r_val=1.05151_dp)
258  CALL section_add_keyword(subsection, keyword)
259  CALL keyword_release(keyword)
260  CALL keyword_create(keyword, __location__, name="a2", &
261  description="OPTX a2 coefficient", &
262  default_r_val=1.43169_dp)
263  CALL section_add_keyword(subsection, keyword)
264  CALL keyword_release(keyword)
265  CALL keyword_create(keyword, __location__, name="gamma", &
266  description="OPTX gamma coefficient", &
267  default_r_val=0.006_dp)
268  CALL section_add_keyword(subsection, keyword)
269  CALL keyword_release(keyword)
270  CALL section_add_subsection(section, subsection)
271  CALL section_release(subsection)
272 
273  CALL libxc_add_sections(section)
274 
275  CALL section_create(subsection, __location__, name="CS1", &
276  description="Uses the CS1 functional", &
277  n_keywords=0, n_subsections=0, repeats=.false.)
278  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
279  description="activates the functional", &
280  lone_keyword_l_val=.true., default_l_val=.false.)
281  CALL section_add_keyword(subsection, keyword)
282  CALL keyword_release(keyword)
283  CALL section_add_subsection(section, subsection)
284  CALL section_release(subsection)
285 
286  CALL section_create(subsection, __location__, name="XGGA", &
287  description="Uses one of the XGGA functionals (optimized versions of "// &
288  "some of these functionals might be available outside this section).", &
289  n_keywords=1, n_subsections=0, repeats=.false.)
290  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
291  description="activates the functional", &
292  lone_keyword_l_val=.true., default_l_val=.false.)
293  CALL section_add_keyword(subsection, keyword)
294  CALL keyword_release(keyword)
295  CALL keyword_create(keyword, __location__, name="FUNCTIONAL", &
296  description="Which one of the XGGA functionals should be used", &
297  usage="FUNCTIONAL PW86X", &
298  enum_c_vals=(/ &
299  "BECKE88X", &
300  "PW86X ", &
301  "PW91X ", &
302  "PBEX ", &
303  "REV_PBEX", &
304  "OPTX ", &
305  "EV93 "/), &
307  default_i_val=xgga_b88x)
308  CALL section_add_keyword(subsection, keyword)
309  CALL keyword_release(keyword)
310  CALL section_add_subsection(section, subsection)
311  CALL section_release(subsection)
312 
313  CALL section_create(subsection, __location__, name="KE_GGA", &
314  description="Uses one of the KE_GGA functionals (optimized versions of "// &
315  "some of these functionals might be available outside this section). "// &
316  "These functionals are needed for the computation of the kinetic "// &
317  "energy in the Kim-Gordon method.", &
318  n_keywords=1, n_subsections=0, repeats=.false.)
319  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
320  description="activates the functional", &
321  lone_keyword_l_val=.true., default_l_val=.false.)
322  CALL section_add_keyword(subsection, keyword)
323  CALL keyword_release(keyword)
324  CALL keyword_create(keyword, __location__, name="FUNCTIONAL", &
325  description="Which one of the KE_GGA functionals should be used", &
326  usage="FUNCTIONAL (OL1|OL2|LLP|PW86|PW91|LC|T92|PBE)", &
327  enum_c_vals=(/"OL1 ", "OL2 ", "LLP ", "PW86", "PW91", "LC ", "T92 ", "PBE "/), &
328  enum_i_vals=(/ke_ol1, ke_ol2, ke_llp, ke_pw86, ke_pw91, ke_lc, ke_t92, ke_pbe/), &
329  enum_desc=s2a("Uses first Ou-Yang and Levy functional, currently not producing correct results", &
330  "Uses second Ou-Yang and Levy functional, currently not producing correct results", &
331  "Uses Lee, Lee, and Parr functional", &
332  "Uses Perdew and Wang's 1986 functional", &
333  "Uses Perdew and Wang's 1991 functional", &
334  "Uses Lembarki and Chermette functional", &
335  "Uses Thakkar functional", &
336  "Uses the 1996 functional of Perdew, Burke and Ernzerhof"), &
337  default_i_val=ke_llp)
338  CALL section_add_keyword(subsection, keyword)
339  CALL keyword_release(keyword)
340  CALL section_add_subsection(section, subsection)
341  CALL section_release(subsection)
342 
343  CALL section_create(subsection, __location__, name="P86C", &
344  description="Uses the P86C functional", &
345  n_keywords=0, n_subsections=0, repeats=.false.)
346  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
347  description="activates the functional", &
348  lone_keyword_l_val=.true., default_l_val=.false.)
349  CALL section_add_keyword(subsection, keyword)
350  CALL keyword_release(keyword)
351  CALL keyword_create(keyword, __location__, name="scale_c", &
352  description="scales the correlation part of the functional", &
353  default_r_val=1._dp)
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  CALL section_create(subsection, __location__, name="PW92", &
360  description="Uses the PerdewWang correlation functional.", &
361  n_keywords=1, n_subsections=0, repeats=.false.)
362  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
363  description="activates the functional", &
364  lone_keyword_l_val=.true., default_l_val=.false.)
365  CALL section_add_keyword(subsection, keyword)
366  CALL keyword_release(keyword)
367  CALL keyword_create(keyword, __location__, name="SCALE", &
368  description="Scaling of the energy functional", &
369  default_r_val=1.0_dp)
370  CALL section_add_keyword(subsection, keyword)
371  CALL keyword_release(keyword)
372  CALL keyword_create(keyword, __location__, name="PARAMETRIZATION", &
373  description="Which one of parametrizations should be used", &
374  usage="PARAMETRIZATION DMC", &
375  enum_c_vals=(/ &
376  "ORIGINAL", &
377  "DMC ", &
378  "VMC "/), &
379  enum_i_vals=(/c_pw92, c_pw92dmc, c_pw92vmc/), &
380  default_i_val=c_pw92)
381  CALL section_add_keyword(subsection, keyword)
382  CALL keyword_release(keyword)
383  CALL section_add_subsection(section, subsection)
384  CALL section_release(subsection)
385 
386  CALL section_create(subsection, __location__, name="PZ81", &
387  description="Uses the PZ functional.", &
388  n_keywords=1, n_subsections=0, repeats=.false., &
389  citations=(/perdew1981, ortiz1994/))
390  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
391  description="activates the functional", &
392  lone_keyword_l_val=.true., default_l_val=.false.)
393  CALL section_add_keyword(subsection, keyword)
394  CALL keyword_release(keyword)
395  CALL keyword_create(keyword, __location__, name="PARAMETRIZATION", &
396  description="Which one of parametrizations should be used", &
397  usage="PARAMETRIZATION DMC", &
398  enum_c_vals=(/ &
399  "ORIGINAL", &
400  "DMC ", &
401  "VMC "/), &
402  enum_i_vals=(/c_pz, c_pzdmc, c_pzvmc/), &
403  default_i_val=pz_orig)
404  CALL section_add_keyword(subsection, keyword)
405  CALL keyword_release(keyword)
406  CALL keyword_create(keyword, __location__, name="scale_c", &
407  description="scales the correlation part of the functional", &
408  default_r_val=1._dp)
409  CALL section_add_keyword(subsection, keyword)
410  CALL keyword_release(keyword)
411  CALL section_add_subsection(section, subsection)
412  CALL section_release(subsection)
413 
414  CALL section_create(subsection, __location__, name="TFW", &
415  description="Uses the TFW functional", &
416  n_keywords=0, n_subsections=0, repeats=.false.)
417  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
418  description="activates the functional", &
419  lone_keyword_l_val=.true., default_l_val=.false.)
420  CALL section_add_keyword(subsection, keyword)
421  CALL keyword_release(keyword)
422  CALL section_add_subsection(section, subsection)
423  CALL section_release(subsection)
424 
425  CALL section_create(subsection, __location__, name="TF", &
426  description="Uses the TF functional", &
427  n_keywords=0, n_subsections=0, repeats=.false.)
428  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
429  description="activates the functional", &
430  lone_keyword_l_val=.true., default_l_val=.false.)
431  CALL section_add_keyword(subsection, keyword)
432  CALL keyword_release(keyword)
433  CALL section_add_subsection(section, subsection)
434  CALL section_release(subsection)
435 
436  CALL section_create(subsection, __location__, name="VWN", &
437  description="Uses the VWN functional", &
438  n_keywords=0, n_subsections=0, repeats=.false., &
439  citations=(/vosko1980/))
440  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
441  description="activates the functional", &
442  lone_keyword_l_val=.true., default_l_val=.false.)
443  CALL section_add_keyword(subsection, keyword)
444  CALL keyword_release(keyword)
445  CALL keyword_create(keyword, __location__, name="scale_c", &
446  description="scales the correlation part of the functional", &
447  default_r_val=1._dp)
448  CALL section_add_keyword(subsection, keyword)
449  CALL keyword_release(keyword)
450 
451  CALL keyword_create(keyword, __location__, name="FUNCTIONAL_TYPE", &
452  description="Which version of the VWN functional should be used", &
453  usage="FUNCTIONAL_TYPE VWN5", &
454  enum_c_vals=s2a("VWN5", "VWN3"), &
455  enum_i_vals=(/do_vwn5, do_vwn3/), &
456  enum_desc=s2a("This is the recommended (correct) version of the VWN functional", &
457  "This version is the default in Gaussian, but not recommended. "// &
458  "Notice that it is also employed in Gaussian's default version of B3LYP"), &
459  default_i_val=do_vwn5)
460 
461  CALL section_add_keyword(subsection, keyword)
462  CALL keyword_release(keyword)
463  CALL section_add_subsection(section, subsection)
464  CALL section_release(subsection)
465 
466  CALL section_create(subsection, __location__, name="XALPHA", &
467  description="Uses the XALPHA (SLATER) functional.", &
468  n_keywords=1, n_subsections=0, repeats=.false.)
469  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
470  description="activates the functional", &
471  lone_keyword_l_val=.true., default_l_val=.false.)
472  CALL section_add_keyword(subsection, keyword)
473  CALL keyword_release(keyword)
474  CALL keyword_create(keyword, __location__, name="XA", &
475  description="Value of the xa parameter (this does not change the exponent, "// &
476  "just the mixing)", &
477  usage="XA 0.7", default_r_val=2._dp/3._dp)
478  CALL section_add_keyword(subsection, keyword)
479  CALL keyword_release(keyword)
480  CALL keyword_create(keyword, __location__, name="scale_x", &
481  description="scales the exchange part of the functional", &
482  default_r_val=1._dp)
483  CALL section_add_keyword(subsection, keyword)
484  CALL keyword_release(keyword)
485  CALL section_add_subsection(section, subsection)
486  CALL section_release(subsection)
487 
488  CALL section_create(subsection, __location__, name="TPSS", &
489  description="Uses the TPSS functional. Note, that there is no LSD version available. "// &
490  "In such cases, use the LIBXC version instead.", &
491  n_keywords=0, n_subsections=0, repeats=.false., &
492  citations=(/tao2003/))
493  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
494  description="Activates the functional", &
495  lone_keyword_l_val=.true., default_l_val=.false.)
496  CALL section_add_keyword(subsection, keyword)
497  CALL keyword_release(keyword)
498  CALL keyword_create(keyword, __location__, name="scale_x", &
499  description="scales the exchange part of the functional", &
500  default_r_val=1._dp)
501  CALL section_add_keyword(subsection, keyword)
502  CALL keyword_release(keyword)
503  CALL keyword_create(keyword, __location__, name="scale_c", &
504  description="scales the correlation part of the functional", &
505  default_r_val=1._dp)
506  CALL section_add_keyword(subsection, keyword)
507  CALL keyword_release(keyword)
508  CALL section_add_subsection(section, subsection)
509  CALL section_release(subsection)
510 
511  CALL section_create(subsection, __location__, name="PBE", &
512  description="Uses the PBE functional", &
513  n_keywords=0, n_subsections=0, repeats=.false., &
514  citations=(/perdew1996, zhang1998, perdew2008/))
515  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
516  description="activates the functional", &
517  lone_keyword_l_val=.true., default_l_val=.false.)
518  CALL section_add_keyword(subsection, keyword)
519  CALL keyword_release(keyword)
520  CALL keyword_create(keyword, __location__, name="parametrization", &
521  description="switches between the different "// &
522  "parametrizations of the functional. "// &
523  "Note: Beta parameters used have only 5 significant digits, "// &
524  "as published. For higher precision and program comparison "// &
525  "use section XC/XC_FUNCTIONAL/LIBXC.", &
526  enum_i_vals=(/xc_pbe_orig, xc_pbe_rev, xc_pbe_sol/), &
527  enum_c_vals=(/"ORIG ", "revPBE", "PBEsol"/), &
528  enum_desc=(/"original PBE ", &
529  "revised PBE (revPBE) ", &
530  "PBE for solids and surfaces (PBEsol)"/), &
531  default_i_val=xc_pbe_orig)
532  CALL section_add_keyword(subsection, keyword)
533  CALL keyword_release(keyword)
534  CALL keyword_create(keyword, __location__, name="scale_x", &
535  description="scales the exchange part of the functional", &
536  default_r_val=1._dp)
537  CALL section_add_keyword(subsection, keyword)
538  CALL keyword_release(keyword)
539  CALL keyword_create(keyword, __location__, name="scale_c", &
540  description="scales the correlation part of the functional", &
541  default_r_val=1._dp)
542  CALL section_add_keyword(subsection, keyword)
543  CALL keyword_release(keyword)
544  CALL section_add_subsection(section, subsection)
545  CALL section_release(subsection)
546 
547  CALL section_create(subsection, __location__, name="XWPBE", &
548  description="Uses the short range PBE functional", &
549  n_keywords=0, n_subsections=0, repeats=.false., &
550  citations=(/heyd2004/))
551  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
552  description="activates the functional", &
553  lone_keyword_l_val=.true., default_l_val=.false.)
554  CALL section_add_keyword(subsection, keyword)
555  CALL keyword_release(keyword)
556  CALL keyword_create(keyword, __location__, name="scale_x", &
557  description="scales the exchange part of the functional", &
558  default_r_val=1._dp)
559  CALL section_add_keyword(subsection, keyword)
560  CALL keyword_release(keyword)
561  CALL keyword_create(keyword, __location__, name="scale_x0", &
562  description="scales the exchange part of the original hole PBE-functional", &
563  default_r_val=0.0_dp)
564  CALL section_add_keyword(subsection, keyword)
565  CALL keyword_release(keyword)
566  CALL keyword_create(keyword, __location__, name="omega", &
567  description="screening parameter", &
568  default_r_val=1._dp)
569  CALL section_add_keyword(subsection, keyword)
570  CALL keyword_release(keyword)
571  CALL section_add_subsection(section, subsection)
572  CALL section_release(subsection)
573 
574  CALL section_create(subsection, __location__, name="BECKE97", &
575  description="Uses the Becke 97 exchange correlation functional", &
576  n_keywords=0, n_subsections=0, repeats=.false., &
577  citations=(/becke1997, grimme2006/))
578  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
579  description="activates the functional", &
580  lone_keyword_l_val=.true., default_l_val=.false.)
581  CALL section_add_keyword(subsection, keyword)
582  CALL keyword_release(keyword)
583  CALL keyword_create(keyword, __location__, name="scale_x", &
584  description="scales the exchange part of the functional, if -1 the default for the given parametrization is used", &
585  default_r_val=-1._dp)
586  CALL section_add_keyword(subsection, keyword)
587  CALL keyword_release(keyword)
588  CALL keyword_create(keyword, __location__, name="scale_c", &
589  description="scales the correlation part of the functional", &
590  default_r_val=1._dp)
591  CALL section_add_keyword(subsection, keyword)
592  CALL keyword_release(keyword)
593  CALL keyword_create(keyword, __location__, name="parametrization", &
594  description="switches between the B97 and Grimme parametrization ", &
596  enum_c_vals=(/"ORIG ", "B97GRIMME ", "B97_GRIMME", "wB97X-V ", "B97-3c "/), &
597  default_i_val=xc_b97_orig)
598  CALL section_add_keyword(subsection, keyword)
599  CALL keyword_release(keyword)
600 
601  CALL section_add_subsection(section, subsection)
602  CALL section_release(subsection)
603 
604  CALL section_create(subsection, __location__, name="BECKE_ROUSSEL", &
605  description="Becke Roussel exchange hole model. Can be used "// &
606  "as long range correction with a truncated coulomb potential", &
607  n_keywords=0, n_subsections=0, repeats=.false., &
608  citations=(/beckeroussel1989, proynov2007/))
609  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
610  description="activates the functional", &
611  lone_keyword_l_val=.true., default_l_val=.false.)
612  CALL section_add_keyword(subsection, keyword)
613  CALL keyword_release(keyword)
614  CALL keyword_create(keyword, __location__, name="scale_x", &
615  description="scales the exchange part of the functional", &
616  default_r_val=1._dp)
617  CALL section_add_keyword(subsection, keyword)
618  CALL keyword_release(keyword)
619  CALL keyword_create(keyword, __location__, name="CUTOFF_RADIUS", &
620  description="Defines the cutoff radius for the truncation. "// &
621  "If put to zero, the standard full range potential will be used", &
622  usage="CUTOFF_RADIUS 2.0", default_r_val=0.0_dp)
623  CALL section_add_keyword(subsection, keyword)
624  CALL keyword_release(keyword)
625  CALL keyword_create(keyword, __location__, name="GAMMA", &
626  description="Parameter in the exchange hole. "// &
627  "Usually this is put to 1.0 or 0.8", &
628  usage="GAMMA 0.8", default_r_val=1.0_dp)
629  CALL section_add_keyword(subsection, keyword)
630  CALL keyword_release(keyword)
631  CALL section_add_subsection(section, subsection)
632  CALL section_release(subsection)
633 
634  CALL section_create(subsection, __location__, name="LDA_HOLE_T_C_LR", &
635  description="LDA exchange hole model in truncated coulomb potential", &
636  n_keywords=0, n_subsections=0, repeats=.false.)
637  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
638  description="activates the functional", &
639  lone_keyword_l_val=.true., default_l_val=.false.)
640  CALL section_add_keyword(subsection, keyword)
641  CALL keyword_release(keyword)
642  CALL keyword_create(keyword, __location__, name="SCALE_X", &
643  description="scales the exchange part of the functional", &
644  default_r_val=1._dp)
645  CALL section_add_keyword(subsection, keyword)
646  CALL keyword_release(keyword)
647  CALL keyword_create(keyword, __location__, name="CUTOFF_RADIUS", &
648  description="Defines cutoff for lower integration boundary", &
649  default_r_val=0.0_dp, unit_str="angstrom")
650  CALL section_add_keyword(subsection, keyword)
651  CALL keyword_release(keyword)
652  CALL section_add_subsection(section, subsection)
653  CALL section_release(subsection)
654 
655  CALL section_create(subsection, __location__, name="PBE_HOLE_T_C_LR", &
656  description="PBE exchange hole model in trucanted coulomb potential", &
657  n_keywords=0, n_subsections=0, repeats=.false.)
658  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
659  description="activates the functional", &
660  lone_keyword_l_val=.true., default_l_val=.false.)
661  CALL section_add_keyword(subsection, keyword)
662  CALL keyword_release(keyword)
663  CALL keyword_create(keyword, __location__, name="SCALE_X", &
664  description="scales the exchange part of the functional", &
665  default_r_val=1._dp)
666  CALL section_add_keyword(subsection, keyword)
667  CALL keyword_release(keyword)
668  CALL keyword_create(keyword, __location__, name="CUTOFF_RADIUS", &
669  description="Defines cutoff for lower integration boundary", &
670  default_r_val=1.0_dp, unit_str="angstrom")
671  CALL section_add_keyword(subsection, keyword)
672  CALL keyword_release(keyword)
673  CALL section_add_subsection(section, subsection)
674  CALL section_release(subsection)
675 
676  CALL section_create(subsection, __location__, name="GV09", &
677  description="Combination of three different exchange hole models", &
678  n_keywords=0, n_subsections=0, repeats=.false.)
679  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
680  description="activates the functional", &
681  lone_keyword_l_val=.true., default_l_val=.false.)
682  CALL section_add_keyword(subsection, keyword)
683  CALL keyword_release(keyword)
684  CALL keyword_create(keyword, __location__, name="SCALE_X", &
685  description="scales the exchange part of the functional", &
686  default_r_val=1._dp)
687  CALL section_add_keyword(subsection, keyword)
688  CALL keyword_release(keyword)
689  CALL keyword_create(keyword, __location__, name="CUTOFF_RADIUS", &
690  description="Defines cutoff for lower integration boundary", &
691  default_r_val=0.0_dp, unit_str="angstrom")
692  CALL section_add_keyword(subsection, keyword)
693  CALL keyword_release(keyword)
694  CALL keyword_create(keyword, __location__, name="GAMMA", &
695  description="Parameter for Becke Roussel hole", &
696  default_r_val=1.0_dp)
697  CALL section_add_keyword(subsection, keyword)
698  CALL keyword_release(keyword)
699  CALL section_add_subsection(section, subsection)
700  CALL section_release(subsection)
701 
702  CALL section_create(subsection, __location__, name="BEEF", & !rk: BEEF Exchange
703  description="Uses the BEEFvdW exchange functional", &
704  n_keywords=0, n_subsections=0, repeats=.false., &
705  citations=(/wellendorff2012/))
706  CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
707  description="activates the functional", &
708  lone_keyword_l_val=.true., default_l_val=.false.)
709  CALL section_add_keyword(subsection, keyword)
710  CALL keyword_release(keyword)
711  CALL keyword_create(keyword, __location__, name="scale_x", &
712  description="scales the exchange part of the functional", &
713  default_r_val=1._dp)
714  CALL section_add_keyword(subsection, keyword)
715  CALL keyword_release(keyword)
716  CALL section_add_subsection(section, subsection)
717  CALL section_release(subsection)
718 
719  END SUBROUTINE create_xc_fun_section
720 
721 ! **************************************************************************************************
722 !> \brief creates the structure of the section needed to select an xc potential
723 !> \param section the section that will be created
724 !> \author thomas chassaing
725 ! **************************************************************************************************
726  SUBROUTINE create_xc_potential_section(section)
727  TYPE(section_type), POINTER :: section
728 
729  TYPE(keyword_type), POINTER :: keyword
730  TYPE(section_type), POINTER :: subsection
731 
732  cpassert(.NOT. ASSOCIATED(section))
733  CALL section_create(section, __location__, name="xc_potential", &
734  description="The xc potential to use (CAREFUL: xc potential here refers "// &
735  "to potentials that are not derived from an xc functional, but rather are "// &
736  "modelled directly. Therefore there is no consistent xc energy available. "// &
737  "To still get an energy expression, see ENERGY below", &
738  n_keywords=1, n_subsections=1, repeats=.false.)
739 
740  NULLIFY (subsection, keyword)
741  CALL section_create(subsection, __location__, name="SAOP", &
742  description="Uses the SAOP potential", &
743  n_keywords=3, n_subsections=0, repeats=.true.)
744  CALL keyword_create(keyword, __location__, name="ALPHA", &
745  description="Value of the alpha parameter (default = 1.19).", &
746  usage="ALPHA 1.19", default_r_val=1.19_dp)
747  CALL section_add_keyword(subsection, keyword)
748  CALL keyword_release(keyword)
749  CALL keyword_create(keyword, __location__, name="BETA", &
750  description="Value of the beta parameter (default = 0.01).", &
751  usage="BETA 0.01", default_r_val=0.01_dp)
752  CALL section_add_keyword(subsection, keyword)
753  CALL keyword_release(keyword)
754  CALL keyword_create(keyword, __location__, name="K_RHO", &
755  description="Value of the K_rho parameter (default = 0.42).", &
756  usage="ALPHA 0.42", default_r_val=0.42_dp)
757  CALL section_add_keyword(subsection, keyword)
758  CALL keyword_release(keyword)
759  CALL section_add_subsection(section, subsection)
760  CALL section_release(subsection)
761 
762  CALL keyword_create(keyword, __location__, name="ENERGY", &
763  description="How to determine the total energy.", &
764  usage="ENERGY [NONE,XC_FUNCTIONAL,SUM_EIGENVALUES", &
765  enum_c_vals=s2a("NONE", "XC_FUNCTIONAL", "FUNCTIONAL", "SUM_EIGENVALUES", "SOE"), &
766  enum_i_vals=(/xc_pot_energy_none, &
771  default_i_val=xc_pot_energy_none)
772  CALL section_add_keyword(section, keyword)
773  CALL keyword_release(keyword)
774 
775  END SUBROUTINE create_xc_potential_section
776 
777 ! **************************************************************************************************
778 !> \brief creates the structure of the section needed to select an xc kernel
779 !> \param section the section that will be created
780 !> \author JGH
781 ! **************************************************************************************************
782  SUBROUTINE create_xc_kernel_section(section)
783  TYPE(section_type), POINTER :: section
784 
785  TYPE(keyword_type), POINTER :: keyword
786 
787  cpassert(.NOT. ASSOCIATED(section))
788  CALL section_create(section, __location__, name="XC_KERNEL", &
789  description="The xc kernel to use (CAREFUL: xc kernel here refers "// &
790  "to kernels that are not derived from an xc functional, but rather are "// &
791  "modelled directly. This kernel will be used in a TDDFPT calculation. "// &
792  "Cannot be combined with XC_FUNCTIONAL or XC_POTENTIAL.", &
793  n_keywords=1, n_subsections=1, repeats=.false.)
794 
795  NULLIFY (keyword)
796  CALL keyword_create( &
797  keyword, __location__, name="_SECTION_PARAMETERS_", &
798  description="Selection of kernel functionals.", &
799  usage="&XC_KERNEL LDAfxc", &
800  enum_c_vals=s2a("PADEfxc", "LDAfxc", "GGAfxc", "NONE"), &
801  enum_i_vals=(/fxc_funct_pade, fxc_funct_lda, fxc_funct_gga, fxc_none/), &
802  enum_desc=s2a("Fxc based on LDA PADE approximation", &
803  "Fxc based on LDA functionals", &
804  "Fxc model from fit to PBE functional", &
805  "NONE"), &
806  default_i_val=fxc_none, &
807  lone_keyword_i_val=fxc_none)
808  CALL section_add_keyword(section, keyword)
809  CALL keyword_release(keyword)
810 
811  CALL keyword_create(keyword, __location__, name="PARAMETER", &
812  description="List of parameters specific to the kernel function", &
813  usage="PARAMETER <REAL> .. <REAL>", &
814  type_of_var=real_t, n_var=-1)
815  CALL section_add_keyword(section, keyword)
816  CALL keyword_release(keyword)
817  CALL keyword_create(keyword, __location__, name="GAMMA", &
818  description="B97 GAMMA parameters [gx, gab, gaa]", &
819  usage="GAMMA <REAL> <REAL> <REAL>", &
820  default_r_vals=(/0.004_dp, 0.006_dp, 0.2_dp/), &
821  type_of_var=real_t, n_var=3)
822  CALL section_add_keyword(section, keyword)
823  CALL keyword_release(keyword)
824  CALL keyword_create(keyword, __location__, name="C_XAA", &
825  description="B97 C parameters for exchange", &
826  usage="C_XAA <REAL> <REAL> <REAL>", &
827  default_r_vals=(/1.0_dp, 0.63_dp, 0.94_dp/), &
828  type_of_var=real_t, n_var=3)
829  CALL section_add_keyword(section, keyword)
830  CALL keyword_release(keyword)
831  CALL keyword_create(keyword, __location__, name="C_CAB", &
832  description="B97 C parameters for same spin correlation.", &
833  usage="C_CAB <REAL> <REAL> <REAL>", &
834  default_r_vals=(/1.0_dp, 0.75_dp, -4.60_dp/), &
835  type_of_var=real_t, n_var=3)
836  CALL section_add_keyword(section, keyword)
837  CALL keyword_release(keyword)
838  CALL keyword_create(keyword, __location__, name="C_CAA", &
839  description="B97 C parameters for opposite spin correlation.", &
840  usage="C_CAB <REAL> <REAL> <REAL>", &
841  default_r_vals=(/0.17_dp, 2.35_dp, -2.55_dp/), &
842  type_of_var=real_t, n_var=3)
843  CALL section_add_keyword(section, keyword)
844  CALL keyword_release(keyword)
845  CALL keyword_create(keyword, __location__, name="SCALE_X", &
846  description="Scaling parameter for exchange kernel.", &
847  usage="SCALE_X 0.2", default_r_val=1.0_dp)
848  CALL section_add_keyword(section, keyword)
849  CALL keyword_release(keyword)
850  CALL keyword_create(keyword, __location__, name="SCALE_C", &
851  description="Scaling parameter for correlation kernel.", &
852  usage="SCALE_C 0.2", default_r_val=1.0_dp)
853  CALL section_add_keyword(section, keyword)
854  CALL keyword_release(keyword)
855 
856  END SUBROUTINE create_xc_kernel_section
857 
858 ! **************************************************************************************************
859 !> \brief creates the structure of the section needed to select an hfx kernel
860 !> \param section the section that will be created
861 !> \author JGH
862 ! **************************************************************************************************
863  SUBROUTINE create_hfx_kernel_section(section)
864  TYPE(section_type), POINTER :: section
865 
866  TYPE(keyword_type), POINTER :: keyword
867  TYPE(section_type), POINTER :: subsection
868 
869  cpassert(.NOT. ASSOCIATED(section))
870  CALL section_create(section, __location__, name="HFX_KERNEL", &
871  description="The hfx kernel to use. Cannot be combined with HF section.", &
872  n_keywords=1, n_subsections=2, repeats=.false.)
873 
874  NULLIFY (subsection, keyword)
875  CALL keyword_create(keyword, __location__, name="DO_HFXSR", &
876  description="Switch to use the HFXSR (short range) kernel.", &
877  usage="DO_HFXSR T/F", default_l_val=.false., &
878  lone_keyword_l_val=.true.)
879  CALL section_add_keyword(section, keyword)
880  CALL keyword_release(keyword)
881  NULLIFY (subsection, keyword)
882  CALL keyword_create(keyword, __location__, name="HFXSR_PRIMBAS", &
883  description="Default number of primitives in ADMM basis in HFXSR. "// &
884  "0 indicates the use of a contracted minimal basis. ", &
885  usage="HFXSR_PRIMBAS 3", default_i_val=0)
886  CALL section_add_keyword(section, keyword)
887  CALL keyword_release(keyword)
888 
889  CALL create_hfx_section(subsection)
890  CALL section_add_subsection(section, subsection)
891  CALL section_release(subsection)
892 
893  CALL section_create(subsection, __location__, name="HFXLR", &
894  description="Uses the HFXLR (long range) kernel", &
895  n_keywords=2, n_subsections=0, repeats=.false.)
896  CALL keyword_create(keyword, __location__, name="RCUT", &
897  description="Value of lower range cutoff of interaction [Bohr]", &
898  usage="RCUT 5.00", default_r_val=6.00_dp, unit_str="bohr")
899  CALL section_add_keyword(subsection, keyword)
900  CALL keyword_release(keyword)
901  CALL keyword_create(keyword, __location__, name="SCALE", &
902  description="Scaling parameter for HFX kernel.", &
903  usage="SCALE 0.25", default_r_val=1.00_dp)
904  CALL section_add_keyword(subsection, keyword)
905  CALL keyword_release(keyword)
906  CALL section_add_subsection(section, subsection)
907  CALL section_release(subsection)
908 
909  END SUBROUTINE create_hfx_kernel_section
910 ! **************************************************************************************************
911 !> \brief creates the structure of the section needed for vdW potentials
912 !> \param section the section that will be created
913 !> \author jgh
914 ! **************************************************************************************************
915  SUBROUTINE create_vdw_potential_section(section)
916  TYPE(section_type), POINTER :: section
917 
918  TYPE(keyword_type), POINTER :: keyword
919  TYPE(section_type), POINTER :: print_key, subsection
920 
921  cpassert(.NOT. ASSOCIATED(section))
922  CALL section_create(section, __location__, name="vdw_potential", &
923  description="This section combines all possible additional dispersion "// &
924  "corrections to the normal XC functionals. This can be more functionals "// &
925  "or simple empirical pair potentials. ", &
926  citations=(/grimme2006, tran2013/), &
927  n_keywords=1, n_subsections=1, repeats=.false.)
928 
929  NULLIFY (subsection, keyword)
930  CALL keyword_create(keyword, __location__, name="POTENTIAL_TYPE", &
931  variants=s2a("DISPERSION_FUNCTIONAL"), &
932  description="Type of dispersion/vdW functional or potential to use", &
933  usage="POTENTIAL_TYPE (NONE|PAIR_POTENTIAL|NON_LOCAL)", &
934  enum_c_vals=s2a("NONE", "PAIR_POTENTIAL", "NON_LOCAL"), &
936  enum_desc=s2a("No dispersion/van der Waals functional", &
937  "Pair potential van der Waals density functional", &
938  "Nonlocal van der Waals density functional"), &
939  default_i_val=xc_vdw_fun_none)
940  CALL section_add_keyword(section, keyword)
941  CALL keyword_release(keyword)
942 
943  CALL section_create(subsection, __location__, name="PAIR_POTENTIAL", &
944  description="Information on the pair potential to calculate dispersion", &
945  n_keywords=5, n_subsections=0, repeats=.true.)
946  CALL keyword_create(keyword, __location__, name="R_CUTOFF", &
947  description="Range of potential. The cutoff will be 2 times this value", &
948  usage="R_CUTOFF 24.0", default_r_val=20.0_dp, &
949  unit_str="angstrom")
950  CALL section_add_keyword(subsection, keyword)
951  CALL keyword_release(keyword)
952  CALL keyword_create(keyword, __location__, name="TYPE", &
953  description="Type of potential", &
954  citations=(/grimme2006, grimme2010, grimme2011/), &
955  usage="TYPE (DFTD2|DFTD3|DFTD3(BJ))", &
956  enum_c_vals=s2a("DFTD2", "DFTD3", "DFTD3(BJ)"), &
958  enum_desc=s2a("Grimme D2 method", &
959  "Grimme D3 method (zero damping)", &
960  "Grimme D3 method (Becke-Johnson damping)"), &
961  default_i_val=vdw_pairpot_dftd3)
962  CALL section_add_keyword(subsection, keyword)
963  CALL keyword_release(keyword)
964  CALL keyword_create(keyword, __location__, name="PARAMETER_FILE_NAME", &
965  description="Name of the parameter file, may include a path", &
966  usage="PARAMETER_FILE_NAME <FILENAME>", &
967  default_lc_val="DISPERSION_PARAMETERS")
968  CALL section_add_keyword(subsection, keyword)
969  CALL keyword_release(keyword)
970  CALL keyword_create(keyword, __location__, name="REFERENCE_FUNCTIONAL", &
971  description="Use parameters for this specific density functional. "// &
972  "For available D3 and D3(BJ) parameters see: "// &
973  "<https://www.chemie.uni-bonn.de/grimme/de/software/dft-d3>.", &
974  usage="REFERENCE_FUNCTIONAL <functional>", &
975  type_of_var=char_t)
976  CALL section_add_keyword(subsection, keyword)
977  CALL keyword_release(keyword)
978  CALL keyword_create(keyword, __location__, name="SCALING", &
979  description="XC Functional dependent scaling parameter, if set to zero CP2K attempts"// &
980  " to guess the xc functional that is in use and sets the associated scaling parameter.", &
981  usage="SCALING 0.2", default_r_val=0._dp)
982  CALL section_add_keyword(subsection, keyword)
983  CALL keyword_release(keyword)
984  CALL keyword_create(keyword, __location__, name="EXP_PRE", &
985  description="Prefactor in exponential damping factor (DFT-D2 potential)", &
986  usage="EXP_PRE 20.", default_r_val=20._dp)
987  CALL section_add_keyword(subsection, keyword)
988  CALL keyword_release(keyword)
989  CALL keyword_create(keyword, __location__, name="EPS_CN", &
990  description="Cutoff value for coordination number function (DFT-D3 method)", &
991  usage="EPS_CN 1.e-6_dp", default_r_val=1.e-6_dp)
992  CALL section_add_keyword(subsection, keyword)
993  CALL keyword_release(keyword)
994  CALL keyword_create(keyword, __location__, name="D3_SCALING", &
995  description="XC Functional dependent scaling parameters (s6,sr6,s8) for the DFT-D3 method,"// &
996  " if set to zero CP2K attempts"// &
997  " to guess the xc functional from REFERENCE_FUNCTIONAL and sets the associated scaling parameter.", &
998  usage="D3_SCALING 1.0 1.0 1.0", n_var=3, &
999  default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/))
1000  CALL section_add_keyword(subsection, keyword)
1001  CALL keyword_release(keyword)
1002  CALL keyword_create(keyword, __location__, name="D3BJ_SCALING", &
1003  description="XC Functional dependent scaling parameters (s6,a1,s8,a2) for the DFT-D3(BJ) method,"// &
1004  " if set to zero CP2K attempts"// &
1005  " to guess the xc functional from REFERENCE_FUNCTIONAL and sets the associated scaling parameter.", &
1006  usage="D3BJ_SCALING 1.0 1.0 1.0 1.0", n_var=4, &
1007  default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp, 0.0_dp/))
1008  CALL section_add_keyword(subsection, keyword)
1009  CALL keyword_release(keyword)
1010  CALL keyword_create(keyword, __location__, name="CALCULATE_C9_TERM", &
1011  description="Calculate C9 terms in DFT-D3 model", &
1012  usage="CALCULATE_C9_TERM", default_l_val=.false., &
1013  lone_keyword_l_val=.true.)
1014  CALL section_add_keyword(subsection, keyword)
1015  CALL keyword_release(keyword)
1016  CALL keyword_create(keyword, __location__, name="REFERENCE_C9_TERM", &
1017  description="Calculate C9 terms in DFT-D3 model using reference coordination numbers", &
1018  usage="REFERENCE_C9_TERM", default_l_val=.false., &
1019  lone_keyword_l_val=.true.)
1020  CALL section_add_keyword(subsection, keyword)
1021  CALL keyword_release(keyword)
1022  CALL keyword_create(keyword, __location__, name="LONG_RANGE_CORRECTION", &
1023  description="Calculate a long range correction to the DFT-D3 model."// &
1024  " WARNING: Use with care! Only for isotropic dense systems.", &
1025  usage="LONG_RANGE_CORRECTION", default_l_val=.false., &
1026  lone_keyword_l_val=.true.)
1027  CALL section_add_keyword(subsection, keyword)
1028  CALL keyword_release(keyword)
1029  CALL keyword_create(keyword, __location__, name="SHORT_RANGE_CORRECTION", &
1030  description="Calculate a short-range bond correction to the DFT-D3 model", &
1031  usage="SHORT_RANGE_CORRECTION", default_l_val=.false., &
1032  lone_keyword_l_val=.true.)
1033  CALL section_add_keyword(subsection, keyword)
1034  CALL keyword_release(keyword)
1035  CALL keyword_create(keyword, __location__, name="SHORT_RANGE_CORRECTION_PARAMETERS", &
1036  description="Parameters for the short-range bond correction to the DFT-D3 model. "// &
1037  "s*(za*zb)^t1*EXP(-g*dr*r0ab^t2), parameters: s, g, t1, t2 "// &
1038  "Defaults: s=0.08, g=10.0, t1=0.5, t2=-1.0 ", &
1039  usage="SHORT_RANGE_CORRECTION_PARAMETRS", default_r_vals=(/0.08_dp, 10.0_dp, 0.5_dp, -1.0_dp/), &
1040  n_var=4, type_of_var=real_t)
1041  CALL section_add_keyword(subsection, keyword)
1042  CALL keyword_release(keyword)
1043  ! KG molecular corrections
1044  CALL keyword_create(keyword, __location__, name="MOLECULE_CORRECTION", &
1045  description="Calculate a intermolecular correction to the DFT-D3 model", &
1046  usage="MOLECULE_CORRECTION", default_l_val=.false., &
1047  lone_keyword_l_val=.true.)
1048  CALL section_add_keyword(subsection, keyword)
1049  CALL keyword_release(keyword)
1050  CALL keyword_create(keyword, __location__, name="MOLECULE_CORRECTION_C8", &
1051  description="Calculate a intermolecular correction to the C8 term in the DFT-D3 model", &
1052  usage="MOLECULE_CORRECTION_C8 1.0 ", default_r_val=0.0_dp)
1053  CALL section_add_keyword(subsection, keyword)
1054  CALL keyword_release(keyword)
1055  CALL keyword_create(keyword, __location__, name="VERBOSE_OUTPUT", &
1056  description="Extensive output for the DFT-D2 and DFT-D3 models", &
1057  usage="VERBOSE_OUTPUT", default_l_val=.false., &
1058  lone_keyword_l_val=.true.)
1059  CALL section_add_keyword(subsection, keyword)
1060  CALL keyword_release(keyword)
1061 
1062  ! Set coordination numbers by atom numbers
1063  CALL keyword_create(keyword, __location__, name="D3_EXCLUDE_KIND", &
1064  description="Specifies the atomic kinds excluded in the DFT-D3 calculation.", &
1065  usage="D3_EXCLUDE_KIND kind1 kind2 ... ", repeats=.false., &
1066  n_var=-1, type_of_var=integer_t)
1067  CALL section_add_keyword(subsection, keyword)
1068  CALL keyword_release(keyword)
1069 
1070  ! Ignore selected pair interactins
1071  CALL keyword_create(keyword, __location__, name="D3_EXCLUDE_KIND_PAIR", &
1072  description="Specifies the atomic kinds for interactions excluded from the DFT-D3 calculation.", &
1073  usage="D3_EXCLUDE_KIND_PAIR kind1 kind2 ", repeats=.true., &
1074  n_var=2, type_of_var=integer_t)
1075  CALL section_add_keyword(subsection, keyword)
1076  CALL keyword_release(keyword)
1077 
1078  ! Set coordination numbers by atom kinds
1079  CALL keyword_create(keyword, __location__, name="KIND_COORDINATION_NUMBERS", &
1080  description="Specifies the coordination number for a kind for the C9 term in DFT-D3.", &
1081  usage="KIND_COORDINATION_NUMBERS CN kind ", repeats=.true., &
1082  n_var=-1, type_of_var=char_t)
1083  CALL section_add_keyword(subsection, keyword)
1084  CALL keyword_release(keyword)
1085  ! Set coordination numbers by atom numbers
1086  CALL keyword_create(keyword, __location__, name="ATOM_COORDINATION_NUMBERS", &
1087  description="Specifies the coordination number of a set of atoms for the C9 term in DFT-D3.", &
1088  usage="ATOM_COORDINATION_NUMBERS CN atom1 atom2 ... ", repeats=.true., &
1089  n_var=-1, type_of_var=char_t)
1090  CALL section_add_keyword(subsection, keyword)
1091  CALL keyword_release(keyword)
1092 
1093  ! parameter specification atom by atom
1094  CALL keyword_create(keyword, __location__, name="ATOMPARM", &
1095  description="Specifies parameters for atom types (in atomic units). If "// &
1096  "not provided default parameters are used (DFT-D2).", &
1097  usage="ATOMPARM <ELEMENT> <C6_parameter> <vdw_radii>", &
1098  repeats=.true., n_var=-1, type_of_var=char_t)
1099  CALL section_add_keyword(subsection, keyword)
1100  CALL keyword_release(keyword)
1101 
1102  NULLIFY (print_key)
1103  CALL cp_print_key_section_create(print_key, __location__, "PRINT_DFTD", &
1104  description="Controls the printing of some info about DFTD contributions", &
1105  print_level=high_print_level, add_last=add_last_numeric, filename="")
1106  CALL section_add_subsection(subsection, print_key)
1107  CALL section_release(print_key)
1108 
1109  CALL section_add_subsection(section, subsection)
1110  CALL section_release(subsection)
1111 
1112  ! nonlocal section
1113  NULLIFY (subsection, keyword)
1114  CALL section_create(subsection, __location__, name="NON_LOCAL", &
1115  description="Information on the non local part of dispersion functionals. "// &
1116  "Correct functionals require a corresponding setting of XC_FUNCTIONAL.", &
1117  n_keywords=0, n_subsections=0, repeats=.true.)
1118 
1119  CALL keyword_create(keyword, __location__, name="TYPE", &
1120  description="Type of functional (the corresponding kernel data file should be selected). "// &
1121  "Allows for common forms such as vdW-DF, vdW-DF2, optB88-vdW, rVV10.", &
1122  usage="TYPE DRSLL", &
1123  enum_c_vals=s2a("DRSLL", "LMKLL", "RVV10"), &
1124  enum_i_vals=(/vdw_nl_drsll, vdw_nl_lmkll, vdw_nl_rvv10/), &
1125  enum_desc=s2a("Dion-Rydberg-Schroeder-Langreth-Lundqvist nonlocal van der Waals density functional", &
1126  "Lee-Murray-Kong-Lundqvist-Langreth nonlocal van der Waals density functional", &
1127  "Revised Vydrov-van Voorhis nonlocal van der Waals density functional"), &
1128  citations=(/tran2013/), &
1129  default_i_val=vdw_nl_drsll)
1130  CALL section_add_keyword(subsection, keyword)
1131  CALL keyword_release(keyword)
1132  CALL keyword_create(keyword, __location__, name="VERBOSE_OUTPUT", &
1133  description="Extensive output for non local functionals", &
1134  usage="VERBOSE_OUTPUT", default_l_val=.false., &
1135  lone_keyword_l_val=.true.)
1136  CALL section_add_keyword(subsection, keyword)
1137  CALL keyword_release(keyword)
1138  CALL keyword_create(keyword, __location__, name="KERNEL_FILE_NAME", &
1139  description="Name of the kernel data file, may include a path. "// &
1140  "vdW_kernel_table.dat is for DRSLL and LMKLL and "// &
1141  "rVV10_kernel_table.dat is for rVV10.", &
1142  usage="KERNEL_FILE_NAME <FILENAME>", &
1143  default_lc_val="vdW_kernel_table.dat")
1144  CALL section_add_keyword(subsection, keyword)
1145  CALL keyword_release(keyword)
1146  CALL keyword_create(keyword, __location__, name="CUTOFF", &
1147  description="The cutoff of the FFT grid used in the calculation "// &
1148  "of the nonlocal vdW functional [Ry].", &
1149  usage="CUTOFF 300", &
1150  default_r_val=-1._dp, unit_str="Ry")
1151  CALL section_add_keyword(subsection, keyword)
1152  CALL keyword_release(keyword)
1153  CALL keyword_create(keyword, __location__, name="PARAMETERS", &
1154  description="Parameters b and C of the rVV10 functional", &
1155  usage="PARAMETERS 6.3 0.0093", &
1156  type_of_var=real_t, default_r_vals=(/6.3_dp, 0.0093_dp/), n_var=2)
1157  CALL section_add_keyword(subsection, keyword)
1158  CALL keyword_release(keyword)
1159  CALL keyword_create(keyword, __location__, name="SCALE", &
1160  description="Scales the energy contribution of the rVV10 functional", &
1161  usage="SCALE 1.0", &
1162  type_of_var=real_t, default_r_val=1.0_dp)
1163  CALL section_add_keyword(subsection, keyword)
1164  CALL keyword_release(keyword)
1165 
1166  CALL section_add_subsection(section, subsection)
1167  CALL section_release(subsection)
1168 
1169  END SUBROUTINE create_vdw_potential_section
1170 
1171 ! **************************************************************************************************
1172 !> \brief creates the structure of the section needed for gCP potentials
1173 !> \param section the section that will be created
1174 !> \author jgh
1175 ! **************************************************************************************************
1176  SUBROUTINE create_gcp_potential_section(section)
1177  TYPE(section_type), POINTER :: section
1178 
1179  TYPE(keyword_type), POINTER :: keyword
1180 
1181  cpassert(.NOT. ASSOCIATED(section))
1182  CALL section_create(section, __location__, name="gcp_potential", &
1183  description="This section combines geometrical counterpoise potentials."// &
1184  " This is a simple empirical pair potential to correct for BSSE. ", &
1185  citations=(/kruse2012/), &
1186  n_keywords=1, n_subsections=1, repeats=.false.)
1187 
1188  NULLIFY (keyword)
1189  CALL keyword_create(keyword, __location__, name="PARAMETER_FILE_NAME", &
1190  description="Name of the parameter file, may include a path", &
1191  usage="PARAMETER_FILE_NAME <FILENAME>", &
1192  default_lc_val="---")
1193  CALL section_add_keyword(section, keyword)
1194  CALL keyword_release(keyword)
1195 
1196  CALL keyword_create(keyword, __location__, name="GLOBAL_PARAMETERS", &
1197  description="Global parameters of the gCP method."// &
1198  " Parameters are sigma, alpha, beta, eta from the original paper.", &
1199  usage="GLOBAL_PARAMETERS 1.0 1.0 1.0 1.0", n_var=4, &
1200  default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp, 0.0_dp/))
1201  CALL section_add_keyword(section, keyword)
1202  CALL keyword_release(keyword)
1203 
1204  CALL keyword_create(keyword, __location__, name="DELTA_ENERGY", &
1205  description="Specify the delta energy [Hartree] term for an atom kind", &
1206  usage="DELTA_ENERGY type value", &
1207  type_of_var=char_t, repeats=.true., n_var=-1, default_c_vals=(/"XX ", "0.0"/))
1208  CALL section_add_keyword(section, keyword)
1209  CALL keyword_release(keyword)
1210 
1211  CALL keyword_create(keyword, __location__, name="VERBOSE", &
1212  description="Verbose output for gCP calculation", &
1213  usage="VERBOSE logical_value", &
1214  default_l_val=.true., lone_keyword_l_val=.true.)
1215  CALL section_add_keyword(section, keyword)
1216  CALL keyword_release(keyword)
1217 
1218  END SUBROUTINE create_gcp_potential_section
1219 
1220 ! **************************************************************************************************
1221 !> \brief creates the input section for the xc part
1222 !> \param section the section to create
1223 !> \author fawzi
1224 ! **************************************************************************************************
1225  SUBROUTINE create_xc_section(section)
1226  TYPE(section_type), POINTER :: section
1227 
1228  TYPE(keyword_type), POINTER :: keyword
1229  TYPE(section_type), POINTER :: subsection
1230 
1231  cpassert(.NOT. ASSOCIATED(section))
1232  CALL section_create(section, __location__, name="xc", &
1233  description="Parameters needed for the calculation of the eXchange and Correlation potential", &
1234  n_keywords=5, n_subsections=2, repeats=.false.)
1235 
1236  NULLIFY (subsection, keyword)
1237 
1238  CALL keyword_create(keyword, __location__, name="density_cutoff", &
1239  description="The cutoff on the density used by the xc calculation", &
1240  usage="density_cutoff 1.e-11", default_r_val=1.0e-10_dp)
1241  CALL section_add_keyword(section, keyword)
1242  CALL keyword_release(keyword)
1243 
1244  CALL keyword_create(keyword, __location__, name="gradient_cutoff", &
1245  description="The cutoff on the gradient of the density used by the "// &
1246  "xc calculation", &
1247  usage="gradient_cutoff 1.e-11", default_r_val=1.0e-10_dp)
1248  CALL section_add_keyword(section, keyword)
1249  CALL keyword_release(keyword)
1250 
1251  CALL keyword_create(keyword, __location__, name="DENSITY_SMOOTH_CUTOFF_RANGE", &
1252  description="Parameter for the smoothing procedure in xc calculation", &
1253  usage="gradient_cutoff {real}", default_r_val=0.0_dp)
1254  CALL section_add_keyword(section, keyword)
1255  CALL keyword_release(keyword)
1256 
1257  CALL keyword_create(keyword, __location__, name="tau_cutoff", &
1258  description="The cutoff on tau used by the xc calculation", &
1259  usage="tau_cutoff 1.e-11", default_r_val=1.0e-10_dp)
1260  CALL section_add_keyword(section, keyword)
1261  CALL keyword_release(keyword)
1262 
1263  CALL keyword_create( &
1264  keyword, __location__, name="FUNCTIONAL_ROUTINE", &
1265  description="Select the code for xc calculation", &
1266  usage="FUNCTIONAL_ROUTINE (DEFAULT|TEST_LSD|DEBUG)", &
1267  default_i_val=xc_default_f_routine, &
1268  enum_c_vals=s2a("DEFAULT", "TEST_LSD", "DEBUG"), &
1270  enum_desc=s2a("Carry out exchange-correlation functional calculation", &
1271  "Use test local-spin-density approximation code for exchange-correlation functional calculation", &
1272  "Use debug new code for exchange-correlation functional calculation"))
1273  CALL section_add_keyword(section, keyword)
1274  CALL keyword_release(keyword)
1275 
1276  CALL section_create(subsection, __location__, name="xc_grid", & !FM to do
1277  description="The xc parameters used when calculating the xc on the grid", &
1278  n_keywords=5, n_subsections=0, repeats=.false.)
1279  CALL keyword_create(keyword, __location__, name="xc_smooth_rho", &
1280  description="The density smoothing used for the xc calculation", &
1281  usage="xc_smooth_rho nn10", default_i_val=xc_rho_no_smooth, &
1282  enum_c_vals=s2a("NONE", "NN50", "NN10", "SPLINE2", "NN6", "SPLINE3", "NN4"), &
1283  enum_i_vals=(/xc_rho_no_smooth, xc_rho_nn50, xc_rho_nn10, &
1286  CALL section_add_keyword(subsection, keyword)
1287  CALL keyword_release(keyword)
1288 
1289  CALL keyword_create(keyword, __location__, name="xc_deriv", &
1290  description="The method used to compute the derivatives", &
1291  usage="xc_deriv NN10_SMOOTH", default_i_val=xc_deriv_pw, &
1292  enum_c_vals=s2a("PW", "SPLINE3", "SPLINE2", "NN50_SMOOTH", "NN10_SMOOTH", &
1293  "SPLINE2_SMOOTH", "NN6_SMOOTH", "SPLINE3_SMOOTH", "NN4_SMOOTH", "COLLOCATE"), &
1294  enum_i_vals=(/xc_deriv_pw, xc_deriv_spline3, xc_deriv_spline2, &
1298  CALL section_add_keyword(subsection, keyword)
1299  CALL keyword_release(keyword)
1300 
1301  CALL keyword_create(keyword, __location__, name="use_finer_grid", &
1302  description="Uses a finer grid only to calculate the xc", &
1303  usage="use_finer_grid", default_l_val=.false., &
1304  lone_keyword_l_val=.true.)
1305  CALL section_add_keyword(subsection, keyword)
1306  CALL keyword_release(keyword)
1307 
1308  CALL keyword_create(keyword, __location__, name="2ND_DERIV_ANALYTICAL", &
1309  description="Use analytical formulas or finite differences for 2nd derivatives of XC", &
1310  usage="2ND_DERIV_ANALYTICAL logical", default_l_val=.true., &
1311  lone_keyword_l_val=.true.)
1312  CALL section_add_keyword(section, keyword)
1313  CALL keyword_release(keyword)
1314 
1315  CALL keyword_create(keyword, __location__, name="3RD_DERIV_ANALYTICAL", &
1316  description="Use analytical formulas or finite differences for 3rd derivatives of XC", &
1317  usage="3RD_DERIV_ANALYTICAL logical", default_l_val=.true., &
1318  lone_keyword_l_val=.true.)
1319  CALL section_add_keyword(section, keyword)
1320  CALL keyword_release(keyword)
1321 
1322  CALL keyword_create(keyword, __location__, name="STEP_SIZE", &
1323  description="Step size in terms of the first order potential for the numerical "// &
1324  "evaluation of XC derivatives", &
1325  usage="STEP_SIZE 1.0E-3", default_r_val=1e-3_dp)
1326  CALL section_add_keyword(section, keyword)
1327  CALL keyword_release(keyword)
1328 
1329  CALL keyword_create(keyword, __location__, name="NSTEPS", &
1330  description="Number of steps to consider in each direction for the numerical "// &
1331  "evaluation of XC derivatives. Must be a value from 1 to 4 (Default: 3).", &
1332  usage="NSTEPS 4", default_i_val=3)
1333  CALL section_add_keyword(section, keyword)
1334  CALL keyword_release(keyword)
1335 
1336  CALL section_add_subsection(section, subsection)
1337  CALL section_release(subsection)
1338 
1339  CALL create_xc_fun_section(subsection)
1340  CALL section_add_subsection(section, subsection)
1341  CALL section_release(subsection)
1342 
1343  CALL create_hfx_section(subsection)
1344  CALL section_add_subsection(section, subsection)
1345  CALL section_release(subsection)
1346 
1347  CALL create_mp2_section(subsection)
1348  CALL section_add_subsection(section, subsection)
1349  CALL section_release(subsection)
1350 
1351  CALL create_adiabatic_section(subsection)
1352  CALL section_add_subsection(section, subsection)
1353  CALL section_release(subsection)
1354 
1355  CALL create_xc_potential_section(subsection)
1356  CALL section_add_subsection(section, subsection)
1357  CALL section_release(subsection)
1358 
1359  CALL create_xc_kernel_section(subsection)
1360  CALL section_add_subsection(section, subsection)
1361  CALL section_release(subsection)
1362 
1363  CALL create_hfx_kernel_section(subsection)
1364  CALL section_add_subsection(section, subsection)
1365  CALL section_release(subsection)
1366 
1367  CALL create_vdw_potential_section(subsection)
1368  CALL section_add_subsection(section, subsection)
1369  CALL section_release(subsection)
1370 
1371  CALL create_gcp_potential_section(subsection)
1372  CALL section_add_subsection(section, subsection)
1373  CALL section_release(subsection)
1374 
1375  END SUBROUTINE create_xc_section
1376 
1377 ! **************************************************************************************************
1378 !> \brief creates the section for adiabatic hybrid functionals
1379 !> \param section ...
1380 !> \author Manuel Guidon
1381 ! **************************************************************************************************
1382  SUBROUTINE create_adiabatic_section(section)
1383  TYPE(section_type), POINTER :: section
1384 
1385  TYPE(keyword_type), POINTER :: keyword
1386 
1387  cpassert(.NOT. ASSOCIATED(section))
1388  CALL section_create(section, __location__, name="ADIABATIC_RESCALING", &
1389  description="Parameters for self interaction corrected hybrid functionals", &
1390  n_keywords=0, n_subsections=0, repeats=.false.)
1391  NULLIFY (keyword)
1392  CALL keyword_create( &
1393  keyword, __location__, &
1394  name="FUNCTIONAL_TYPE", &
1395  description="Which Hybrid functional should be used. "// &
1396  "(Has to be consistent with the definitions in XC and HF).", &
1397  usage="FUNCTIONAL_TYPE MCY3", &
1398  enum_c_vals=s2a("MCY3"), &
1399  enum_i_vals=(/do_adiabatic_hybrid_mcy3/), &
1400  enum_desc=s2a("Use MCY3 hybrid functional"), &
1401  default_i_val=do_adiabatic_hybrid_mcy3)
1402  CALL section_add_keyword(section, keyword)
1403  CALL keyword_release(keyword)
1404 
1405  NULLIFY (keyword)
1406  CALL keyword_create( &
1407  keyword, __location__, &
1408  name="LAMBDA", &
1409  description="The point to be used along the adiabatic curve (0 &lt; &lambda; &lt; 1)", &
1410  usage="LAMBDA 0.71", &
1411  default_r_val=0.71_dp)
1412  CALL section_add_keyword(section, keyword)
1413  CALL keyword_release(keyword)
1414 
1415  NULLIFY (keyword)
1416  CALL keyword_create( &
1417  keyword, __location__, &
1418  name="OMEGA", &
1419  description="Long-range parameter", &
1420  usage="OMEGA 0.2", &
1421  default_r_val=0.2_dp)
1422  CALL section_add_keyword(section, keyword)
1423  CALL keyword_release(keyword)
1424 
1425  NULLIFY (keyword)
1426  CALL keyword_create( &
1427  keyword, __location__, &
1428  name="FUNCTIONAL_MODEL", &
1429  description="Which model for the coupling constant integration should be used. ", &
1430  usage="FUNCTIONAL_MODEL PADE", &
1431  enum_c_vals=s2a("PADE"), &
1432  enum_i_vals=(/do_adiabatic_model_pade/), &
1433  enum_desc=s2a("Use pade model: W(lambda)=a+(b*lambda)/(1+c*lambda)"), &
1434  default_i_val=do_adiabatic_model_pade)
1435  CALL section_add_keyword(section, keyword)
1436  CALL keyword_release(keyword)
1437  END SUBROUTINE create_adiabatic_section
1438 
1439 END MODULE input_cp2k_xc
collects all references to literature in CP2K as new algorithms / method are included from literature...
Definition: bibliography.F:28
integer, save, public goedecker1996
Definition: bibliography.F:43
integer, save, public perdew1996
Definition: bibliography.F:43
integer, save, public proynov2007
Definition: bibliography.F:43
integer, save, public heyd2004
Definition: bibliography.F:43
integer, save, public wellendorff2012
Definition: bibliography.F:43
integer, save, public grimme2006
Definition: bibliography.F:43
integer, save, public becke1997
Definition: bibliography.F:43
integer, save, public perdew2008
Definition: bibliography.F:43
integer, save, public vosko1980
Definition: bibliography.F:43
integer, save, public beckeroussel1989
Definition: bibliography.F:43
integer, save, public perdew1981
Definition: bibliography.F:43
integer, save, public tao2003
Definition: bibliography.F:43
integer, save, public tran2013
Definition: bibliography.F:43
integer, save, public ortiz1994
Definition: bibliography.F:43
integer, save, public lee1988
Definition: bibliography.F:43
integer, save, public grimme2011
Definition: bibliography.F:43
integer, save, public kruse2012
Definition: bibliography.F:43
integer, save, public grimme2010
Definition: bibliography.F:43
integer, save, public becke1988
Definition: bibliography.F:43
integer, save, public zhang1998
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
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 xc_funct_tpss
integer, parameter, public xc_funct_bp
integer, parameter, public xc_funct_olyp
integer, parameter, public vdw_nl_rvv10
integer, parameter, public xc_vdw_fun_none
integer, parameter, public xc_funct_pbe
integer, parameter, public fxc_funct_pade
integer, parameter, public fxc_funct_gga
integer, parameter, public vdw_pairpot_dftd3
integer, parameter, public xc_funct_no_shortcut
integer, parameter, public do_adiabatic_hybrid_mcy3
integer, parameter, public xc_vdw_fun_nonloc
integer, parameter, public xc_funct_pbe0
integer, parameter, public fxc_none
integer, parameter, public xc_funct_beefvdw
integer, parameter, public xc_funct_pade
integer, parameter, public xc_funct_blyp
integer, parameter, public vdw_nl_drsll
integer, parameter, public xc_pot_energy_xc_functional
integer, parameter, public xc_pot_energy_none
integer, parameter, public do_adiabatic_model_pade
integer, parameter, public xc_pot_energy_sum_eigenvalues
integer, parameter, public vdw_nl_lmkll
integer, parameter, public gaussian
integer, parameter, public vdw_pairpot_dftd2
integer, parameter, public fxc_funct_lda
integer, parameter, public xc_vdw_fun_pairpot
integer, parameter, public xc_funct_b3lyp
integer, parameter, public xc_none
integer, parameter, public vdw_pairpot_dftd3bj
integer, parameter, public xc_funct_hcth120
integer, parameter, public slater
function that builds the hartree fock exchange section of the input
subroutine, public create_hfx_section(section)
creates the input section for the hf part
input section for MP2
subroutine, public create_mp2_section(section)
creates the input section for the mp2 part
function that build the xc section of the input
Definition: input_cp2k_xc.F:14
subroutine, public create_xc_section(section)
creates the input section for the xc part
subroutine, public create_xc_fun_section(section)
creates the structure of the section needed to select the xc functional
Definition: input_cp2k_xc.F:73
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 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.
input constants for xc
integer, parameter, public xc_deriv_spline2_smooth
integer, parameter, public xc_rho_spline2_smooth
integer, parameter, public c_pw92
integer, parameter, public ke_ol1
integer, parameter, public xc_deriv_collocate
integer, parameter, public ke_ol2
integer, parameter, public xc_rho_spline3_smooth
integer, parameter, public xc_deriv_nn10_smooth
integer, parameter, public xc_pbe_orig
integer, parameter, public xc_deriv_pw
integer, parameter, public xc_pbe_rev
integer, parameter, public xgga_opt
integer, parameter, public xc_b97_mardirossian
integer, parameter, public xc_b97_orig
integer, parameter, public do_vwn5
integer, parameter, public xgga_revpbe
integer, parameter, public ke_pw91
integer, parameter, public ke_pbe
integer, parameter, public xc_default_f_routine
integer, parameter, public xgga_pw86
integer, parameter, public c_pz
integer, parameter, public c_pw92vmc
integer, parameter, public xc_deriv_spline2
integer, parameter, public pz_orig
integer, parameter, public xc_rho_nn10
integer, parameter, public ke_pw86
integer, parameter, public xgga_pw91
integer, parameter, public xc_deriv_nn50_smooth
integer, parameter, public xc_b97_grimme
integer, parameter, public xc_deriv_spline3
integer, parameter, public c_pzvmc
integer, parameter, public xc_pbe_sol
integer, parameter, public xc_rho_nn50
integer, parameter, public ke_lc
integer, parameter, public xgga_ev93
integer, parameter, public xc_test_lsd_f_routine
integer, parameter, public xalpha
integer, parameter, public ke_llp
integer, parameter, public xc_deriv_spline3_smooth
integer, parameter, public xc_b97_3c
integer, parameter, public xc_debug_new_routine
integer, parameter, public ke_t92
integer, parameter, public xgga_pbex
integer, parameter, public c_pw92dmc
integer, parameter, public do_vwn3
integer, parameter, public xgga_b88x
integer, parameter, public c_pzdmc
integer, parameter, public xc_rho_no_smooth
calculates a functional from libxc and its derivatives
Definition: xc_libxc.F:28
subroutine, public libxc_add_sections(section)
...
Definition: xc_libxc.F:206