Processing math: 20%
 (git:ed6f26b)
All Data Structures Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros
input_cp2k_mp2.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief input section for MP2
10!> \par History
11!> 05.2011 created
12!> \author MDB
13! **************************************************************************************************
15 USE bibliography, ONLY: &
26 USE cp_units, ONLY: cp_unit_to_cp2k
27 USE input_constants, ONLY: &
53
54 USE input_val_types, ONLY: char_t, &
55 integer_t, &
56 logical_t, &
57 real_t
58 USE kinds, ONLY: dp
59 USE string_utilities, ONLY: newline, &
60 s2a
61#include "./base/base_uses.f90"
62
63 IMPLICIT NONE
64 PRIVATE
65
66 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_mp2'
67
68 PUBLIC :: create_mp2_section
69
70CONTAINS
71
72! **************************************************************************************************
73!> \brief creates the input section for the mp2 part
74!> \param section the section to create
75!> \author MDB
76! **************************************************************************************************
77 SUBROUTINE create_mp2_section(section)
78 TYPE(section_type), POINTER :: section
79
80 TYPE(keyword_type), POINTER :: keyword
81 TYPE(section_type), POINTER :: print_key, subsection
82
83 cpassert(.NOT. ASSOCIATED(section))
84 CALL section_create(section, __location__, name="WF_CORRELATION", &
85 description="Sets up the wavefunction-based correlation methods as MP2, "// &
86 "RI-MP2, RI-SOS-MP2, RI-RPA and GW (inside RI-RPA). ", &
87 n_keywords=4, n_subsections=7, repeats=.true., &
91
92 NULLIFY (keyword, subsection)
93
94 CALL keyword_create( &
95 keyword, __location__, &
96 name="MEMORY", &
97 description="Maximum allowed total memory usage during MP2 methods [MiB].", &
98 usage="MEMORY 1500 ", &
99 default_r_val=1.024e+3_dp)
100 CALL section_add_keyword(section, keyword)
101 CALL keyword_release(keyword)
102
103 CALL keyword_create( &
104 keyword, __location__, &
105 name="E_GAP", &
106 description="Gap energy for integration grids in Hartree. Defaults to -1.0 (automatic determination). "// &
107 "Recommended to set if several RPA or SOS-MP2 gradient calculations are requested or to be restarted. "// &
108 "In this way, differences of integration grids across different runs are removed as CP2K "// &
109 "does not include derivatives thereof.", &
110 usage="E_GAP 0.5", &
111 default_r_val=-1.0_dp)
112 CALL section_add_keyword(section, keyword)
113 CALL keyword_release(keyword)
114
115 CALL keyword_create( &
116 keyword, __location__, &
117 name="E_RANGE", &
118 description="Energy range (ratio of largest and smallest) energy difference "// &
119 "of unoccupied and occupied orbitals for integration grids. Defaults to 0.0 (automatic determination). "// &
120 "Recommended to set if several RPA or SOS-MP2 gradient calculations are requested or to be restarted. "// &
121 "In this way, differences of integration grids across different runs are removed as CP2K "// &
122 "does not include derivatives thereof.", &
123 usage="E_RANGE 10.0", &
124 default_r_val=-1.0_dp)
125 CALL section_add_keyword(section, keyword)
126 CALL keyword_release(keyword)
127
128 CALL keyword_create( &
129 keyword, __location__, &
130 name="SCALE_S", &
131 description="Scaling factor of the singlet energy component (opposite spin, OS) of the "// &
132 "MP2, RI-MP2 and SOS-MP2 correlation energy. ", &
133 usage="SCALE_S 1.0", &
134 default_r_val=1.0_dp)
135 CALL section_add_keyword(section, keyword)
136 CALL keyword_release(keyword)
137
138 CALL keyword_create( &
139 keyword, __location__, &
140 name="SCALE_T", &
141 description="Scaling factor of the triplet energy component (same spin, SS) of the MP2 "// &
142 "and RI-MP2 correlation energy.", &
143 usage="SCALE_T 1.0", &
144 default_r_val=1.0_dp)
145 CALL section_add_keyword(section, keyword)
146 CALL keyword_release(keyword)
147
148 CALL keyword_create( &
149 keyword, __location__, &
150 name="GROUP_SIZE", &
151 variants=(/"NUMBER_PROC"/), &
152 description="Group size used in the computation of GPW and MME integrals and the MP2 correlation energy. "// &
153 "The group size must be a divisor of the total number of MPI ranks. "// &
154 "A smaller group size (for example the number of MPI ranks per node) "// &
155 "accelerates the computation of integrals but a too large group size increases communication costs. "// &
156 "A too small group size may lead to out of memory.", &
157 usage="GROUP_SIZE 2", &
158 default_i_val=1)
159 CALL section_add_keyword(section, keyword)
160 CALL keyword_release(keyword)
161
162 NULLIFY (subsection)
163 CALL create_mp2_details_section(subsection)
164 CALL section_add_subsection(section, subsection)
165 CALL section_release(subsection)
166
167 CALL create_ri_mp2(subsection)
168 CALL section_add_subsection(section, subsection)
169 CALL section_release(subsection)
170
171 CALL create_ri_rpa(subsection)
172 CALL section_add_subsection(section, subsection)
173 CALL section_release(subsection)
174
175 CALL create_ri_laplace(subsection)
176 CALL section_add_subsection(section, subsection)
177 CALL section_release(subsection)
178
179 ! here we generate an imag. time subsection to use with RPA or Laplace-SOS-MP2
180 CALL create_low_scaling(subsection)
181 CALL section_add_subsection(section, subsection)
182 CALL section_release(subsection)
183
184 CALL create_ri_section(subsection)
185 CALL section_add_subsection(section, subsection)
186 CALL section_release(subsection)
187
188 CALL create_integrals_section(subsection)
189 CALL section_add_subsection(section, subsection)
190 CALL section_release(subsection)
191
192 CALL create_canonical_gradients(subsection)
193 CALL section_add_subsection(section, subsection)
194 CALL section_release(subsection)
195
196 NULLIFY (print_key)
197 CALL cp_print_key_section_create(print_key, __location__, "PRINT", &
198 description="Controls the printing basic info about WFC methods", &
199 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
200 CALL section_add_subsection(section, print_key)
201 CALL section_release(print_key)
202
203 END SUBROUTINE create_mp2_section
204
205! **************************************************************************************************
206!> \brief ...
207!> \param section ...
208! **************************************************************************************************
209 SUBROUTINE create_mp2_details_section(section)
210 TYPE(section_type), POINTER :: section
211
212 TYPE(keyword_type), POINTER :: keyword
213
214 cpassert(.NOT. ASSOCIATED(section))
215 CALL section_create(section, __location__, name="MP2", &
216 description="Parameters influencing MP2 (non-RI).", &
217 n_keywords=3, n_subsections=0, repeats=.false.)
218
219 NULLIFY (keyword)
220 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
221 description="Activates MP2 calculations.", &
222 usage="&MP2 .TRUE.", &
223 default_l_val=.false., lone_keyword_l_val=.true.)
224 CALL section_add_keyword(section, keyword)
225 CALL keyword_release(keyword)
226
227 CALL keyword_create( &
228 keyword, __location__, &
229 name="METHOD", &
230 citations=(/delben2012, delben2013/), &
231 description="Method that is used to compute the MP2 energy.", &
232 usage="METHOD MP2_GPW", &
233 enum_c_vals=s2a("NONE", "DIRECT_CANONICAL", "MP2_GPW"), &
235 enum_desc=s2a("Skip MP2 calculation.", &
236 "Use the direct mp2 canonical approach.", &
237 "Use the GPW approach to MP2."), &
238 default_i_val=mp2_method_direct)
239 CALL section_add_keyword(section, keyword)
240 CALL keyword_release(keyword)
241
242 CALL keyword_create( &
243 keyword, __location__, &
244 name="BIG_SEND", &
245 description="Influencing the direct canonical MP2 method: Send big "// &
246 "messages between processes (useful for >48 processors).", &
247 usage="BIG_SEND", &
248 default_l_val=.true., &
249 lone_keyword_l_val=.true.)
250 CALL section_add_keyword(section, keyword)
251 CALL keyword_release(keyword)
252
253 END SUBROUTINE create_mp2_details_section
254
255! **************************************************************************************************
256!> \brief ...
257!> \param section ...
258! **************************************************************************************************
259 SUBROUTINE create_ri_mp2(section)
260 TYPE(section_type), POINTER :: section
261
262 TYPE(keyword_type), POINTER :: keyword
263
264 cpassert(.NOT. ASSOCIATED(section))
265 CALL section_create(section, __location__, name="RI_MP2", &
266 description="Parameters influencing the RI-MP2 method. RI-MP2 supports gradients.", &
267 n_keywords=3, n_subsections=1, repeats=.false., &
268 citations=(/delben2013/))
269
270 NULLIFY (keyword)
271 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
272 description="Putting the &RI_MP2 section activates RI-MP2 calculation.", &
273 usage="&RI_MP2 .TRUE.", &
274 default_l_val=.false., lone_keyword_l_val=.true.)
275 CALL section_add_keyword(section, keyword)
276 CALL keyword_release(keyword)
277
278 CALL keyword_create(keyword, __location__, name="BLOCK_SIZE", &
279 variants=(/"MESSAGE_SIZE"/), &
280 description="Determines the blocking used for communication in RI-MP2. Larger BLOCK_SIZE "// &
281 "reduces communication but requires more memory. The default (-1) is automatic.", &
282 usage="BLOCK_SIZE 2", &
283 default_i_val=-1)
284 CALL section_add_keyword(section, keyword)
285 CALL keyword_release(keyword)
286
287 CALL keyword_create(keyword, __location__, name="NUMBER_INTEGRATION_GROUPS", &
288 description="Sets the number of integration groups of the communication scheme in RI-MP2. "// &
289 "Integrals will be replicated such that each integration group has all integrals available. "// &
290 "Must be a divisor of the number of subgroups (see GROUP_SIZE keyword in the WF_CORRELATION "// &
291 "section. Smaller groups reduce the communication costs but increase the memory developments. "// &
292 "If the provided value is non-positive or not a divisor of the number of subgroups, "// &
293 "the number of integration groups is determined automatically (default).", &
294 usage="NUMBER_INTEGRATION_GROUPS 2", &
295 default_i_val=-1)
296 CALL section_add_keyword(section, keyword)
297 CALL keyword_release(keyword)
298
299 CALL keyword_create( &
300 keyword, __location__, &
301 name="PRINT_DGEMM_INFO", &
302 description="Print details about all DGEMM calls.", &
303 lone_keyword_l_val=.true., &
304 default_l_val=.false.)
305 CALL section_add_keyword(section, keyword)
306 CALL keyword_release(keyword)
307
308 END SUBROUTINE create_ri_mp2
309
310! **************************************************************************************************
311!> \brief ...
312!> \param section ...
313! **************************************************************************************************
314 SUBROUTINE create_opt_ri_basis(section)
315 TYPE(section_type), POINTER :: section
316
317 TYPE(keyword_type), POINTER :: keyword
318
319 cpassert(.NOT. ASSOCIATED(section))
320 CALL section_create(section, __location__, name="OPT_RI_BASIS", &
321 description="Parameters influencing the optimization of the RI MP2 basis. "// &
322 "Only exponents of non-contracted auxiliary basis can be optimized. "// &
323 "An initial RI auxiliary basis has to be specified.", &
324 n_keywords=6, n_subsections=0, repeats=.false., &
325 citations=(/delben2013/))
326 NULLIFY (keyword)
327 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
328 description="Putting the &OPT_RI_BASIS section activates optimization of RI basis.", &
329 usage="&OPT_RI_BASIS .TRUE.", &
330 default_l_val=.false., lone_keyword_l_val=.true.)
331 CALL section_add_keyword(section, keyword)
332 CALL keyword_release(keyword)
333
334 CALL keyword_create(keyword, __location__, name="DELTA_I_REL", &
335 variants=(/"DI_REL"/), &
336 description="Target accuracy in the relative deviation of the amplitudes calculated with "// &
337 "and without RI approximation, (more details in Chem.Phys.Lett.294(1998)143).", &
338 usage="DELTA_I_REL 1.0E-6_dp", &
339 default_r_val=1.0e-6_dp)
340 CALL section_add_keyword(section, keyword)
341 CALL keyword_release(keyword)
342
343 CALL keyword_create(keyword, __location__, name="DELTA_RI", &
344 variants=(/"DRI"/), &
345 description="Target accuracy in the absolute difference between the RI-MP2 "// &
346 "and the exact MP2 energy, DRI=ABS(E_MP2-E_RI-MP2).", &
347 usage="DELTA_RI 1.0E-6_dp", &
348 default_r_val=5.0e-6_dp)
349 CALL section_add_keyword(section, keyword)
350 CALL keyword_release(keyword)
351
352 CALL keyword_create(keyword, __location__, name="EPS_DERIV", &
353 variants=(/"EPS_NUM_DERIV"/), &
354 description="The derivatives of the MP2 energy with respect to the "// &
355 "exponents of the basis are calculated numerically. "// &
356 "The change in the exponent a_i employed for the numerical evaluation "// &
357 "is defined as h_i=EPS_DERIV*a_i.", &
358 usage="EPS_DERIV 1.0E-3_dp", &
359 default_r_val=1.0e-3_dp)
360 CALL section_add_keyword(section, keyword)
361 CALL keyword_release(keyword)
362
363 CALL keyword_create(keyword, __location__, name="MAX_ITER", &
364 variants=(/"MAX_NUM_ITER"/), &
365 description="Specifies the maximum number of steps in the RI basis optimization.", &
366 usage="MAX_ITER 100", &
367 default_i_val=50)
368 CALL section_add_keyword(section, keyword)
369 CALL keyword_release(keyword)
370
371 CALL keyword_create(keyword, __location__, name="NUM_FUNC", &
372 description="Specifies the number of function, for each angular momentum (s, p, d ...), "// &
373 "employed in the automatically generated initial guess. "// &
374 "This will be effective only if RI_AUX_BASIS_SET in the KIND section is not specified.", &
375 usage="NUM_FUNC {number of s func.} {number of p func.} ...", &
376 n_var=-1, default_i_vals=(/-1/), type_of_var=integer_t)
377 CALL section_add_keyword(section, keyword)
378 CALL keyword_release(keyword)
379
380 CALL keyword_create(keyword, __location__, name="BASIS_SIZE", &
381 description="Specifies the size of the auxiliary basis set automatically "// &
382 "generated as initial guess. This will be effective only if RI_AUX_BASIS_SET "// &
383 "in the KIND section and NUM_FUNC are not specified.", &
384 usage="BASIS_SIZE (MEDIUM|LARGE|VERY_LARGE)", &
385 enum_c_vals=s2a("MEDIUM", "LARGE", "VERY_LARGE"), &
386 enum_i_vals=(/0, 1, 2/), &
387 default_i_val=0)
388 CALL section_add_keyword(section, keyword)
389 CALL keyword_release(keyword)
390
391 END SUBROUTINE create_opt_ri_basis
392
393! **************************************************************************************************
394!> \brief ...
395!> \param section ...
396! **************************************************************************************************
397 SUBROUTINE create_ri_laplace(section)
398 TYPE(section_type), POINTER :: section
399
400 TYPE(keyword_type), POINTER :: keyword
401
402 cpassert(.NOT. ASSOCIATED(section))
403 CALL section_create(section, __location__, name="RI_SOS_MP2", &
404 description="Parameters influencing the RI-SOS-MP2-Laplace method", &
405 n_keywords=3, n_subsections=1, repeats=.false., &
406 citations=(/delben2013/))
407
408 NULLIFY (keyword)
409 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
410 description="Putting the &RI_SOS_MP2 section activates RI-SOS-MP2 calculation.", &
411 usage="&RI_SOS_MP2 .TRUE.", &
412 default_l_val=.false., lone_keyword_l_val=.true.)
413 CALL section_add_keyword(section, keyword)
414 CALL keyword_release(keyword)
415
416 CALL keyword_create( &
417 keyword, __location__, name="QUADRATURE_POINTS", &
418 variants=(/"LAPLACE_NUM_QUAD_POINTS"/), &
419 description="Number of quadrature points for the numerical integration in the RI-SOS-MP2-Laplace method.", &
420 usage="QUADRATURE_POINTS 6", &
421 default_i_val=5)
422 CALL section_add_keyword(section, keyword)
423 CALL keyword_release(keyword)
424
425 CALL keyword_create( &
426 keyword, __location__, name="NUM_INTEG_GROUPS", &
427 description="Number of groups for the integration in the Laplace method. Each groups processes "// &
428 "the same amount of quadrature points. It must be a divisor of the number of quadrature points and "// &
429 "NUM_INTEG_GROUPS*GROUP_SIZE must be a divisor of the total number of processes. The default (-1) is automatic.", &
430 usage="NUM_INTEG_GROUPS 2", &
431 default_i_val=-1)
432 CALL section_add_keyword(section, keyword)
433 CALL keyword_release(keyword)
434
435 END SUBROUTINE create_ri_laplace
436
437! **************************************************************************************************
438!> \brief ...
439!> \param section ...
440! **************************************************************************************************
441 SUBROUTINE create_canonical_gradients(section)
442 TYPE(section_type), POINTER :: section
443
444 TYPE(keyword_type), POINTER :: keyword
445 TYPE(section_type), POINTER :: subsection
446
447 cpassert(.NOT. ASSOCIATED(section))
448 CALL section_create(section, __location__, name="CANONICAL_GRADIENTS", &
449 description="Parameters influencing gradient calculations of canonical RI methods. "// &
450 "Ignored if the IM_TIME section is set.", &
451 n_keywords=3, n_subsections=1, repeats=.false., &
452 citations=(/delben2015b, rybkin2016, stein2022, stein2024/))
453
454 NULLIFY (subsection, keyword)
455 CALL create_cphf(subsection)
456 CALL section_add_subsection(section, subsection)
457 CALL section_release(subsection)
458
459 CALL keyword_create(keyword, __location__, name="EPS_CANONICAL", &
460 description="Threshold under which a given ij or ab pair is considered to be degenerate and "// &
461 "its contribution to the density matrix is calculated directly. "// &
462 "Ignored in case of energy-only calculation.", &
463 usage="EPS_CANONICAL 1.0E-8", type_of_var=real_t, &
464 default_r_val=1.0e-7_dp)
465 CALL section_add_keyword(section, keyword)
466 CALL keyword_release(keyword)
467
468 CALL keyword_create( &
469 keyword, __location__, &
470 name="FREE_HFX_BUFFER", &
471 description="Free the buffer containing the 4 center integrals used in the Hartree-Fock exchange calculation. "// &
472 "Ignored for energy-only calculations. May fail.", &
473 usage="FREE_HFX_BUFFER", &
474 default_l_val=.false., &
475 lone_keyword_l_val=.true.)
476 CALL section_add_keyword(section, keyword)
477 CALL keyword_release(keyword)
478
479 CALL keyword_create( &
480 keyword, __location__, &
481 name="DOT_PRODUCT_BLKSIZE", &
482 description="Dot products for the calculation of the RPA/SOS-MP2 density matrices "// &
483 "are calculated in batches of the size given by this keyword. Larger block sizes "// &
484 "improve the performance but reduce the numerical accuracy. Recommended block sizes are multiples of the number of "// &
485 "doubles per cache line (usually 8). Ignored with MP2 gradients. Set it to -1 to prevent blocking.", &
486 default_i_val=-1)
487 CALL section_add_keyword(section, keyword)
488 CALL keyword_release(keyword)
489
490 CALL keyword_create( &
491 keyword, __location__, &
492 name="MAX_PARALLEL_COMM", &
493 description="Sets the maximum number of parallel communication steps of the non-blocking communication scheme. "// &
494 "The number of channels is determined from the available memory. If set to a value smaller than one, "// &
495 "CP2K will use all memory for communication. A value of one enforces the blocking communication scheme "// &
496 "increasing the communication costs.", &
497 default_i_val=2)
498 CALL section_add_keyword(section, keyword)
499 CALL keyword_release(keyword)
500
501 END SUBROUTINE create_canonical_gradients
502
503! **************************************************************************************************
504!> \brief ...
505!> \param section ...
506! **************************************************************************************************
507 SUBROUTINE create_ri_rpa(section)
508 TYPE(section_type), POINTER :: section
509
510 TYPE(keyword_type), POINTER :: keyword
511 TYPE(section_type), POINTER :: subsection
512
513 cpassert(.NOT. ASSOCIATED(section))
514 CALL section_create(section, __location__, name="RI_RPA", &
515 description="Parameters influencing RI-RPA and GW.", &
516 n_keywords=8, n_subsections=4, repeats=.false., &
517 citations=(/delben2013, delben2015/))
518
519 NULLIFY (keyword, subsection)
520 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
521 description="Putting the &RI_RPA section activates RI-RPA calculation.", &
522 usage="&RI_RPA .TRUE.", &
523 default_l_val=.false., lone_keyword_l_val=.true.)
524 CALL section_add_keyword(section, keyword)
525 CALL keyword_release(keyword)
526
527 CALL keyword_create( &
528 keyword, __location__, &
529 name="SIGMA_FUNCTIONAL", &
530 description="Determine parametrization for sigma-functional", &
531 usage="SIGMA_FUNCTIONAL PBE_S2", &
532 enum_c_vals=s2a("NONE", "PBE0_S1", "PBE0_S2", "PBE_S1", "PBE_S2"), &
534 enum_desc=s2a("No sigma functional calculation", &
535 "use parameters based on PBE0 with S1 set.", &
536 "use parameters based on PBE0 with S2 set.", &
537 "use parameters based on PBE with S1 set.", &
538 "use parameters based on PBE with S2 set." &
539 ), &
540 default_i_val=sigma_none)
541 CALL section_add_keyword(section, keyword)
542 CALL keyword_release(keyword)
543
544 CALL keyword_create(keyword, __location__, name="QUADRATURE_POINTS", &
545 variants=(/"RPA_NUM_QUAD_POINTS"/), &
546 description="Number of quadrature points for the numerical integration in the RI-RPA method.", &
547 usage="QUADRATURE_POINTS 60", &
548 default_i_val=40)
549 CALL section_add_keyword(section, keyword)
550 CALL keyword_release(keyword)
551
552 CALL keyword_create(keyword, __location__, name="NUM_INTEG_GROUPS", &
553 description="Number of groups for the integration in the Laplace method. Each groups processes "// &
554 "the same amount of quadrature points. It must be a divisor of the number of quadrature points and "// &
555 "NUM_INTEG_GROUPS*GROUP_SIZE must be a divisor of the total number of processes. "// &
556 "The default (-1) is automatic.", &
557 usage="NUM_INTEG_GROUPS 2", &
558 default_i_val=-1)
559 CALL section_add_keyword(section, keyword)
560 CALL keyword_release(keyword)
561
562 CALL keyword_create(keyword, __location__, &
563 name="MM_STYLE", &
564 description="Matrix multiplication style for the Q matrix.", &
565 usage="MM_STYLE GEMM", &
566 enum_c_vals=s2a("GEMM", "SYRK"), &
567 enum_i_vals=(/wfc_mm_style_gemm, wfc_mm_style_syrk/), &
568 enum_desc=s2a("Use pdgemm: more flops, maybe faster.", &
569 "Use pdysrk: fewer flops, maybe slower."), &
570 default_i_val=wfc_mm_style_gemm)
571 CALL section_add_keyword(section, keyword)
572 CALL keyword_release(keyword)
573
574 CALL keyword_create( &
575 keyword, __location__, &
576 name="MINIMAX_QUADRATURE", &
577 variants=(/"MINIMAX"/), &
578 description="Use the Minimax quadrature scheme for performing the numerical integration. "// &
579 "Maximum number of quadrature point limited to 20.", &
580 usage="MINIMAX_QUADRATURE", &
581 default_l_val=.false., &
582 lone_keyword_l_val=.true.)
583 CALL section_add_keyword(section, keyword)
584 CALL keyword_release(keyword)
585
586 CALL keyword_create( &
587 keyword, __location__, &
588 name="RSE", &
589 variants=(/"SE"/), &
590 description="Decide whether to add singles correction.", &
591 usage="RSE", &
592 default_l_val=.false., &
593 lone_keyword_l_val=.true.)
594 CALL section_add_keyword(section, keyword)
595 CALL keyword_release(keyword)
596
597 CALL keyword_create( &
598 keyword, __location__, &
599 name="ADMM", &
600 description="Decide whether to perform ADMM in the exact exchange calc. for RPA and/or GW. "// &
601 "The ADMM XC correction is governed by the AUXILIARY_DENSITY_MATRIX_METHOD section in &DFT. "// &
602 "In most cases, the Hartree-Fock exchange is not too expensive and there is no need for ADMM, "// &
603 "ADMM can however provide significant speedup and memory savings in case of diffuse basis sets. "// &
604 "If it is a GW bandgap calculations, RI_SIGMA_X can also be used. ", &
605 usage="ADMM", &
606 default_l_val=.false., &
607 lone_keyword_l_val=.true.)
608 CALL section_add_keyword(section, keyword)
609 CALL keyword_release(keyword)
610
611 CALL keyword_create( &
612 keyword, __location__, &
613 name="SCALE_RPA", &
614 description="Scales RPA energy contributions (RPA, exchange correction).", &
615 usage="SCALE_RPA 1.0", &
616 default_r_val=1.0_dp)
617 CALL section_add_keyword(section, keyword)
618 CALL keyword_release(keyword)
619
620 CALL keyword_create( &
621 keyword, __location__, &
622 name="PRINT_DGEMM_INFO", &
623 description="Print details about all DGEMM calls.", &
624 lone_keyword_l_val=.true., &
625 default_l_val=.false.)
626 CALL section_add_keyword(section, keyword)
627 CALL keyword_release(keyword)
628
629 ! here we generate a hfx subsection to use in the case EXX has to be computed after RPA
630 CALL create_hfx_section(subsection)
631 CALL section_add_subsection(section, subsection)
632 CALL section_release(subsection)
633
634 ! here we generate a G0W0 subsection to use if G0W0 is desired
635 CALL create_ri_g0w0(subsection)
636 CALL section_add_subsection(section, subsection)
637 CALL section_release(subsection)
638
639 ! here we the RPA exchange section
640 CALL create_rpa_exchange(subsection)
641 CALL section_add_subsection(section, subsection)
642 CALL section_release(subsection)
643
644 END SUBROUTINE create_ri_rpa
645
646! **************************************************************************************************
647!> \brief ...
648!> \param section ...
649! **************************************************************************************************
650 SUBROUTINE create_rpa_exchange(section)
651 TYPE(section_type), POINTER :: section
652
653 TYPE(keyword_type), POINTER :: keyword
654
655 cpassert(.NOT. ASSOCIATED(section))
656 CALL section_create(section, __location__, name="EXCHANGE_CORRECTION", &
657 description="Parameters influencing exchange corrections to RPA. No gradients available.", &
658 n_keywords=3, n_subsections=1, repeats=.false.)
659
660 NULLIFY (keyword)
661 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
662 description="Choose the kind of exchange correction.", &
663 usage="&EXCHANGE_CORRECTION AXK", &
664 enum_c_vals=s2a("NONE", "AXK", "SOSEX"), &
666 enum_desc=s2a("Apply no exchange correction.", &
667 "Apply Approximate eXchange Kernel (AXK) correction.", &
668 "Apply Second Order Screened eXchange (SOSEX) correction."), &
669 default_i_val=rpa_exchange_none)
670 CALL section_add_keyword(section, keyword)
671 CALL keyword_release(keyword)
672
673 CALL keyword_create( &
674 keyword, __location__, &
675 name="BLOCK_SIZE", &
676 description="Choose the block size of the contraction step. Larger block sizes improve performance but "// &
677 "require more memory (quadratically!, number of stored elements: $o^2\cdot N_B^2$). "// &
678 "Nonpositive numbers turn off blocking.", &
679 usage="BLOCK_SIZE 1", &
680 default_i_val=1)
681 CALL section_add_keyword(section, keyword)
682 CALL keyword_release(keyword)
683
684 CALL keyword_create( &
685 keyword, __location__, &
686 name="USE_HFX_IMPLEMENTATION", &
687 description="Use a HF-based implementation with RI_RPA%HF section. Recommended for large systems.", &
688 usage="USE_HFX_IMPLEMENTATION T", &
689 default_l_val=.false., lone_keyword_l_val=.true.)
690 CALL section_add_keyword(section, keyword)
691 CALL keyword_release(keyword)
692
693 END SUBROUTINE create_rpa_exchange
694
695! **************************************************************************************************
696!> \brief ...
697!> \param section ...
698! **************************************************************************************************
699 SUBROUTINE create_ri_g0w0(section)
700 TYPE(section_type), POINTER :: section
701
702 TYPE(keyword_type), POINTER :: keyword
703 TYPE(section_type), POINTER :: subsection
704
705 cpassert(.NOT. ASSOCIATED(section))
706 CALL section_create(section, __location__, name="GW", &
707 description="Parameters influencing GW calculations on molecules, "// &
708 "see also 'Electronic band structure from GW', "// &
709 "https://manual.cp2k.org/trunk/methods/properties/bandstructure_gw.html.", &
710 n_keywords=24, n_subsections=1, repeats=.false.)
711
712 NULLIFY (keyword, subsection)
713
714 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
715 description="Activates GW calculations.", &
716 usage="&GW .TRUE.", &
717 default_l_val=.false., lone_keyword_l_val=.true.)
718 CALL section_add_keyword(section, keyword)
719 CALL keyword_release(keyword)
720
721 CALL keyword_create(keyword, __location__, name="SELF_CONSISTENCY", &
722 description="Decide the level of self-consistency of eigenvalues "// &
723 "(= quasiparticle energies = single-electron energies) in GW. "// &
724 "Updates of Kohn-Sham orbitals (for example qsGW) are not implemented. "// &
725 "For details which type of eigenvalue self-consistency might be good, "// &
726 "please consult Golze, Dvorak, Rinke, Front. Chem. 2019.", &
727 usage="SELF_CONSISTENCY evGW0", &
728 enum_c_vals=s2a("G0W0", "evGW0", "evGW"), &
729 enum_i_vals=(/g0w0, evgw0, evgw/), &
730 enum_desc=s2a("Use DFT eigenvalues; not update.", &
731 "Update DFT eigenvalues in G, not in W.", &
732 "Update DFT eigenvalues in G and W."), &
733 default_i_val=g0w0)
734 CALL section_add_keyword(section, keyword)
735 CALL keyword_release(keyword)
736
737 CALL keyword_create(keyword, __location__, name="CORR_MOS_OCC", &
738 variants=(/"CORR_OCC"/), &
739 description="Number of occupied MOs whose energies are corrected in GW. "// &
740 "Counting beginning from HOMO, e.g. 3 corrected occ. MOs correspond "// &
741 "to correction of HOMO, HOMO-1 and HOMO-2. Numerical effort and "// &
742 "storage of RI-G0W0 increase linearly with this number. In case you "// &
743 "want to correct all occ. MOs, insert either a negative number or "// &
744 "a number larger than the number of occ. MOs. Invoking CORR_MOS_OCC -2 "// &
745 "together with a BSE cutoff, sets a sufficiently large CORR_MOS_OCC "// &
746 "for the given BSE cutoff deduced from DFT eigenvalues.", &
747 usage="CORR_OCC 3", &
748 default_i_val=10)
749 CALL section_add_keyword(section, keyword)
750 CALL keyword_release(keyword)
751
752 CALL keyword_create(keyword, __location__, name="CORR_MOS_VIRT", &
753 variants=(/"CORR_VIRT"/), &
754 description="Number of virtual MOs whose energies are corrected by GW. "// &
755 "Counting beginning from LUMO, e.g. 3 corrected occ. MOs correspond "// &
756 "to correction of LUMO, LUMO+1 and LUMO+2. Numerical effort and "// &
757 "storage of RI-G0W0 increase linearly with this number. In case you "// &
758 "want to correct all virt. MOs, insert either a negative number or "// &
759 "a number larger than the number of virt. MOs. Invoking CORR_MOS_VIRT -2 "// &
760 "together with a BSE cutoff, sets a sufficiently large CORR_MOS_VIRT "// &
761 "for the given BSE cutoff deduced from DFT eigenvalues.", &
762 usage="CORR_VIRT 3", &
763 default_i_val=10)
764 CALL section_add_keyword(section, keyword)
765 CALL keyword_release(keyword)
766
767 CALL keyword_create(keyword, __location__, name="NUMB_POLES", &
768 description="Number of poles for the fitting. Usually, two poles are sufficient. ", &
769 usage="NUMB_POLES 2", &
770 default_i_val=2)
771 CALL section_add_keyword(section, keyword)
772 CALL keyword_release(keyword)
773
774 CALL keyword_create(keyword, __location__, name="OMEGA_MAX_FIT", &
775 description="Determines fitting range for the self-energy on the imaginary axis: "// &
776 "[0, OMEGA_MAX_FIT] for virt orbitals, [-OMEGA_MAX_FIT,0] for occ orbitals. "// &
777 "Unit: Hartree. Default: 0.734996 H = 20 eV. ", &
778 usage="OMEGA_MAX_FIT 0.5", &
779 default_r_val=0.734996_dp)
780 CALL section_add_keyword(section, keyword)
781 CALL keyword_release(keyword)
782
783 CALL keyword_create(keyword, __location__, name="CROSSING_SEARCH", &
784 description="Determines, how the self_energy is evaluated on the real axis.", &
785 usage="CROSSING_SEARCH Z_SHOT", &
786 enum_c_vals=s2a("Z_SHOT", "NEWTON", "BISECTION"), &
787 enum_i_vals=(/ri_rpa_g0w0_crossing_z_shot, &
789 enum_desc=s2a("Calculate the derivative of Sigma and out of it Z. Then extrapolate using Z.", &
790 "Make a Newton-Raphson fix point iteration.", &
791 "Make a bisection fix point iteration."), &
792 default_i_val=ri_rpa_g0w0_crossing_newton)
793 CALL section_add_keyword(section, keyword)
794 CALL keyword_release(keyword)
795
796 CALL keyword_create(keyword, __location__, name="FERMI_LEVEL_OFFSET", &
797 description="Fermi level for occ. orbitals: e_HOMO + FERMI_LEVEL_OFFSET; "// &
798 "Fermi level for virt. orbitals: e_LUMO - FERMI_LEVEL_OFFSET. "// &
799 "In case e_homo + FERMI_LEVEL_OFFSET < e_lumo - FERMI_LEVEL_OFFSET, "// &
800 "we set Fermi level = (e_HOMO+e_LUMO)/2. For cubic-scaling GW, the Fermi level "// &
801 "is always equal to (e_HOMO+e_LUMO)/2 regardless of FERMI_LEVEL_OFFSET.", &
802 usage="FERMI_LEVEL_OFFSET 1.0E-2", &
803 default_r_val=2.0e-2_dp)
804 CALL section_add_keyword(section, keyword)
805 CALL keyword_release(keyword)
806
807 CALL keyword_create(keyword, __location__, name="HEDIN_SHIFT", &
808 description="If true, use Hedin's shift in G0W0, evGW and evGW0 "// &
809 "(aka scGW0). Details see in Li et al. JCTC 18, 7570 "// &
810 "(2022), Figure 1. G0W0 with Hedin's shift should give "// &
811 "similar GW eigenvalues as evGW0; at a lower "// &
812 "computational cost.", &
813 usage="HEDIN_SHIFT", &
814 default_l_val=.false., &
815 lone_keyword_l_val=.true.)
816 CALL section_add_keyword(section, keyword)
817 CALL keyword_release(keyword)
818
819 CALL keyword_create(keyword, __location__, name="EV_GW_ITER", &
820 description="Maximum number of iterations for eigenvalue "// &
821 "self-consistency cycle. The computational effort of GW scales "// &
822 "linearly with this number. In case of choosing "// &
823 "GW_SELF_CONSISTENCY EVGW, the code sets EV_GW_ITER 10.", &
824 usage="EV_GW_ITER 3", &
825 default_i_val=1)
826 CALL section_add_keyword(section, keyword)
827 CALL keyword_release(keyword)
828
829 CALL keyword_create(keyword, __location__, name="SC_GW0_ITER", &
830 description="Maximum number of iterations for GW0 "// &
831 "self-consistency cycle. The computational effort "// &
832 "of GW is not much affected by the number of scGW0 cycles. "// &
833 "In case of choosing "// &
834 "GW_SELF_CONSISTENCY EVGW0, the code sets SC_GW0_ITER 10.", &
835 usage="SC_GW0_ITER 3", &
836 default_i_val=1)
837 CALL section_add_keyword(section, keyword)
838 CALL keyword_release(keyword)
839
840 CALL keyword_create(keyword, __location__, name="EPS_ITER", &
841 description="Target accuracy for the eigenvalue self-consistency. "// &
842 "If the G0W0 HOMO-LUMO gap differs by less than the "// &
843 "target accuracy during the iteration, the eigenvalue "// &
844 "self-consistency cycle stops. Unit: Hartree.", &
845 usage="EPS_ITER 0.00005", &
846 default_r_val=cp_unit_to_cp2k(value=0.00136_dp, unit_str="eV"), &
847 unit_str="eV")
848
849 CALL section_add_keyword(section, keyword)
850 CALL keyword_release(keyword)
851
852 CALL keyword_create(keyword, __location__, name="PRINT_EXX", &
853 description="Print exchange self-energy minus exchange correlation potential for Gamma-only "// &
854 "calculation (PRINT). For a GW calculation with k-points we use this output as "// &
855 "exchange self-energy (READ). This is a temporary solution because the hybrid MPI/OMP "// &
856 "parallelization in the HFX by Manuel Guidon conflicts with the parallelization in "// &
857 "low-scaling GW k-points which is most efficient with maximum number of MPI tasks and "// &
858 "minimum number of OMP threads. For HFX by M. Guidon, the density matrix is "// &
859 "fully replicated on every MPI rank which necessitates a high number of OMP threads per MPI "// &
860 "rank for large systems to prevent out of memory. "// &
861 "Such a high number of OMP threads would slow down the GW calculation "// &
862 "severely. Therefore, it was decided to temporarily divide the GW k-point calculation in a "// &
863 "Gamma-only HF calculation with high number of OMP threads to prevent out of memory and "// &
864 "a GW k-point calculation with 1 OMP thread per MPI rank reading the previousHF output.", &
865 usage="PRINT_EXX TRUE", &
866 enum_c_vals=s2a("TRUE", "FALSE", "READ", "SKIP_FOR_REGTEST"), &
868 enum_desc=s2a("Please, put TRUE for Gamma only calculation to get the exchange self-energy. "// &
869 "If 'SIGMA_X' and the corresponding values for the exchange-energy are written, "// &
870 "the writing has been successful", &
871 "FALSE is needed if you want to do nothing here.", &
872 "Please, put READ for the k-point GW calculation to read the exact exchange. "// &
873 "You have to provide an output file including the exact exchange. This file "// &
874 "has to be named 'exx.dat'.", &
875 "SKIP_FOR_REGTEST is only used for the GW k-point regtest where no exchange "// &
876 "self-energy is computed."), &
877 default_i_val=gw_no_print_exx)
878 CALL section_add_keyword(section, keyword)
879 CALL keyword_release(keyword)
880
881 CALL keyword_create(keyword, __location__, name="PRINT_SELF_ENERGY", &
882 description="If true, print the self-energy for all levels for real energy "// &
883 "together with the straight line to see the quasiparticle energy as intersection. "// &
884 "In addition, prints the self-energy for imaginary frequencies together with the Pade fit.", &
885 usage="PRINT_SELF_ENERGY", &
886 default_l_val=.false., &
887 lone_keyword_l_val=.true.)
888 CALL section_add_keyword(section, keyword)
889 CALL keyword_release(keyword)
890
891 CALL keyword_create(keyword, __location__, name="RI_SIGMA_X", &
892 description="If true, the exchange self-energy is calculated approximatively with RI. "// &
893 "If false, the Hartree-Fock implementation in CP2K is used.", &
894 usage="RI_SIGMA_X", &
895 default_l_val=.true., &
896 lone_keyword_l_val=.true.)
897 CALL section_add_keyword(section, keyword)
898 CALL keyword_release(keyword)
899
900 CALL keyword_create(keyword, __location__, name="IC_CORR_LIST", &
901 description="List of image charge correction from a previous calculation to be applied in G0W0 "// &
902 "or evGW. Keyword is active, if the first entry is positive (since IC corrections are positive "// &
903 "occupied MOs. The start corresponds to the first corrected GW level.", &
904 usage="IC_CORR_LIST <REAL> ... <REAL>", &
905 default_r_vals=(/-1.0_dp/), &
906 type_of_var=real_t, n_var=-1, unit_str="eV")
907 CALL section_add_keyword(section, keyword)
908 CALL keyword_release(keyword)
909
910 CALL keyword_create(keyword, __location__, name="IC_CORR_LIST_BETA", &
911 description="IC_CORR_LIST for beta spins in case of open shell calculation.", &
912 usage="IC_CORR_LIST_BETA <REAL> ... <REAL>", &
913 default_r_vals=(/-1.0_dp/), &
914 type_of_var=real_t, n_var=-1, unit_str="eV")
915 CALL section_add_keyword(section, keyword)
916 CALL keyword_release(keyword)
917
918 CALL keyword_create(keyword, __location__, name="PERIODIC_CORRECTION", &
919 description="If true, the periodic correction scheme is used employing k-points. "// &
920 "Method is not recommended to use, use instead PERIODIC_LOW_SCALING which much "// &
921 "more accurate than the periodic correction.", &
922 usage="PERIODIC_CORRECTION", &
923 default_l_val=.false., &
924 lone_keyword_l_val=.true.)
925 CALL section_add_keyword(section, keyword)
926 CALL keyword_release(keyword)
927
928 CALL keyword_create(keyword, __location__, name="IMAGE_CHARGE_MODEL", &
929 variants=(/"IC"/), &
930 description="If true, an image charge model is applied to mimic the renormalization of "// &
931 "electronic levels of a molecule at a metallic surface. For this calculation, the molecule "// &
932 "has to be reflected on the desired xy image plane. The coordinates of the reflected molecule "// &
933 "have to be added to the coord file as ghost atoms. For the ghost atoms, identical basis sets "// &
934 "the normal atoms have to be used.", &
935 usage="IC TRUE", &
936 default_l_val=.false., &
937 lone_keyword_l_val=.true.)
938 CALL section_add_keyword(section, keyword)
939 CALL keyword_release(keyword)
940
941 CALL keyword_create(keyword, __location__, name="ANALYTIC_CONTINUATION", &
942 description="Defines which type of analytic continuation for the self energy is used", &
943 usage="ANALYTIC_CONTINUATION", &
944 enum_c_vals=s2a("TWO_POLE", "PADE"), &
945 enum_i_vals=(/gw_two_pole_model, gw_pade_approx/), &
946 enum_desc=s2a("Use 'two-pole' model.", &
947 "Use Pade approximation."), &
948 default_i_val=gw_pade_approx)
949 CALL section_add_keyword(section, keyword)
950 CALL keyword_release(keyword)
951
952 CALL keyword_create(keyword, __location__, name="NPARAM_PADE", &
953 description="Number of parameters for the Pade approximation "// &
954 "when using the latter for the analytic continuation of the "// &
955 "self energy. 16 parameters (corresponding to 8 poles) are "// &
956 "are recommended.", &
957 usage="NPARAM_PADE 16", &
958 default_i_val=16)
959 CALL section_add_keyword(section, keyword)
960 CALL keyword_release(keyword)
961
962 CALL keyword_create(keyword, __location__, name="GAMMA_ONLY_SIGMA", &
963 variants=(/"GAMMA"/), &
964 description="If true, the correlation self-energy is only computed at the Gamma point. "// &
965 "The Gamma point itself is obtained by averaging over all kpoints of the DFT mesh.", &
966 usage="GAMMA TRUE", &
967 default_l_val=.false., &
968 lone_keyword_l_val=.true.)
969 CALL section_add_keyword(section, keyword)
970 CALL keyword_release(keyword)
971
972 CALL keyword_create(keyword, __location__, name="UPDATE_XC_ENERGY", &
973 description="If true, the Hartree-Fock and RPA total energy are printed and the total energy "// &
974 "is corrected using exact exchange and the RPA correlation energy.", &
975 usage="UPDATE_XC_ENERGY", &
976 default_l_val=.false., &
977 lone_keyword_l_val=.true.)
978 CALL section_add_keyword(section, keyword)
979 CALL keyword_release(keyword)
980
981 CALL keyword_create(keyword, __location__, name="KPOINTS_SELF_ENERGY", &
982 description="Specify number of k-points for the k-point grid of the self-energy. Internally, a "// &
983 "Monkhorst-Pack grid is used. A dense k-point grid may be necessary to compute an accurate density "// &
984 "of state from GW. Large self-energy k-meshes do not cost much more computation time.", &
985 usage="KPOINTS_SELF_ENERGY nx ny nz", repeats=.true., &
986 n_var=3, type_of_var=integer_t, default_i_vals=(/0, 0, 0/))
987 CALL section_add_keyword(section, keyword)
988 CALL keyword_release(keyword)
989
990 CALL keyword_create(keyword, __location__, name="REGULARIZATION_MINIMAX", &
991 description="Tikhonov regularization for computing weights of the Fourier transform "// &
992 "from imaginary time to imaginary frequency and vice versa. Needed for large minimax "// &
993 "grids with 20 or more points and a small range.", &
994 usage="REGULARIZATION_MINIMAX 1.0E-6", &
995 default_r_val=0.0_dp)
996 CALL section_add_keyword(section, keyword)
997 CALL keyword_release(keyword)
998
999 CALL keyword_create(keyword, __location__, name="SOC", &
1000 description="Calculate the spin-orbit splitting of the eigenvalues/band structure "// &
1001 "using the spin-orbit part of the GTH pseudos parametrized in Hartwigsen, Goedecker, "// &
1002 "Hutter, Phys. Rev. B 58, 3641 (1998), Eq. 19, "// &
1003 "parameters in Table I.", &
1004 usage="SOC", &
1005 enum_c_vals=s2a("NONE", "LDA", "PBE"), &
1006 enum_i_vals=(/soc_none, soc_lda, soc_pbe/), &
1007 enum_desc=s2a("No SOC.", &
1008 "Use parameters from LDA (PADE) pseudopotential.", &
1009 "Use parameters from PBE pseudopotential."), &
1010 default_i_val=soc_none)
1011 CALL section_add_keyword(section, keyword)
1012 CALL keyword_release(keyword)
1013
1014 CALL keyword_create(keyword, __location__, name="SOC_ENERGY_WINDOW", &
1015 description="For perturbative SOC calculation, only "// &
1016 "take frontier levels in an energy window "// &
1017 "[E_HOMO - SOC_ENERGY_WINDOW/2 , E_LUMO + SOC_ENERGY_WINDOW/2 "// &
1018 "into account for the diagonalization of H^GW,SOC.", &
1019 usage="SOC_ENERGY_WINDOW 20.0_eV", &
1020 default_r_val=cp_unit_to_cp2k(value=50.0_dp, unit_str="eV"), &
1021 unit_str="eV")
1022 CALL section_add_keyword(section, keyword)
1023 CALL keyword_release(keyword)
1024
1025 ! here we generate a subsection for the periodic GW correction
1026 CALL create_periodic_gw_correction_section(subsection)
1027 CALL section_add_subsection(section, subsection)
1028 CALL section_release(subsection)
1029
1030 ! here we generate a subsection for Bethe-Salpeter
1031 CALL create_bse_section(subsection)
1032 CALL section_add_subsection(section, subsection)
1033 CALL section_release(subsection)
1034
1035 ! here we generate a subsection for image charge calculations
1036 CALL create_ic_section(subsection)
1037 CALL section_add_subsection(section, subsection)
1038 CALL section_release(subsection)
1039
1040 ! here we generate a subsection for calculating the GW band structures
1041 CALL create_kpoint_set_section(subsection)
1042 CALL section_add_subsection(section, subsection)
1043 CALL section_release(subsection)
1044
1045 ! here we generate a subsection for additional printing
1046 CALL create_print_section(subsection)
1047 CALL section_add_subsection(section, subsection)
1048 CALL section_release(subsection)
1049
1050 END SUBROUTINE create_ri_g0w0
1051
1052! **************************************************************************************************
1053!> \brief ...
1054!> \param section ...
1055! **************************************************************************************************
1056 SUBROUTINE create_print_section(section)
1057 TYPE(section_type), POINTER :: section
1058
1059 TYPE(keyword_type), POINTER :: keyword
1060 TYPE(section_type), POINTER :: gw_dos_section, print_key
1061
1062 cpassert(.NOT. ASSOCIATED(section))
1063 NULLIFY (print_key, keyword)
1064 NULLIFY (gw_dos_section, keyword)
1065 CALL section_create(section, __location__, name="PRINT", &
1066 description="Section of possible print options specific for the GW code.", &
1067 n_keywords=0, n_subsections=2, repeats=.false.)
1068
1069 CALL cp_print_key_section_create(print_key, __location__, "LOCAL_BANDGAP", &
1070 description="Prints a local bandgap E_gap(r), derived from the local density of "// &
1071 "states rho(r,E). Details and formulae in the SI of the periodic GW paper (2023).", &
1072 print_level=high_print_level, add_last=add_last_numeric, &
1073 filename="LOCAL_BANDGAP", &
1074 common_iter_levels=3)
1075
1076 CALL keyword_create(keyword, __location__, name="ENERGY_WINDOW", &
1077 description="Energy window in the LDOS for searching the gap.", &
1078 usage="ENERGY_WINDOW 6.0", &
1079 default_r_val=cp_unit_to_cp2k(value=6.0_dp, unit_str="eV"), &
1080 unit_str="eV")
1081 CALL section_add_keyword(print_key, keyword)
1082 CALL keyword_release(keyword)
1083
1084 CALL keyword_create(keyword, __location__, name="ENERGY_SPACING", &
1085 description="Energy spacing of the LDOS for searching the gap.", &
1086 usage="ENERGY_SPACING 0.03", &
1087 default_r_val=cp_unit_to_cp2k(value=0.03_dp, unit_str="eV"), &
1088 unit_str="eV")
1089 CALL section_add_keyword(print_key, keyword)
1090 CALL keyword_release(keyword)
1091
1092 CALL keyword_create(keyword, __location__, name="LDOS_THRESHOLD_GAP", &
1093 description="Relative LDOS threshold that determines the local bandgap.", &
1094 usage="LDOS_THRESHOLD_GAP 0.1", &
1095 default_r_val=0.1_dp)
1096 CALL section_add_keyword(print_key, keyword)
1097 CALL keyword_release(keyword)
1098
1099 CALL keyword_create(keyword, __location__, name="STRIDE", &
1100 description="The stride (X,Y,Z) used to write the cube file "// &
1101 "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
1102 " 1 number valid for all components.", &
1103 usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
1104 CALL section_add_keyword(print_key, keyword)
1105 CALL keyword_release(keyword)
1106
1107 CALL section_add_subsection(section, print_key)
1108 CALL section_release(print_key)
1109
1110 CALL section_create(gw_dos_section, __location__, name="GW_DOS", &
1111 description="Section for printing the spectral function.", &
1112 n_keywords=6, n_subsections=0, repeats=.false.)
1113
1114 CALL keyword_create(keyword, __location__, name="LOWER_BOUND", &
1115 description="Lower bound for GW-DOS in eV.", &
1116 usage="LOWER_BOUND -20.0", &
1117 default_r_val=cp_unit_to_cp2k(value=-20.0_dp, unit_str="eV"), &
1118 unit_str="eV")
1119 CALL section_add_keyword(gw_dos_section, keyword)
1120 CALL keyword_release(keyword)
1121
1122 CALL keyword_create(keyword, __location__, name="UPPER_BOUND", &
1123 description="Upper bound for GW-DOS in eV.", &
1124 usage="UPPER_BOUND 5.0", &
1125 default_r_val=cp_unit_to_cp2k(value=0.0_dp, unit_str="eV"), &
1126 unit_str="eV")
1127 CALL section_add_keyword(gw_dos_section, keyword)
1128 CALL keyword_release(keyword)
1129
1130 CALL keyword_create(keyword, __location__, name="STEP", &
1131 description="Difference of two consecutive energy levels for GW-DOS.", &
1132 usage="STEP 0.1", &
1133 default_r_val=cp_unit_to_cp2k(value=0.0_dp, unit_str="eV"), &
1134 unit_str="eV")
1135 CALL section_add_keyword(gw_dos_section, keyword)
1136 CALL keyword_release(keyword)
1137
1138 CALL keyword_create(keyword, __location__, name="MIN_LEVEL_SPECTRAL", &
1139 description="Lowest energy level to print the self energy to files.", &
1140 usage="MIN_LEVEL_SPECTRAL 3", &
1141 default_i_val=1)
1142 CALL section_add_keyword(gw_dos_section, keyword)
1143 CALL keyword_release(keyword)
1144
1145 CALL keyword_create(keyword, __location__, name="MAX_LEVEL_SPECTRAL", &
1146 description="Highest energy level to print the self energy to files.", &
1147 usage="MAX_LEVEL_SPECTRAL 6", &
1148 default_i_val=0)
1149 CALL section_add_keyword(gw_dos_section, keyword)
1150 CALL keyword_release(keyword)
1151
1152 CALL keyword_create(keyword, __location__, name="MIN_LEVEL_SELF_ENERGY", &
1153 description="Lowest energy level to print the self energy to files.", &
1154 usage="MIN_LEVEL_SELF_ENERGY 3", &
1155 default_i_val=1)
1156 CALL section_add_keyword(gw_dos_section, keyword)
1157 CALL keyword_release(keyword)
1158
1159 CALL keyword_create(keyword, __location__, name="MAX_LEVEL_SELF_ENERGY", &
1160 description="Highest energy level to print the self energy to files.", &
1161 usage="MAX_LEVEL_SELF_ENERGY 6", &
1162 default_i_val=0)
1163 CALL section_add_keyword(gw_dos_section, keyword)
1164 CALL keyword_release(keyword)
1165
1166 CALL keyword_create(keyword, __location__, name="BROADENING", &
1167 description="Broadening parameter for spectral function.", &
1168 usage="BROADENING 0.001", &
1169 default_r_val=cp_unit_to_cp2k(value=0.0_dp, unit_str="eV"), &
1170 unit_str="eV")
1171 CALL section_add_keyword(gw_dos_section, keyword)
1172 CALL keyword_release(keyword)
1173
1174 CALL section_add_subsection(section, gw_dos_section)
1175 CALL section_release(gw_dos_section)
1176
1177 END SUBROUTINE
1178
1179! **************************************************************************************************
1180!> \brief ...
1181!> \param section ...
1182! **************************************************************************************************
1183 SUBROUTINE create_periodic_gw_correction_section(section)
1184 TYPE(section_type), POINTER :: section
1185
1186 TYPE(keyword_type), POINTER :: keyword
1187
1188 cpassert(.NOT. ASSOCIATED(section))
1189 CALL section_create(section, __location__, name="PERIODIC_CORRECTION", &
1190 description="Parameters influencing correction for periodic GW. Old method, "// &
1191 "not recommended to use", &
1192 n_keywords=12, n_subsections=1, repeats=.false.)
1193
1194 NULLIFY (keyword)
1195
1196 CALL keyword_create(keyword, __location__, name="KPOINTS", &
1197 description="Specify number of k-points for a single k-point grid. Internally, a "// &
1198 "Monkhorst-Pack grid is used. Typically, even numbers are chosen such that the Gamma "// &
1199 "point is excluded from the k-point mesh.", &
1200 usage="KPOINTS nx ny nz", repeats=.true., &
1201 n_var=3, type_of_var=integer_t, default_i_vals=(/16, 16, 16/))
1202 CALL section_add_keyword(section, keyword)
1203 CALL keyword_release(keyword)
1204
1205 CALL keyword_create(keyword, __location__, name="NUM_KP_GRIDS", &
1206 description="Number of k-point grids around the Gamma point with different resolution. "// &
1207 "E.g. for KPOINTS 4 4 4 and NUM_KP_GRIDS 3, there will be a 3x3x3 Monkhorst-Pack (MP) k-point "// &
1208 "grid for the whole Brillouin zone (excluding Gamma), another 3x3x3 MP grid with smaller "// &
1209 "spacing around Gamma (again excluding Gamma) and a very fine 4x4x4 MP grid around Gamma.", &
1210 usage="NUM_KP_GRIDS 5", &
1211 default_i_val=1)
1212 CALL section_add_keyword(section, keyword)
1213 CALL keyword_release(keyword)
1214
1215 CALL keyword_create(keyword, __location__, name="EPS_KPOINT", &
1216 description="If the absolute value of a k-point is below EPS_KPOINT, this kpoint is "// &
1217 "neglected since the Gamma point is not included in the periodic correction.", &
1218 usage="EPS_KPOINT 1.0E-4", &
1219 default_r_val=1.0e-05_dp)
1220 CALL section_add_keyword(section, keyword)
1221 CALL keyword_release(keyword)
1222
1223 CALL keyword_create(keyword, __location__, name="MO_COEFF_GAMMA", &
1224 description="If true, only the MO coefficients at the Gamma point are used for the periodic "// &
1225 "correction. Otherwise, the MO coeffs are computed at every k-point which is much more "// &
1226 "expensive. It should be okay to use the Gamma MO coefficients.", &
1227 usage="MO_COEFF_GAMMA", &
1228 default_l_val=.true., &
1229 lone_keyword_l_val=.true.)
1230 CALL section_add_keyword(section, keyword)
1231 CALL keyword_release(keyword)
1232
1233 CALL keyword_create(keyword, __location__, name="AVERAGE_DEGENERATE_LEVELS", &
1234 variants=(/"ADL"/), &
1235 description="If true, the correlation self-energy of degenerate levels is averaged.", &
1236 usage="AVERAGE_DEGENERATE_LEVELS", &
1237 default_l_val=.true., &
1238 lone_keyword_l_val=.true.)
1239 CALL section_add_keyword(section, keyword)
1240 CALL keyword_release(keyword)
1241
1242 CALL keyword_create(keyword, __location__, name="EPS_EIGENVAL", &
1243 description="Threshold for considering levels as degenerate. Unit: Hartree.", &
1244 usage="EPS_EIGENVAL 1.0E-5", &
1245 default_r_val=2.0e-04_dp)
1246 CALL section_add_keyword(section, keyword)
1247 CALL keyword_release(keyword)
1248
1249 CALL keyword_create(keyword, __location__, name="EXTRAPOLATE_KPOINTS", &
1250 variants=(/"EXTRAPOLATE"/), &
1251 description="If true, extrapolates the k-point mesh. Only working if k-point mesh numbers are "// &
1252 "divisible by 4, e.g. 8x8x8 or 12x12x12 is recommended.", &
1253 usage="EXTRAPOLATE_KPOINTS FALSE", &
1254 default_l_val=.true., &
1255 lone_keyword_l_val=.true.)
1256 CALL section_add_keyword(section, keyword)
1257 CALL keyword_release(keyword)
1258
1259 CALL keyword_create(keyword, __location__, name="DO_AUX_BAS_GW", &
1260 description="If true, use a different basis for the periodic correction. This can be necessary "// &
1261 "in case a diffused basis is used for GW to converge the HOMO-LUMO gap. In this case, "// &
1262 "numerical problems may occur due to diffuse functions in the basis. This keyword only works if "// &
1263 "AUX_GW <basis set> is specified in the kind section for every atom kind.", &
1264 usage="DO_AUX_BAS_GW TRUE", &
1265 default_l_val=.false., &
1266 lone_keyword_l_val=.true.)
1267 CALL section_add_keyword(section, keyword)
1268 CALL keyword_release(keyword)
1269
1270 CALL keyword_create(keyword, __location__, name="FRACTION_AUX_MOS", &
1271 description="Fraction how many MOs are used in the auxiliary basis.", &
1272 usage="FRACTION_AUX_MOS 0.6", &
1273 default_r_val=0.5_dp)
1274 CALL section_add_keyword(section, keyword)
1275 CALL keyword_release(keyword)
1276
1277 CALL keyword_create(keyword, __location__, name="NUM_OMEGA_POINTS", &
1278 description="Number of Clenshaw-Curtis integration points for the periodic correction in cubic- "// &
1279 "scaling GW. This variable is a dummy variable for canonical N^4 GW calculations.", &
1280 usage="NUM_OMEGA_POINTS 200", &
1281 default_i_val=300)
1282 CALL section_add_keyword(section, keyword)
1283 CALL keyword_release(keyword)
1284
1285 END SUBROUTINE
1286
1287! **************************************************************************************************
1288!> \brief ...
1289!> \param section ...
1290! **************************************************************************************************
1291 SUBROUTINE create_bse_section(section)
1292 TYPE(section_type), POINTER :: section
1293
1294 TYPE(keyword_type), POINTER :: keyword
1295 TYPE(section_type), POINTER :: subsection
1296
1297 cpassert(.NOT. ASSOCIATED(section))
1298 CALL section_create(section, __location__, name="BSE", &
1299 description="Parameters for a calculation solving the Bethe-Salpeter equation "// &
1300 "(BSE) for electronic excitations. The full BSE "// &
1301 "$\left( \begin{array}{cc}A & B\\B & A\end{array} \right)$ "// &
1302 "$\left( \begin{array}{cc}\mathbf{X}^{(n)}\\\mathbf{Y}^{(n)}\end{array} \right) = "// &
1303 "\Omega^{(n)}\left(\begin{array}{cc}1&0\\0&-1\end{array}\right)$ "// &
1304 "$\left(\begin{array}{cc}\mathbf{X}^{(n)}\\\mathbf{Y}^{(n)}\end{array}\right)$ "// &
1305 "enables, for example, the computation of electronic excitation energies $\Omega^{(n)}$ "// &
1306 "as well as optical properties. The BSE can be solved by diagonalizing "// &
1307 "the full ABBA-matrix or by setting B=0, i.e. within the Tamm-Dancoff approximation (TDA). "// &
1308 "Preliminary reference: Eq. (35) in PRB 92, 045209 (2015); http://dx.doi.org/10.1103/PhysRevB.92.045209", &
1309 n_keywords=8, n_subsections=3, repeats=.false.)
1310
1311 NULLIFY (keyword)
1312
1313 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
1314 description="Activates BSE calculations.", &
1315 usage="&BSE .TRUE.", &
1316 default_l_val=.false., lone_keyword_l_val=.true.)
1317 CALL section_add_keyword(section, keyword)
1318 CALL keyword_release(keyword)
1319
1320 CALL keyword_create(keyword, __location__, name="SPIN_CONFIG", &
1321 description="Choose between calculation of singlet or triplet excitation (cf. given Reference above).", &
1322 usage="SPIN_CONFIG TRIPLET", &
1323 enum_c_vals=s2a("SINGLET", "TRIPLET"), &
1324 enum_i_vals=(/bse_singlet, bse_triplet/), &
1325 enum_desc=s2a("Computes singlet excitations.", &
1326 "Computes triplet excitations."), &
1327 default_i_val=bse_singlet)
1328 CALL section_add_keyword(section, keyword)
1329 CALL keyword_release(keyword)
1330
1331 CALL keyword_create(keyword, __location__, name="BSE_DIAG_METHOD", &
1332 description="Method for BSE calculations. "// &
1333 "Choose between full or iterative diagonalization.", &
1334 usage="BSE_DIAG_METHOD FULLDIAG", &
1335 enum_c_vals=s2a("FULLDIAG", "ITERDIAG"), &
1336 enum_i_vals=(/bse_fulldiag, bse_iterdiag/), &
1337 enum_desc=s2a("Fully diagonalizes the BSE matrices within the chosen level of approximation.", &
1338 "Iterative diagonalization has not been implemented yet."), &
1339 default_i_val=bse_fulldiag)
1340 CALL section_add_keyword(section, keyword)
1341 CALL keyword_release(keyword)
1342
1343 CALL keyword_create(keyword, __location__, name="TDA", &
1344 description="Level of approximation applied to BSE calculations. "// &
1345 "Choose between Tamm Dancoff approximation (TDA) and/or diagonalization of the full ABBA-matrix.", &
1346 usage="TDA ON", &
1347 enum_c_vals=s2a("ON", "OFF", "TDA+ABBA"), &
1348 enum_i_vals=(/bse_tda, bse_abba, bse_both/), &
1349 enum_desc=s2a("The TDA is applied, i.e. B=0.", &
1350 "The ABBA-matrix is diagonalized, i.e. the TDA is not applied.", &
1351 "The BSE is solved within the TDA (B=0) as well as for the full ABBA-matrix."), &
1352 default_i_val=bse_tda)
1353 CALL section_add_keyword(section, keyword)
1354 CALL keyword_release(keyword)
1355
1356 CALL keyword_create(keyword, __location__, name="ENERGY_CUTOFF_OCC", &
1357 description="Remove all orbitals with indices i,j from A_ia,jb and B_ia,jb with energy difference "// &
1358 "to HOMO level larger than the given energy cutoff, i.e. "// &
1359 "$\varepsilon_i\in[\varepsilon_{i=\text{HOMO}}^{GW}-E_\text{cut}^\text{occ},\varepsilon_{i=\text{HOMO}}^{GW}]$. "// &
1360 "Can be used to accelerate runtime and reduce memory consumption.", &
1361 usage="ENERGY_CUTOFF_OCC 10.0", unit_str="eV", &
1362 type_of_var=real_t, default_r_val=-1.0_dp)
1363 CALL section_add_keyword(section, keyword)
1364 CALL keyword_release(keyword)
1365
1366 CALL keyword_create(keyword, __location__, name="ENERGY_CUTOFF_EMPTY", &
1367 description="Remove all orbitals with indices a,b from A_ia,jb and B_ia,jb with energy difference "// &
1368 "to LUMO level larger than the given energy cutoff, i.e. "// &
1369 "$\varepsilon_a\in[\varepsilon_{a=\text{LUMO}}^{GW},\varepsilon_{a=\text{LUMO}}^{GW}+E_\text{cut}^\text{empty}]$. "// &
1370 "Can be used to accelerate runtime and reduce memory consumption.", &
1371 usage="ENERGY_CUTOFF_EMPTY 10.0", unit_str="eV", &
1372 type_of_var=real_t, default_r_val=-1.0_dp)
1373 CALL section_add_keyword(section, keyword)
1374 CALL keyword_release(keyword)
1375
1376 CALL keyword_create(keyword, __location__, name="BSE_DEBUG_PRINT", &
1377 description="Activates debug print statements in the BSE calculation.", &
1378 usage="BSE_DEBUG_PRINT .TRUE.", &
1379 default_l_val=.false., lone_keyword_l_val=.true.)
1380 CALL section_add_keyword(section, keyword)
1381 CALL keyword_release(keyword)
1382
1383 CALL keyword_create(keyword, __location__, name="NUM_PRINT_EXC", &
1384 description="Number of printed excitation levels with respective "// &
1385 "energies and oscillator strengths. Does not affect computation time.", &
1386 usage="NUM_PRINT_EXC 25", &
1387 default_i_val=25)
1388 CALL section_add_keyword(section, keyword)
1389 CALL keyword_release(keyword)
1390
1391 CALL keyword_create(keyword, __location__, name="NUM_PRINT_EXC_DESCR", &
1392 description="Number of excitation levels for which the exciton "// &
1393 "descriptors are computed. Negative or too large "// &
1394 "NUM_PRINT_EXC_DESCR defaults to NUM_PRINT_EXC.", &
1395 usage="NUM_PRINT_EXC_DESCR 5", &
1396 default_i_val=0)
1397 CALL section_add_keyword(section, keyword)
1398 CALL keyword_release(keyword)
1399
1400 CALL keyword_create(keyword, __location__, name="PRINT_DIRECTIONAL_EXC_DESCR", &
1401 description="Activates printing of exciton descriptors per direction.", &
1402 usage="PRINT_DIRECTIONAL_EXC_DESCR .TRUE.", &
1403 default_l_val=.false., lone_keyword_l_val=.true.)
1404 CALL section_add_keyword(section, keyword)
1405 CALL keyword_release(keyword)
1406
1407 CALL keyword_create(keyword, __location__, name="EPS_X", &
1408 description="Threshold for printing contributions of singleparticle "// &
1409 "transitions, i.e. elements of the eigenvectors $X_{ia}^{(n)}$ and $Y_{ia}^{(n)}$.", &
1410 usage="EPS_X 0.1", &
1411 type_of_var=real_t, default_r_val=0.1_dp)
1412 CALL section_add_keyword(section, keyword)
1413 CALL keyword_release(keyword)
1414
1415 CALL keyword_create(keyword, __location__, name="USE_KS_ENERGIES", &
1416 description="Uses KS energies instead of GW quasiparticle energies.", &
1417 usage="USE_KS_ENERGIES .TRUE.", &
1418 default_l_val=.false., lone_keyword_l_val=.true.)
1419 CALL section_add_keyword(section, keyword)
1420 CALL keyword_release(keyword)
1421
1422 NULLIFY (subsection)
1423 CALL create_bse_screening_section(subsection)
1424 CALL section_add_subsection(section, subsection)
1425 CALL section_release(subsection)
1426
1427 NULLIFY (subsection)
1428 CALL create_bse_iterat_section(subsection)
1429 CALL section_add_subsection(section, subsection)
1430 CALL section_release(subsection)
1431
1432 NULLIFY (subsection)
1433 CALL create_bse_spectrum_section(subsection)
1434 CALL section_add_subsection(section, subsection)
1435 CALL section_release(subsection)
1436
1437 NULLIFY (subsection)
1438 CALL create_bse_nto_section(subsection)
1439 CALL section_add_subsection(section, subsection)
1440 CALL section_release(subsection)
1441
1442 END SUBROUTINE
1443
1444 SUBROUTINE create_bse_screening_section(section)
1445 TYPE(section_type), POINTER :: section
1446
1447 TYPE(keyword_type), POINTER :: keyword
1448
1449 cpassert(.NOT. ASSOCIATED(section))
1450
1451 CALL section_create(section, __location__, name="SCREENING_IN_W", &
1452 description="Screening $\epsilon$ applied to $W(\omega=0)=\epsilon^{-1}(\omega=0) v $ "// &
1453 "in the BSE calculation. Besides default BSE, i.e. $W_0$ (screening with DFT energies), "// &
1454 "a fixed $\alpha = \epsilon^{-1}(\omega)$ can be applied, which is similar to the mixing "// &
1455 "parameter for hybrid functionals in LR-TDDFT. In addition, the keywords TDHF "// &
1456 "(no screening - $\alpha = 1$) and RPA (infinite screening - $\alpha = 0$) can be applied.", &
1457 n_keywords=2, n_subsections=0, repeats=.false.)
1458
1459 NULLIFY (keyword)
1460
1461 CALL keyword_create( &
1462 keyword, __location__, name="_SECTION_PARAMETERS_", &
1463 description="Shortcut for the most common functional combinations.", &
1464 usage="&xc_functional BLYP", &
1465 enum_c_vals=s2a("W_0", "TDHF", "RPA", "ALPHA"), &
1467 enum_desc=s2a("The Coulomb interaction is screened by applying DFT energies "// &
1468 "$\varepsilon_p^{DFT}$, which is typically used for GW-BSE and "// &
1469 "often labeled as $W_0$.", &
1470 "The Coulomb interaction is not screened, i.e. $W_{pq,rs}(\omega=0) "// &
1471 "\rightarrow v_{pq,rs}$ enters.", &
1472 "Infinite screening is applied, i.e. $W_{pq,rs}(\omega=0) \rightarrow 0$.", &
1473 "Arbitrary screening parameter. Specify within section."), &
1474 default_i_val=bse_screening_w0, &
1475 lone_keyword_i_val=bse_screening_w0)
1476 CALL section_add_keyword(section, keyword)
1477 CALL keyword_release(keyword)
1478
1479 CALL keyword_create(keyword, __location__, name="ALPHA", &
1480 description="Screening parameter similar to the mixing in hybrid functionals used in TDDFT. "// &
1481 "$\alpha$ mimicks the screening $\epsilon^{-1}(\omega)$ and enforces $W = \alpha v$ "// &
1482 "in the BSE calculation.", &
1483 usage="ALPHA 0.25", &
1484 type_of_var=real_t, default_r_val=-1.00_dp)
1485 CALL section_add_keyword(section, keyword)
1486 CALL keyword_release(keyword)
1487
1488 END SUBROUTINE create_bse_screening_section
1489
1490 SUBROUTINE create_bse_nto_section(print_key)
1491 TYPE(section_type), POINTER :: print_key
1492
1493 TYPE(keyword_type), POINTER :: keyword
1494
1495 cpassert(.NOT. ASSOCIATED(print_key))
1496
1497 CALL cp_print_key_section_create(print_key, __location__, name="NTO_ANALYSIS", &
1498 description="Perform a natural transition orbital analysis, i.e. the transition density matrix "// &
1499 "$T^{(n)}=\left( \begin{array}{cc}0& {X}^{(n)}\\ \left({Y}^{(n)} \right)^T & 0\end{array} \right)$ "// &
1500 "is decomposed into its singular values "// &
1501 "$T^{(n)} = {U}^{(n)} {\Lambda^{(n)}} \left({V}^{(n)}\right)^T$ "// &
1502 "in order to compute the NTO pairs "// &
1503 "$\phi_I^{(n)}(\mathbf{r}_e) = \sum_{p=1}^{N_b} \varphi_p(\mathbf{r}_e) V_{p,I}^{(n)}$ for the electron and "// &
1504 "$\chi_I^{(n)}(\mathbf{r}_h) = \sum_{q=1}^{N_b} \varphi_q(\mathbf{r}_h) U_{q,I}^{(n)}$ for the hole.", &
1505 print_level=debug_print_level + 1, & ! Corresponds to "off" as default behavior
1506 filename="BSE-NTO_ANALYSIS") ! All other print levels will trigger the analysis
1507 ! cf. input/cp_output_handling.F:cp_print_key_section_create
1508
1509 NULLIFY (keyword)
1510 CALL keyword_create(keyword, __location__, name="EPS_NTO_EIGVAL", &
1511 description="Threshold for NTO eigenvalues, i.e. only "// &
1512 "${\left(\lambda_I^{(n)}\right)}^2$ > EPS_NTO_EIGVAL are considered.", &
1513 usage="EPS_NTO_EIGVAL 0.01", &
1514 n_var=1, &
1515 type_of_var=real_t, &
1516 default_r_val=0.01_dp)
1517 CALL section_add_keyword(print_key, keyword)
1518 CALL keyword_release(keyword)
1519
1520 CALL keyword_create(keyword, __location__, name="EPS_OSC_STR", &
1521 description="Threshold of oscillator strengths $f^{(n)}$ for an excitation level. "// &
1522 "In case, the excitation level n has a smaller oscillator strength, the "// &
1523 "NTOs for this excitation level are not printed.", &
1524 usage="EPS_OSC_STR 0.01", &
1525 n_var=1, &
1526 type_of_var=real_t, &
1527 default_r_val=-1.0_dp)
1528 CALL section_add_keyword(print_key, keyword)
1529 CALL keyword_release(keyword)
1530
1531 CALL keyword_create(keyword, __location__, name="NUM_PRINT_EXC_NTOS", &
1532 description="Number of excitation level $n$ up to which NTOs are printed. "// &
1533 "By default, this is set to NUM_PRINT_EXC. Negative or too large "// &
1534 "NUM_PRINT_EXC_NTOS defaults to NUM_PRINT_EXC.", &
1535 usage="NUM_PRINT_EXC_NTOS 5", &
1536 n_var=1, &
1537 type_of_var=integer_t, &
1538 default_i_val=-1)
1539 CALL section_add_keyword(print_key, keyword)
1540 CALL keyword_release(keyword)
1541
1542 CALL keyword_create(keyword, __location__, name="STATE_LIST", &
1543 description="Specifies a list of excitation levels $n$ for which NTOs are printed. "// &
1544 "Overrides NUM_PRINT_EXC_NTOS.", &
1545 usage="STATE_LIST {integer} {integer} .. {integer}", &
1546 n_var=-1, type_of_var=integer_t)
1547 CALL section_add_keyword(print_key, keyword)
1548 CALL keyword_release(keyword)
1549
1550 CALL keyword_create(keyword, __location__, name="CUBE_FILES", &
1551 description="Print NTOs on Cube Files", &
1552 usage="CUBE_FILES {logical}", repeats=.false., n_var=1, &
1553 default_l_val=.true., lone_keyword_l_val=.true., type_of_var=logical_t)
1554 CALL section_add_keyword(print_key, keyword)
1555 CALL keyword_release(keyword)
1556
1557 CALL keyword_create(keyword, __location__, name="STRIDE", &
1558 description="The stride (X,Y,Z) used to write the cube file "// &
1559 "(larger values result in smaller cube files). Provide 3 numbers (for X,Y,Z) or"// &
1560 " 1 number valid for all components.", &
1561 usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
1562 CALL section_add_keyword(print_key, keyword)
1563 CALL keyword_release(keyword)
1564
1565 CALL keyword_create(keyword, __location__, name="APPEND", &
1566 description="append the cube files when they already exist", &
1567 default_l_val=.false., lone_keyword_l_val=.true.)
1568 CALL section_add_keyword(print_key, keyword)
1569 CALL keyword_release(keyword)
1570
1571 END SUBROUTINE create_bse_nto_section
1572
1573 SUBROUTINE create_bse_spectrum_section(section)
1574 TYPE(section_type), POINTER :: section
1575
1576 TYPE(keyword_type), POINTER :: keyword
1577
1578 cpassert(.NOT. ASSOCIATED(section))
1579 CALL section_create(section, __location__, name="BSE_SPECTRUM", &
1580 description="Parameters influencing the output of the optical absorption spectrum, i.e. "// &
1581 "the dynamical dipole polarizability tensor $\alpha_{\mu,\mu'}(\omega)$ "// &
1582 "($\mu,\mu'\in\{x,y,z\}$), obtained from a BSE calculation, which is defined as "// &
1583 "$ \alpha_{\mu,\mu'}(\omega) = \sum_n \frac{2 E^{(n)} d^{(n)}_{\mu} d^{(n)}_{\mu'}} "// &
1584 "{(\omega+i\eta)^2-\left(\Omega^{(n)}\right)^2} $. "// &
1585 "The printed file will contain the specified frequency range $\omega$ and the "// &
1586 "corresponding imaginary part of the average $\bar{\alpha}(\omega)=\frac{1}{3}\mathrm{Tr} "// &
1587 "\left[ \alpha_{\mu,\mu'}(\omega)\right]$ as well as of the elements of $\alpha_{\mu,\mu'}(\omega)$.", &
1588 n_keywords=9, n_subsections=0, repeats=.false.)
1589
1590 NULLIFY (keyword)
1591
1592 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
1593 description="Activates printing of optical absorption spectrum from the BSE calculation.", &
1594 usage="&BSE .TRUE.", &
1595 default_l_val=.false., lone_keyword_l_val=.true.)
1596 CALL section_add_keyword(section, keyword)
1597 CALL keyword_release(keyword)
1598
1599 CALL keyword_create(keyword, __location__, name="FREQUENCY_STEP_SIZE", &
1600 description="Step size of frequencies for the optical absorption spectrum.", &
1601 usage="FREQUENCY_STEP_SIZE 0.1", unit_str="eV", &
1602 type_of_var=real_t, &
1603 default_r_val=cp_unit_to_cp2k(value=0.1_dp, unit_str="eV"))
1604 CALL section_add_keyword(section, keyword)
1605 CALL keyword_release(keyword)
1606
1607 CALL keyword_create(keyword, __location__, name="FREQUENCY_STARTING_POINT", &
1608 description="First frequency to print in the optical absorption spectrum.", &
1609 usage="FREQUENCY_STARTING_POINT 0", unit_str="eV", &
1610 type_of_var=real_t, default_r_val=0.0_dp)
1611 CALL section_add_keyword(section, keyword)
1612 CALL keyword_release(keyword)
1613
1614 CALL keyword_create(keyword, __location__, name="FREQUENCY_END_POINT", &
1615 description="Last frequency to print in the optical absorption spectrum.", &
1616 usage="FREQUENCY_END_POINT 0", unit_str="eV", &
1617 type_of_var=real_t, &
1618 default_r_val=cp_unit_to_cp2k(value=100.0_dp, unit_str="eV"))
1619 CALL section_add_keyword(section, keyword)
1620 CALL keyword_release(keyword)
1621
1622 CALL keyword_create(keyword, __location__, name="ETA_LIST", &
1623 description="List of broadening of the peaks in the optical absorption spectrum.", &
1624 usage="ETA_LIST 0.01 ...", unit_str="eV", &
1625 default_r_vals=(/cp_unit_to_cp2k(value=0.01_dp, unit_str="eV")/), &
1626 type_of_var=real_t, n_var=-1)
1627 CALL section_add_keyword(section, keyword)
1628 CALL keyword_release(keyword)
1629
1630 END SUBROUTINE
1631
1632! **************************************************************************************************
1633!> \brief ...
1634!> \param section ...
1635! **************************************************************************************************
1636 SUBROUTINE create_bse_iterat_section(section)
1637 TYPE(section_type), POINTER :: section
1638
1639 TYPE(keyword_type), POINTER :: keyword
1640
1641 cpassert(.NOT. ASSOCIATED(section))
1642 CALL section_create(section, __location__, name="BSE_ITERAT", &
1643 description="Parameters influencing the iterative Bethe-Salpeter calculation. "// &
1644 "The iterative solver has not been fully implemented yet.", &
1645 n_keywords=9, n_subsections=0, repeats=.false.)
1646
1647 NULLIFY (keyword)
1648
1649 CALL keyword_create(keyword, __location__, name="DAVIDSON_ABORT_COND", &
1650 description="Desired abortion condition for Davidson solver", &
1651 usage="DAVIDSON_ABORT_COND OR", &
1652 enum_c_vals=s2a("EN", "RES", "OR"), &
1654 enum_desc=s2a("Uses energy threshold for successfully exiting solver.", &
1655 "Uses residual threshold for successfully exiting solver.", &
1656 "Uses either energy or residual threshold for successfully exiting solver."), &
1657 default_i_val=bse_iter_en_cond)
1658 CALL section_add_keyword(section, keyword)
1659 CALL keyword_release(keyword)
1660
1661 CALL keyword_create(keyword, __location__, name="NUM_EXC_EN", &
1662 description="Number of lowest excitation energies to be computed.", &
1663 usage="NUM_EXC_EN 3", &
1664 default_i_val=3)
1665 CALL section_add_keyword(section, keyword)
1666 CALL keyword_release(keyword)
1667
1668 CALL keyword_create(keyword, __location__, name="NUM_ADD_START_Z_SPACE", &
1669 description="Determines the initial dimension of the subspace as "// &
1670 "dim = (NUM_EXC_EN+NUM_ADD_START_Z_SPACE)", &
1671 usage="NUM_ADD_START_Z_SPACE 1", &
1672 default_i_val=0)
1673 CALL section_add_keyword(section, keyword)
1674 CALL keyword_release(keyword)
1675
1676 CALL keyword_create(keyword, __location__, name="FAC_MAX_Z_SPACE", &
1677 description="Factor to determine maximum dimension of the Davidson subspace. "// &
1678 "dimension = (NUM_EXC_EN+NUM_ADD_START_Z_SPACE)*FAC_MAX_Z_SPACE", &
1679 usage="FAC_MAX_Z_SPACE 5", &
1680 default_i_val=5)
1681 CALL section_add_keyword(section, keyword)
1682 CALL keyword_release(keyword)
1683
1684 CALL keyword_create(keyword, __location__, name="NUM_NEW_T", &
1685 description="Number of new t vectors added. "// &
1686 "Must be smaller/equals (NUM_EXC_EN+NUM_ADD_START_Z_SPACE)", &
1687 usage="NUM_NEW_T 4", &
1688 default_i_val=1)
1689 CALL section_add_keyword(section, keyword)
1690 CALL keyword_release(keyword)
1691
1692 CALL keyword_create(keyword, __location__, name="EPS_RES", &
1693 description="Threshold for stopping the iteration for computing the transition energies. "// &
1694 "If the residuals inside the Davidson space change by less than EPS_RES (in eV), the iteration "// &
1695 "stops.", &
1696 usage="EPS_RES 0.001", unit_str="eV", &
1697 type_of_var=real_t, default_r_val=0.001_dp)
1698 CALL section_add_keyword(section, keyword)
1699 CALL keyword_release(keyword)
1700
1701 CALL keyword_create(keyword, __location__, name="EPS_EXC_EN", &
1702 description="Threshold for stopping the iteration for computing the transition energies. "// &
1703 "If the desired excitation energies change by less than EPS_EXC_EN (in eV), the iteration "// &
1704 "stops.", &
1705 usage="EPS_EXC_EN 0.001", unit_str="eV", &
1706 type_of_var=real_t, default_r_val=0.001_dp)
1707 CALL section_add_keyword(section, keyword)
1708 CALL keyword_release(keyword)
1709
1710 CALL keyword_create(keyword, __location__, name="NUM_DAVIDSON_ITER", &
1711 description="Maximum number of iterations for determining the transition energies.", &
1712 usage="NUM_DAVIDSON_ITER 100", &
1713 default_i_val=100)
1714 CALL section_add_keyword(section, keyword)
1715 CALL keyword_release(keyword)
1716
1717 CALL keyword_create(keyword, __location__, name="Z_SPACE_ENERGY_CUTOFF", &
1718 description="Cutoff (in eV) for maximal energy difference entering the A matrix. "// &
1719 "Per default and for negative values, there is no cutoff applied.", &
1720 usage="Z_SPACE_ENERGY_CUTOFF 60", unit_str="eV", &
1721 type_of_var=real_t, default_r_val=-1.0_dp)
1722 CALL section_add_keyword(section, keyword)
1723 CALL keyword_release(keyword)
1724 END SUBROUTINE
1725
1726! **************************************************************************************************
1727!> \brief ...
1728!> \param section ...
1729! **************************************************************************************************
1730 SUBROUTINE create_ic_section(section)
1731 TYPE(section_type), POINTER :: section
1732
1733 TYPE(keyword_type), POINTER :: keyword
1734
1735 cpassert(.NOT. ASSOCIATED(section))
1736 CALL section_create(section, __location__, name="IC", &
1737 description="Parameters influencing the image charge correction. "// &
1738 "The image plane is always an xy plane, so adjust the molecule according "// &
1739 "to that. ", &
1740 n_keywords=3, n_subsections=1, repeats=.false.)
1741
1742 NULLIFY (keyword)
1743
1744 CALL keyword_create(keyword, __location__, name="PRINT_IC_LIST", &
1745 description="If true, the image charge correction values are printed in a list, "// &
1746 "such that it can be used as input for a subsequent evGW calculation.", &
1747 usage="PRINT_IC_LIST .TRUE.", &
1748 default_l_val=.false., &
1749 lone_keyword_l_val=.true.)
1750 CALL section_add_keyword(section, keyword)
1751 CALL keyword_release(keyword)
1752
1753 CALL keyword_create(keyword, __location__, name="EPS_DIST", &
1754 description="Threshold where molecule and image molecule have to coincide. ", &
1755 usage="EPS_DIST 0.1", unit_str="angstrom", &
1756 type_of_var=real_t, default_r_val=3.0e-02_dp, repeats=.false.)
1757 CALL section_add_keyword(section, keyword)
1758 CALL keyword_release(keyword)
1759
1760 END SUBROUTINE
1761
1762! **************************************************************************************************
1763!> \brief ...
1764!> \param section ...
1765! **************************************************************************************************
1766 SUBROUTINE create_low_scaling(section)
1767 TYPE(section_type), POINTER :: section
1768
1769 TYPE(keyword_type), POINTER :: keyword
1770 TYPE(section_type), POINTER :: subsection
1771
1772 cpassert(.NOT. ASSOCIATED(section))
1773 CALL section_create( &
1774 section, __location__, name="LOW_SCALING", &
1775 description="Cubic scaling RI-RPA, GW and Laplace-SOS-MP2 method using the imaginary time formalism. "// &
1776 "EPS_GRID in WFC_GPW section controls accuracy / req. memory for 3-center integrals. "// &
1777 "SORT_BASIS EXP should be specified in DFT section.", &
1778 n_keywords=12, n_subsections=2, repeats=.false., &
1779 citations=(/wilhelm2016b, wilhelm2018, bussy2023/))
1780
1781 NULLIFY (keyword)
1782 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
1783 description="Activates cubic-scaling RPA, GW and Laplace-SOS-MP2 calculations.", &
1784 usage="&LOW_SCALING .TRUE.", &
1785 default_l_val=.false., lone_keyword_l_val=.true.)
1786 CALL section_add_keyword(section, keyword)
1787 CALL keyword_release(keyword)
1788
1789 CALL keyword_create(keyword, __location__, name="MEMORY_CUT", &
1790 description="Reduces memory for sparse tensor contractions by this factor. "// &
1791 "A high value leads to some loss of performance. "// &
1792 "This memory reduction factor applies to storage of the tensors 'M occ' / 'M virt' "// &
1793 "but does not reduce storage of '3c ints'.", &
1794 usage="MEMORY_CUT 16", &
1795 default_i_val=5)
1796 CALL section_add_keyword(section, keyword)
1797 CALL keyword_release(keyword)
1798
1799 CALL keyword_create(keyword, __location__, name="MEMORY_INFO", &
1800 description="Decide whether to print memory info on the sparse matrices.", &
1801 usage="MEMORY_INFO", &
1802 default_l_val=.false., &
1803 lone_keyword_l_val=.true.)
1804 CALL section_add_keyword(section, keyword)
1805 CALL keyword_release(keyword)
1806
1807 CALL keyword_create( &
1808 keyword, __location__, name="EPS_FILTER", &
1809 description="Determines a threshold for the DBCSR based multiply. "// &
1810 "Normally, this EPS_FILTER determines accuracy and timing of low-scaling RPA and GW calculations.", &
1811 usage="EPS_FILTER 1.0E-10 ", type_of_var=real_t, &
1812 default_r_val=1.0e-9_dp)
1813 CALL section_add_keyword(section, keyword)
1814 CALL keyword_release(keyword)
1815
1816 CALL keyword_create( &
1817 keyword, __location__, name="EPS_FILTER_FACTOR", &
1818 description="Multiply EPS_FILTER with this factor to determine filter epsilon "// &
1819 "for DBCSR based multiply P(it)=(Mocc(it))^T*Mvirt(it) "// &
1820 "Default should be kept.", &
1821 type_of_var=real_t, &
1822 default_r_val=10.0_dp)
1823 CALL section_add_keyword(section, keyword)
1824 CALL keyword_release(keyword)
1825
1826 CALL keyword_create( &
1827 keyword, __location__, &
1828 name="EPS_STORAGE_SCALING", &
1829 variants=(/"EPS_STORAGE"/), &
1830 description="Scaling factor to scale EPS_FILTER. Storage threshold for compression "// &
1831 "will be EPS_FILTER*EPS_STORAGE_SCALING.", &
1832 default_r_val=1.0e-3_dp)
1833 CALL section_add_keyword(section, keyword)
1834 CALL keyword_release(keyword)
1835
1836 CALL keyword_create( &
1837 keyword, __location__, &
1838 name="DO_KPOINTS", &
1839 description="Besides in DFT, this keyword has to be switched on if one wants to do kpoints in. "// &
1840 "cubic RPA.", &
1841 usage="DO_KPOINTS", &
1842 default_l_val=.false., &
1843 lone_keyword_l_val=.true.)
1844 CALL section_add_keyword(section, keyword)
1845 CALL keyword_release(keyword)
1846
1847 CALL keyword_create( &
1848 keyword, __location__, name="KPOINTS", &
1849 description="Keyword activates periodic, low-scaling GW calculations (&LOW_SCALING section also needed). "// &
1850 "For periodic calculations, kpoints are used for the density response, the "// &
1851 "Coulomb interaction and the screened Coulomb interaction. For 2d periodic systems, e.g. xz "// &
1852 "periodicity, please also specify KPOINTS, e.g. N_x 1 N_z.", &
1853 usage="KPOINTS N_x N_y N_z", &
1854 n_var=3, type_of_var=integer_t, default_i_vals=(/0, 0, 0/))
1855 CALL section_add_keyword(section, keyword)
1856 CALL keyword_release(keyword)
1857
1858 CALL keyword_create( &
1859 keyword, __location__, &
1860 name="KPOINT_WEIGHTS_W", &
1861 description="For kpoints in low-scaling GW, a Monkhorst-Pack mesh is used. The screened Coulomb "// &
1862 "interaction W(k) needs special care near the Gamma point (e.g. in 3d, W(k) diverges at the "// &
1863 "Gamma point with W(k) ~ k^alpha). KPOINT_WEIGHTS_W decides how the weights of the "// &
1864 "Monkhorst-Pack mesh are chosen to compute W(R) = int_BZ W(k) exp(ikR) dk (BZ=Brllouin zone). ", &
1865 usage="KPOINT_WEIGHTS_W AUTO", &
1866 enum_c_vals=s2a("TAILORED", "AUTO", "UNIFORM"), &
1868 enum_desc=s2a("Choose k-point integration weights such that the function f(k)=k^alpha is "// &
1869 "exactly integrated. alpha is specified using EXPONENT_TAILORED_WEIGHTS.", &
1870 "As 'TAILORED', but alpha is chosen automatically according to dimensionality "// &
1871 "(3D: alpha = -2 for 3D, 2D: alpha = -1 for exchange self-energy, uniform "// &
1872 "weights for correlation self-energy).", &
1873 "Choose the same weight for every k-point (original Monkhorst-Pack method)."), &
1874 default_i_val=kp_weights_w_uniform)
1875 CALL section_add_keyword(section, keyword)
1876 CALL keyword_release(keyword)
1877
1878 CALL keyword_create( &
1879 keyword, __location__, &
1880 name="EXPONENT_TAILORED_WEIGHTS", &
1881 description="Gives the exponent of exactly integrated function in case 'KPOINT_WEIGHTS_W "// &
1882 "TAILORED' is chosen.", &
1883 usage="EXPONENT_TAILORED_WEIGHTS -2", &
1884 default_r_val=-2.0_dp)
1885 CALL section_add_keyword(section, keyword)
1886 CALL keyword_release(keyword)
1887
1888 CALL keyword_create( &
1889 keyword, __location__, &
1890 name="REGULARIZATION_RI", &
1891 description="Parameter to reduce the expansion coefficients in RI for periodic GW. Larger parameter "// &
1892 "means smaller expansion coefficients that leads to a more stable calculation at the price "// &
1893 "of a slightly worse RI approximation. In case the parameter 0.0 is chosen, ordinary RI is used.", &
1894 usage="REGULARIZATION_RI 1.0E-4", &
1895 default_r_val=0.0_dp)
1896 CALL section_add_keyword(section, keyword)
1897 CALL keyword_release(keyword)
1898
1899 CALL keyword_create( &
1900 keyword, __location__, &
1901 name="EPS_EIGVAL_S", &
1902 description="Parameter to reduce the expansion coefficients in RI for periodic GW. Removes all "// &
1903 "eigenvectors and eigenvalues of S_PQ(k) that are smaller than EPS_EIGVAL_S. ", &
1904 usage="EPS_EIGVAL_S 1.0E-3", &
1905 default_r_val=0.0_dp)
1906 CALL section_add_keyword(section, keyword)
1907 CALL keyword_release(keyword)
1908
1909 CALL keyword_create( &
1910 keyword, __location__, &
1911 name="EPS_EIGVAL_S_GAMMA", &
1912 description="Parameter to reduce the expansion coefficients in RI for periodic GW. Removes all "// &
1913 "eigenvectors and eigenvalues of M_PQ(k=0) that are smaller than EPS_EIGVAL_S. ", &
1914 usage="EPS_EIGVAL_S_GAMMA 1.0E-3", &
1915 default_r_val=0.0_dp)
1916 CALL section_add_keyword(section, keyword)
1917 CALL keyword_release(keyword)
1918
1919 CALL keyword_create( &
1920 keyword, __location__, &
1921 name="MAKE_CHI_POS_DEFINITE", &
1922 description="If true, makes eigenvalue decomposition of chi(iw,k) and removes negative "// &
1923 "eigenvalues. May increase computational cost significantly. Only recommended to try in case "// &
1924 "Cholesky decomposition of epsilon(iw,k) fails.", &
1925 usage="MAKE_CHI_POS_DEFINITE", &
1926 default_l_val=.true., &
1927 lone_keyword_l_val=.true.)
1928 CALL section_add_keyword(section, keyword)
1929 CALL keyword_release(keyword)
1930
1931 CALL keyword_create( &
1932 keyword, __location__, &
1933 name="MAKE_OVERLAP_MAT_AO_POS_DEFINITE", &
1934 description="If true, makes eigenvalue decomposition of S_mu,nu(k) and removes negative "// &
1935 "eigenvalues. Slightly increases computational cost. Only recommended to try in case "// &
1936 "Cholesky decomposition of S_mu,nu(k) fails (error message: Cholesky decompose failed: "// &
1937 "matrix is not positive definite or ill-conditioned; when calling create_kp_and_calc_kp_orbitals).", &
1938 usage="MAKE_OVERLAP_MAT_AO_POS_DEFINITE", &
1939 default_l_val=.false., &
1940 lone_keyword_l_val=.true.)
1941 CALL section_add_keyword(section, keyword)
1942 CALL keyword_release(keyword)
1943
1944 CALL keyword_create( &
1945 keyword, __location__, &
1946 name="DO_EXTRAPOLATE_KPOINTS", &
1947 description="If true, use a larger k-mesh to extrapolate the k-point integration of W. "// &
1948 "For example, in 2D, when using KPOINTS 4 4 1, an additional 6x6x1 mesh will be used to "// &
1949 "extrapolate the k-point integration of W with N_k^-0.5, where Nk is the number of k-points.", &
1950 usage="DO_EXTRAPOLATE_KPOINTS FALSE", &
1951 default_l_val=.true., &
1952 lone_keyword_l_val=.true.)
1953 CALL section_add_keyword(section, keyword)
1954 CALL keyword_release(keyword)
1955
1956 CALL keyword_create( &
1957 keyword, __location__, &
1958 name="TRUNC_COULOMB_RI_X", &
1959 description="If true, use the truncated Coulomb operator for the exchange-self-energy in "// &
1960 "periodic GW.", &
1961 usage="TRUNC_COULOMB_RI_X", &
1962 default_l_val=.true., &
1963 lone_keyword_l_val=.true.)
1964 CALL section_add_keyword(section, keyword)
1965 CALL keyword_release(keyword)
1966
1967 CALL keyword_create( &
1968 keyword, __location__, &
1969 name="REL_CUTOFF_TRUNC_COULOMB_RI_X", &
1970 description="Only active in case TRUNC_COULOMB_RI_X = True. Normally, relative cutoff = 0.5 is "// &
1971 "good choice; still needs to be evaluated for RI schemes. ", &
1972 usage="REL_CUTOFF_TRUNC_COULOMB_RI_X 0.3", &
1973 default_r_val=0.5_dp)
1974 CALL section_add_keyword(section, keyword)
1975 CALL keyword_release(keyword)
1976
1977 CALL keyword_create( &
1978 keyword, __location__, &
1979 name="KEEP_QUADRATURE", &
1980 variants=s2a("KEEP_WEIGHTS", "KEEP_QUAD", "KEEP_WEIGHT"), &
1981 description="Keep the Laplace quadrature defined at the first energy evaluations throughout "// &
1982 "the run. Allows to have consistent force evaluations.", &
1983 usage="KEEP_QUADRATURE", &
1984 default_l_val=.true., &
1985 lone_keyword_l_val=.true.)
1986 CALL section_add_keyword(section, keyword)
1987 CALL keyword_release(keyword)
1988
1989 CALL keyword_create( &
1990 keyword, __location__, &
1991 name="K_MESH_G_FACTOR", &
1992 description="The k-mesh for the Green's function can be chosen to be larger than the k-mesh for "// &
1993 "W (without much higher computational cost). The factor given here multiplies the mesh for W to obtain "// &
1994 "the k-mesh for G. Example: factor 4, k-mesh for W: 4x4x1 -> k-mesh for G: 16x16x1 (z-dir. is "// &
1995 "non-periodic).", &
1996 default_i_val=1)
1997 CALL section_add_keyword(section, keyword)
1998 CALL keyword_release(keyword)
1999
2000 CALL keyword_create( &
2001 keyword, __location__, &
2002 name="MIN_BLOCK_SIZE", &
2003 description="Minimum tensor block size. Adjusting this value may have minor effect on "// &
2004 "performance but default should be good enough.", &
2005 default_i_val=5)
2006 CALL section_add_keyword(section, keyword)
2007 CALL keyword_release(keyword)
2008
2009 CALL keyword_create( &
2010 keyword, __location__, &
2011 name="MIN_BLOCK_SIZE_MO", &
2012 description="Tensor block size for MOs. Only relevant for GW calculations. "// &
2013 "The memory consumption of GW scales as O(MIN_BLOCK_SIZE_MO). It is recommended to "// &
2014 "set this parameter to a smaller number if GW runs out of memory. "// &
2015 "Otherwise the default should not be changed.", &
2016 default_i_val=64)
2017 CALL section_add_keyword(section, keyword)
2018 CALL keyword_release(keyword)
2019
2020 NULLIFY (subsection)
2021 CALL create_low_scaling_cphf(subsection)
2022 CALL section_add_subsection(section, subsection)
2023 CALL section_release(subsection)
2024
2025 END SUBROUTINE
2026
2027! **************************************************************************************************
2028!> \brief ...
2029!> \param section ...
2030! **************************************************************************************************
2031 SUBROUTINE create_wfc_gpw(section)
2032 TYPE(section_type), POINTER :: section
2033
2034 TYPE(keyword_type), POINTER :: keyword
2035
2036 cpassert(.NOT. ASSOCIATED(section))
2037 CALL section_create(section, __location__, name="WFC_GPW", &
2038 description="Parameters for the GPW approach in Wavefunction-based Correlation methods", &
2039 n_keywords=5, n_subsections=0, repeats=.false.)
2040
2041 NULLIFY (keyword)
2042 CALL keyword_create(keyword, __location__, name="EPS_GRID", &
2043 description="Determines a threshold for the GPW based integration", &
2044 usage="EPS_GRID 1.0E-9 ", type_of_var=real_t, &
2045 default_r_val=1.0e-8_dp)
2046 CALL section_add_keyword(section, keyword)
2047 CALL keyword_release(keyword)
2048
2049 CALL keyword_create( &
2050 keyword, __location__, name="EPS_FILTER", &
2051 description="Determines a threshold for the DBCSR based multiply (usually 10 times smaller than EPS_GRID). "// &
2052 "Normally, this EPS_FILTER determines accuracy and timing of cubic-scaling RPA calculation.", &
2053 usage="EPS_FILTER 1.0E-10 ", type_of_var=real_t, &
2054 default_r_val=1.0e-9_dp)
2055 CALL section_add_keyword(section, keyword)
2056 CALL keyword_release(keyword)
2057
2058 CALL keyword_create(keyword, __location__, name="CUTOFF", &
2059 description="The cutoff of the finest grid level in the MP2 gpw integration.", &
2060 usage="CUTOFF 300", type_of_var=real_t, &
2061 default_r_val=300.0_dp)
2062 CALL section_add_keyword(section, keyword)
2063 CALL keyword_release(keyword)
2064
2065 CALL keyword_create(keyword, __location__, name="REL_CUTOFF", &
2066 variants=(/"RELATIVE_CUTOFF"/), &
2067 description="Determines the grid at which a Gaussian is mapped.", &
2068 usage="REL_CUTOFF 50", type_of_var=real_t, &
2069 default_r_val=50.0_dp)
2070 CALL section_add_keyword(section, keyword)
2071 CALL keyword_release(keyword)
2072
2073 CALL keyword_create(keyword, __location__, name="PRINT_LEVEL", &
2074 variants=(/"IOLEVEL"/), &
2075 description="How much output is written by the individual groups.", &
2076 usage="PRINT_LEVEL HIGH", &
2077 default_i_val=silent_print_level, enum_c_vals= &
2078 s2a("SILENT", "LOW", "MEDIUM", "HIGH", "DEBUG"), &
2079 enum_desc=s2a("Almost no output", &
2080 "Little output", "Quite some output", "Lots of output", &
2081 "Everything is written out, useful for debugging purposes only"), &
2084 CALL section_add_keyword(section, keyword)
2085 CALL keyword_release(keyword)
2086
2087 CALL keyword_create( &
2088 keyword, __location__, name="EPS_PGF_ORB_S", &
2089 description="Screening for overlap matrix in RI. Usually, it is best to choose this parameter "// &
2090 "to be very small since the inversion of overlap matrix might be ill-conditioned.", &
2091 usage="EPS_PGF_ORB_S 1.0E-10 ", type_of_var=real_t, &
2092 default_r_val=1.0e-10_dp)
2093 CALL section_add_keyword(section, keyword)
2094 CALL keyword_release(keyword)
2095
2096 END SUBROUTINE create_wfc_gpw
2097
2098! **************************************************************************************************
2099!> \brief ...
2100!> \param section ...
2101! **************************************************************************************************
2102 SUBROUTINE create_cphf(section)
2103 TYPE(section_type), POINTER :: section
2104
2105 TYPE(keyword_type), POINTER :: keyword
2106
2107 cpassert(.NOT. ASSOCIATED(section))
2108 CALL section_create( &
2109 section, __location__, name="CPHF", &
2110 description="Parameters influencing the solution of the Z-vector equations in MP2 gradients calculations.", &
2111 n_keywords=2, n_subsections=0, repeats=.false., &
2112 citations=(/delben2013/))
2113
2114 NULLIFY (keyword)
2115
2116 CALL keyword_create(keyword, __location__, name="MAX_ITER", &
2117 variants=(/"MAX_NUM_ITER"/), &
2118 description="Maximum number of iterations allowed for the solution of the Z-vector equations.", &
2119 usage="MAX_ITER 50", &
2120 default_i_val=30)
2121 CALL section_add_keyword(section, keyword)
2122 CALL keyword_release(keyword)
2123
2124 CALL keyword_create(keyword, __location__, name="RESTART_EVERY", &
2125 description="Restart iteration every given number of steps.", &
2126 usage="RESTART_EVERY 5", &
2127 default_i_val=5)
2128 CALL section_add_keyword(section, keyword)
2129 CALL keyword_release(keyword)
2130
2131 CALL keyword_create(keyword, __location__, name="SOLVER_METHOD", &
2132 description="Chose solver of the z-vector equations.", &
2133 usage="SOLVER_METHOD POPLE", enum_c_vals= &
2134 s2a("POPLE", "CG", "RICHARDSON", "SD"), &
2135 enum_desc=s2a("Pople's method (Default).", &
2136 "Conjugated gradient method (equivalent to Pople).", &
2137 "Richardson iteration", &
2138 "Steepest Descent iteration"), &
2140 default_i_val=z_solver_pople)
2141 CALL section_add_keyword(section, keyword)
2142 CALL keyword_release(keyword)
2143
2144 CALL keyword_create(keyword, __location__, name="EPS_CONV", &
2145 description="Convergence threshold for the solution of the Z-vector equations. "// &
2146 "The Z-vector equations have the form of a linear system of equations Ax=b, "// &
2147 "convergence is achieved when |Ax-b|<=EPS_CONV.", &
2148 usage="EPS_CONV 1.0E-6", type_of_var=real_t, &
2149 default_r_val=1.0e-4_dp)
2150 CALL section_add_keyword(section, keyword)
2151 CALL keyword_release(keyword)
2152
2153 CALL keyword_create(keyword, __location__, name="SCALE_STEP_SIZE", &
2154 description="Scaling factor of each step.", &
2155 usage="SCALE_STEP_SIZE 1.0", &
2156 default_r_val=1.0_dp)
2157 CALL section_add_keyword(section, keyword)
2158 CALL keyword_release(keyword)
2159
2160 CALL keyword_create(keyword, __location__, name="ENFORCE_DECREASE", &
2161 description="Restarts if residual does not decrease.", &
2162 usage="ENFORCE_DECREASE T", &
2163 lone_keyword_l_val=.true., &
2164 default_l_val=.false.)
2165 CALL section_add_keyword(section, keyword)
2166 CALL keyword_release(keyword)
2167
2168 CALL keyword_create(keyword, __location__, name="DO_POLAK_RIBIERE", &
2169 description="Use a Polak-Ribiere update of the search vector in CG instead of the Fletcher "// &
2170 "Reeves update. Improves the convergence with modified step sizes. "// &
2171 "Ignored with other methods than CG.", &
2172 usage="DO_POLAK_RIBIERE T", &
2173 lone_keyword_l_val=.true., &
2174 default_l_val=.false.)
2175 CALL section_add_keyword(section, keyword)
2176 CALL keyword_release(keyword)
2177
2178 CALL keyword_create(keyword, __location__, name="RECALC_RESIDUAL", &
2179 description="Recalculates residual in every step.", &
2180 usage="RECALC_RESIDUAL T", &
2181 lone_keyword_l_val=.true., &
2182 default_l_val=.false.)
2183 CALL section_add_keyword(section, keyword)
2184 CALL keyword_release(keyword)
2185
2186 END SUBROUTINE create_cphf
2187
2188! **************************************************************************************************
2189!> \brief ...
2190!> \param section ...
2191! **************************************************************************************************
2192 SUBROUTINE create_low_scaling_cphf(section)
2193 TYPE(section_type), POINTER :: section
2194
2195 TYPE(keyword_type), POINTER :: keyword
2196
2197 NULLIFY (keyword)
2198
2199 cpassert(.NOT. ASSOCIATED(section))
2200 CALL section_create(section, __location__, name="CPHF", &
2201 description="Parameters influencing the solution of the Z-vector equations "// &
2202 "in low-scaling Laplace-SOS-MP2 gradients calculations.", &
2203 n_keywords=5, n_subsections=0, repeats=.false.)
2204
2205 CALL keyword_create(keyword, __location__, name="EPS_CONV", &
2206 description="Target accuracy for Z-vector euation solution.", &
2207 usage="EPS_CONV 1.e-6", default_r_val=1.e-6_dp)
2208 CALL section_add_keyword(section, keyword)
2209 CALL keyword_release(keyword)
2210
2211 CALL keyword_create(keyword, __location__, name="MAX_ITER", &
2212 description="Maximum number of conjugate gradient iteration to be performed for one optimization.", &
2213 usage="MAX_ITER 200", default_i_val=50)
2214 CALL section_add_keyword(section, keyword)
2215 CALL keyword_release(keyword)
2216
2217 CALL keyword_create( &
2218 keyword, __location__, name="PRECONDITIONER", &
2219 description="Type of preconditioner to be used with all minimization schemes. "// &
2220 "They differ in effectiveness, cost of construction, cost of application. "// &
2221 "Properly preconditioned minimization can be orders of magnitude faster than doing nothing.", &
2222 usage="PRECONDITIONER FULL_ALL", &
2223 default_i_val=ot_precond_full_all, &
2224 enum_c_vals=s2a("FULL_ALL", "FULL_SINGLE_INVERSE", "FULL_SINGLE", "FULL_KINETIC", "FULL_S_INVERSE", &
2225 "NONE"), &
2226 enum_desc=s2a("Most effective state selective preconditioner based on diagonalization, "// &
2227 "requires the ENERGY_GAP parameter to be an underestimate of the HOMO-LUMO gap. "// &
2228 "This preconditioner is recommended for almost all systems, except very large systems where "// &
2229 "make_preconditioner would dominate the total computational cost.", &
2230 "Based on H-eS cholesky inversion, similar to FULL_SINGLE in preconditioning efficiency "// &
2231 "but cheaper to construct, "// &
2232 "might be somewhat less robust. Recommended for large systems.", &
2233 "Based on H-eS diagonalisation, not as good as FULL_ALL, but somewhat cheaper to apply. ", &
2234 "Cholesky inversion of S and T, fast construction, robust, and relatively good, "// &
2235 "use for very large systems.", &
2236 "Cholesky inversion of S, not as good as FULL_KINETIC, yet equally expensive.", &
2237 "skip preconditioning"), &
2240 CALL section_add_keyword(section, keyword)
2241 CALL keyword_release(keyword)
2242
2243 CALL keyword_create(keyword, __location__, name="ENERGY_GAP", &
2244 description="Energy gap estimate [a.u.] for preconditioning", &
2245 usage="ENERGY_GAP 0.1", &
2246 default_r_val=0.2_dp)
2247 CALL section_add_keyword(section, keyword)
2248 CALL keyword_release(keyword)
2249
2250 END SUBROUTINE create_low_scaling_cphf
2251
2252! **************************************************************************************************
2253!> \brief ...
2254!> \param section ...
2255! **************************************************************************************************
2256 SUBROUTINE create_mp2_potential(section)
2257 TYPE(section_type), POINTER :: section
2258
2259 TYPE(keyword_type), POINTER :: keyword
2260
2261 cpassert(.NOT. ASSOCIATED(section))
2262 CALL section_create(section, __location__, name="INTERACTION_POTENTIAL", &
2263 description="Parameters the interaction potential in computing the biel integrals", &
2264 n_keywords=4, n_subsections=0, repeats=.false.)
2265
2266 NULLIFY (keyword)
2267 CALL keyword_create( &
2268 keyword, __location__, &
2269 name="POTENTIAL_TYPE", &
2270 description="Which interaction potential should be used "// &
2271 "(Coulomb, TShPSC operator).", &
2272 usage="POTENTIAL_TYPE TSHPSC", &
2273 enum_c_vals=s2a("COULOMB", "TShPSC", "LONGRANGE", "SHORTRANGE", "TRUNCATED", "MIX_CL", "IDENTITY"), &
2274 enum_i_vals=(/do_potential_coulomb, &
2280 do_potential_id/), &
2281 enum_desc=s2a("Coulomb potential: 1/r", &
2282 "| Range | TShPSC |"//newline// &
2283 "| ----- | ------ |"//newline// &
2284 "| $ x \leq R_c $ | $ 1/x - s/R_c $ |"//newline// &
2285 "| $ R_c < x \leq nR_c $ | "// &
2286 "$ (1 - s)/R_c - (x - R_c)/R_c^2 + (x - R_c)^2/R_c^3 - "// &
2287 "(2n^2 - 7n + 9 - 4s)(x - R_c)^3/(R_c^4(n^2 - 2n + 1)(n - 1)) + "// &
2288 "(6-3s - 4n + n^2)(x - R_c)^4/(R_c^5(n^4 - 4n^3 + 6n^2 - 4n + 1)) $ "// &
2289 "(4th order polynomial) | "//newline// &
2290 "| $ x > nR_c $ | $ 0 $ | "//newline, &
2291 "Longrange Coulomb potential: $ \operatorname{erf}(wr)/r $", &
2292 "Shortrange Coulomb potential: $ \operatorname{erfc}(wr)/r $", &
2293 "Truncated Coulomb potential", &
2294 "Mixed Coulomb/Longrange Coulomb potential", &
2295 "Delta potential"), &
2296 default_i_val=do_potential_coulomb)
2297 CALL section_add_keyword(section, keyword)
2298 CALL keyword_release(keyword)
2299
2300 CALL keyword_create(keyword, __location__, name="TRUNCATION_RADIUS", &
2301 variants=(/"CUTOFF_RADIUS"/), &
2302 description="Determines truncation radius for the truncated potentials. "// &
2303 "Only valid when doing truncated calculations", &
2304 usage="TRUNCATION_RADIUS 10.0", type_of_var=real_t, &
2305 default_r_val=10.0_dp, &
2306 unit_str="angstrom")
2307 CALL section_add_keyword(section, keyword)
2308 CALL keyword_release(keyword)
2309
2310 CALL keyword_create( &
2311 keyword, __location__, &
2312 name="POTENTIAL_DATA", &
2313 variants=s2a("TShPSC_DATA", "T_C_G_DATA"), &
2314 description="Location of the file TShPSC.dat or t_c_g.dat that contains the data for the "// &
2315 "evaluation of the evaluation of the truncated potentials", &
2316 usage="TShPSC_DATA t_sh_p_s_c.dat", &
2317 default_c_val="t_sh_p_s_c.dat")
2318 CALL section_add_keyword(section, keyword)
2319 CALL keyword_release(keyword)
2320
2321 CALL keyword_create( &
2322 keyword, __location__, &
2323 name="OMEGA", &
2324 description="Range separation parameter for the longrange or shortrange potential. "// &
2325 "Only valid when longrange or shortrange potential is requested.", &
2326 usage="OMEGA 0.5", type_of_var=real_t, &
2327 default_r_val=0.5_dp)
2328 CALL section_add_keyword(section, keyword)
2329 CALL keyword_release(keyword)
2330
2331 CALL keyword_create( &
2332 keyword, __location__, &
2333 name="SCALE_COULOMB", &
2334 description="Scaling factor of (truncated) Coulomb potential in mixed (truncated) Coulomb/Longrange potential. "// &
2335 "Only valid when mixed potential is requested.", &
2336 usage="SCALE_COULOMB 0.5", type_of_var=real_t, &
2337 default_r_val=1.0_dp)
2338 CALL section_add_keyword(section, keyword)
2339 CALL keyword_release(keyword)
2340
2341 CALL keyword_create( &
2342 keyword, __location__, &
2343 name="SCALE_LONGRANGE", &
2344 description="Scaling factor of longrange Coulomb potential in mixed (truncated) Coulomb/Longrange potential. "// &
2345 "Only valid when mixed potential is requested.", &
2346 usage="SCALE_LONGRANGE 0.5", type_of_var=real_t, &
2347 default_r_val=1.0_dp)
2348 CALL section_add_keyword(section, keyword)
2349 CALL keyword_release(keyword)
2350
2351 END SUBROUTINE create_mp2_potential
2352
2353! **************************************************************************************************
2354!> \brief ...
2355!> \param section ...
2356! **************************************************************************************************
2357 SUBROUTINE create_ri_section(section)
2358 TYPE(section_type), POINTER :: section
2359
2360 TYPE(keyword_type), POINTER :: keyword
2361 TYPE(section_type), POINTER :: subsection
2362
2363 cpassert(.NOT. ASSOCIATED(section))
2364 CALL section_create(section, __location__, name="RI", &
2365 description="Parameters influencing resolution of the identity (RI) that is "// &
2366 "used in RI-MP2, RI-RPA, RI-SOS-MP2 and GW (inside RI-RPA).", &
2367 n_keywords=6, n_subsections=2, repeats=.false.)
2368
2369 NULLIFY (subsection)
2370 CALL create_ri_metric_section(subsection)
2371 CALL section_add_subsection(section, subsection)
2372 CALL section_release(subsection)
2373
2374 CALL create_opt_ri_basis(subsection)
2375 CALL section_add_subsection(section, subsection)
2376 CALL section_release(subsection)
2377
2378 NULLIFY (keyword)
2379 CALL keyword_create( &
2380 keyword, __location__, &
2381 name="ROW_BLOCK", &
2382 variants=(/"ROW_BLOCK_SIZE"/), &
2383 description="Size of the row block used in the SCALAPACK block cyclic data distribution. "// &
2384 "Default is (ROW_BLOCK=-1) is automatic. "// &
2385 "A proper choice can speedup the parallel matrix multiplication in the case of RI-RPA and RI-SOS-MP2-Laplace.", &
2386 usage="ROW_BLOCK 512", &
2387 default_i_val=-1)
2388 CALL section_add_keyword(section, keyword)
2389 CALL keyword_release(keyword)
2390
2391 CALL keyword_create( &
2392 keyword, __location__, &
2393 name="COL_BLOCK", &
2394 variants=(/"COL_BLOCK_SIZE"/), &
2395 description="Size of the column block used in the SCALAPACK block cyclic data distribution. "// &
2396 "Default is (COL_BLOCK=-1) is automatic. "// &
2397 "A proper choice can speedup the parallel matrix multiplication in the case of RI-RPA and RI-SOS-MP2-Laplace.", &
2398 usage="COL_BLOCK 512", &
2399 default_i_val=-1)
2400 CALL section_add_keyword(section, keyword)
2401 CALL keyword_release(keyword)
2402
2403 CALL keyword_create( &
2404 keyword, __location__, &
2405 name="CALC_COND_NUM", &
2406 variants=(/"CALC_CONDITION_NUMBER"/), &
2407 description="Calculate the condition number of the (P|Q) matrix for the RI methods.", &
2408 usage="CALC_COND_NUM", &
2409 default_l_val=.false., &
2410 lone_keyword_l_val=.true.)
2411 CALL section_add_keyword(section, keyword)
2412 CALL keyword_release(keyword)
2413
2414 CALL keyword_create(keyword, __location__, name="DO_SVD", &
2415 description="Wether to perform a singular value decomposition instead of the Cholesky decomposition "// &
2416 "of the potential operator in the RI basis. Computationally expensive but numerically more stable. "// &
2417 "It reduces the computational costs of some subsequent steps. Recommended when a longrange Coulomb "// &
2418 "potential is employed.", &
2419 usage="DO_SVD .TRUE.", &
2420 default_l_val=.false., lone_keyword_l_val=.true.)
2421 CALL section_add_keyword(section, keyword)
2422 CALL keyword_release(keyword)
2423
2424 CALL keyword_create(keyword, __location__, name="EPS_SVD", &
2425 description="Determines the upper bound of eigenvectors to be removed during the SVD (see DO_SVD).", &
2426 usage="EPS_SVD 1E-5", &
2427 default_r_val=0.0_dp)
2428 CALL section_add_keyword(section, keyword)
2429 CALL keyword_release(keyword)
2430
2431 CALL keyword_create(keyword, __location__, name="ERI_BLKSIZE", &
2432 description="block sizes for tensors (only used if ERI_METHOD=MME). First value "// &
2433 "is the block size for ORB basis, second value is the block size for RI_AUX basis.", &
2434 usage="ERI_BLKSIZE", &
2435 n_var=2, &
2436 default_i_vals=(/4, 16/))
2437 CALL section_add_keyword(section, keyword)
2438 CALL keyword_release(keyword)
2439
2440 END SUBROUTINE create_ri_section
2441
2442! **************************************************************************************************
2443!> \brief ...
2444!> \param section ...
2445! **************************************************************************************************
2446 SUBROUTINE create_integrals_section(section)
2447 TYPE(section_type), POINTER :: section
2448
2449 TYPE(keyword_type), POINTER :: keyword
2450 TYPE(section_type), POINTER :: subsection
2451
2452 cpassert(.NOT. ASSOCIATED(section))
2453 CALL section_create(section, __location__, name="INTEGRALS", &
2454 description="Parameters controlling how to compute integrals that are needed "// &
2455 "in MP2, RI-MP2, RI-RPA, RI-SOS-MP2 and GW (inside RI-RPA).", &
2456 n_keywords=2, n_subsections=3, repeats=.false.)
2457
2458 NULLIFY (subsection)
2459 CALL create_eri_mme_section(subsection)
2460 CALL section_add_subsection(section, subsection)
2461 CALL section_release(subsection)
2462
2463 CALL create_wfc_gpw(subsection)
2464 CALL section_add_subsection(section, subsection)
2465 CALL section_release(subsection)
2466
2467 CALL create_mp2_potential(subsection)
2468 CALL section_add_subsection(section, subsection)
2469 CALL section_release(subsection)
2470
2471 NULLIFY (keyword)
2472 CALL keyword_create(keyword, __location__, name="ERI_METHOD", &
2473 description="Method for calculating periodic electron repulsion integrals "// &
2474 "(MME method is faster but experimental, forces not yet implemented). "// &
2475 "Obara-Saika (OS) for the Coulomb operator can only be used for non-periodic calculations.", &
2476 usage="ERI_METHOD MME", &
2477 enum_c_vals=s2a("DEFAULT", "GPW", "MME", "OS"), &
2478 enum_i_vals=(/eri_default, do_eri_gpw, do_eri_mme, do_eri_os/), &
2479 enum_desc=s2a("Use default ERI method (for periodic systems: GPW, for molecules: OS, "// &
2480 "for MP2 and RI-MP2: GPW in any case).", &
2481 "Uses Gaussian Plane Wave method [DelBen2013].", &
2482 "Uses MiniMax-Ewald method (experimental, ERI_MME subsection, only for fully periodic "// &
2483 "systems with orthorhombic cells).", &
2484 "Use analytical Obara-Saika method."), &
2485 default_i_val=eri_default)
2486 CALL section_add_keyword(section, keyword)
2487 CALL keyword_release(keyword)
2488
2489 CALL keyword_create(keyword, __location__, name="SIZE_LATTICE_SUM", &
2490 description="Size of sum range L. ", &
2491 usage="SIZE_LATTICE_SUM 10", &
2492 default_i_val=5)
2493 CALL section_add_keyword(section, keyword)
2494 CALL keyword_release(keyword)
2495
2496 END SUBROUTINE create_integrals_section
2497
2498! **************************************************************************************************
2499!> \brief ...
2500!> \param section ...
2501! **************************************************************************************************
2502 SUBROUTINE create_ri_metric_section(section)
2503 TYPE(section_type), POINTER :: section
2504
2505 TYPE(keyword_type), POINTER :: keyword
2506
2507 cpassert(.NOT. ASSOCIATED(section))
2508 CALL section_create(section, __location__, name="RI_METRIC", &
2509 description="Sets up RI metric", &
2510 repeats=.false.)
2511
2512 NULLIFY (keyword)
2513 CALL keyword_create( &
2514 keyword, __location__, &
2515 name="POTENTIAL_TYPE", &
2516 description="Decides which operator/metric is used for resolution of the identity (RI).", &
2517 usage="POTENTIAL_TYPE DEFAULT", &
2518 enum_c_vals=s2a("DEFAULT", "COULOMB", "IDENTITY", "LONGRANGE", "SHORTRANGE", "TRUNCATED"), &
2521 enum_desc=s2a("Use Coulomb metric for RI-MP2 and normal-scaling RI-SOS-MP2, RI-RPA and GW. "// &
2522 "Use Overlap metric for low-scaling RI-SOS-MP2, RI-RPA and GW for periodic systems. "// &
2523 "Use truncated Coulomb metric for low-scaling RI-SOS-MP2, RI-RPA and GW for non-periodic systems.", &
2524 "Coulomb metric: 1/r. Recommended for RI-MP2,", &
2525 "Overlap metric: delta(r).", &
2526 "Longrange metric: erf(omega*r)/r. Not recommended with DO_SVD .TRUE.", &
2527 "Shortrange metric: erfc(omega*r)/r", &
2528 "Truncated Coulomb metric: if (r &lt; R_c) 1/r else 0. More "// &
2529 "accurate than IDENTITY for non-periodic systems. Recommended for low-scaling methods."), &
2530 default_i_val=ri_default)
2531 CALL section_add_keyword(section, keyword)
2532 CALL keyword_release(keyword)
2533
2534 NULLIFY (keyword)
2535 CALL keyword_create( &
2536 keyword, __location__, &
2537 name="OMEGA", &
2538 description="The range parameter for the short/long range operator (in 1/a0).", &
2539 usage="OMEGA 0.5", &
2540 default_r_val=0.0_dp)
2541 CALL section_add_keyword(section, keyword)
2542 CALL keyword_release(keyword)
2543
2544 CALL keyword_create(keyword, __location__, name="CUTOFF_RADIUS", &
2545 description="The cutoff radius (in Angstrom) for the truncated Coulomb operator.", &
2546 usage="CUTOFF_RADIUS 3.0", default_r_val=cp_unit_to_cp2k(value=3.0_dp, unit_str="angstrom"), &
2547 type_of_var=real_t, unit_str="angstrom")
2548 CALL section_add_keyword(section, keyword)
2549 CALL keyword_release(keyword)
2550
2551 CALL keyword_create( &
2552 keyword, __location__, &
2553 name="T_C_G_DATA", &
2554 description="Location of the file t_c_g.dat that contains the data for the "// &
2555 "evaluation of the truncated gamma function ", &
2556 default_c_val="t_c_g.dat")
2557 CALL section_add_keyword(section, keyword)
2558 CALL keyword_release(keyword)
2559
2560 CALL keyword_create(keyword, __location__, name="EPS_RANGE", &
2561 description="The threshold to determine the effective range of the short range "// &
2562 "RI metric: erfc(omega*eff_range)/eff_range = EPS_RANGE", &
2563 default_r_val=1.0e-08_dp, &
2564 repeats=.false.)
2565 CALL section_add_keyword(section, keyword)
2566 CALL keyword_release(keyword)
2567
2568 END SUBROUTINE create_ri_metric_section
2569
2570END MODULE input_cp2k_mp2
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public stein2024
integer, save, public stein2022
integer, save, public wilhelm2016b
integer, save, public delben2015
integer, save, public wilhelm2016a
integer, save, public wilhelm2018
integer, save, public rybkin2016
integer, save, public delben2013
integer, save, public delben2012
integer, save, public delben2015b
integer, save, public wilhelm2017
integer, save, public bussy2023
integer, save, public bates2013
Interface to Minimax-Ewald method for periodic ERI's to be used in CP2K.
subroutine, public create_eri_mme_section(section, default_n_minimax)
Create main input section.
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public debug_print_level
integer, parameter, public low_print_level
integer, parameter, public medium_print_level
integer, parameter, public high_print_level
integer, parameter, public add_last_numeric
integer, parameter, public silent_print_level
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
unit conversion facility
Definition cp_units.F:30
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
Definition cp_units.F:1150
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public evgw
integer, parameter, public rpa_exchange_none
integer, parameter, public wfc_mm_style_syrk
integer, parameter, public sigma_pbe_s2
integer, parameter, public soc_lda
integer, parameter, public bse_screening_tdhf
integer, parameter, public bse_iterdiag
integer, parameter, public gw_pade_approx
integer, parameter, public z_solver_pople
integer, parameter, public sigma_none
integer, parameter, public bse_iter_both_cond
integer, parameter, public sigma_pbe0_s2
integer, parameter, public do_eri_os
integer, parameter, public gw_skip_for_regtest
integer, parameter, public mp2_method_direct
integer, parameter, public rpa_exchange_sosex
integer, parameter, public kp_weights_w_auto
integer, parameter, public kp_weights_w_uniform
integer, parameter, public bse_iter_res_cond
integer, parameter, public do_eri_mme
integer, parameter, public sigma_pbe0_s1
integer, parameter, public ri_rpa_g0w0_crossing_bisection
integer, parameter, public wfc_mm_style_gemm
integer, parameter, public ot_precond_full_kinetic
integer, parameter, public gw_print_exx
integer, parameter, public do_potential_mix_cl
integer, parameter, public bse_singlet
integer, parameter, public z_solver_cg
integer, parameter, public bse_fulldiag
integer, parameter, public bse_triplet
integer, parameter, public bse_screening_w0
integer, parameter, public ot_precond_full_single
integer, parameter, public sigma_pbe_s1
integer, parameter, public bse_tda
integer, parameter, public bse_both
integer, parameter, public do_potential_truncated
integer, parameter, public bse_iter_en_cond
integer, parameter, public z_solver_sd
integer, parameter, public ot_precond_none
integer, parameter, public bse_screening_alpha
integer, parameter, public mp2_method_gpw
integer, parameter, public g0w0
integer, parameter, public ot_precond_full_single_inverse
integer, parameter, public bse_screening_rpa
integer, parameter, public do_potential_id
integer, parameter, public mp2_method_none
integer, parameter, public soc_pbe
integer, parameter, public gw_read_exx
integer, parameter, public eri_default
integer, parameter, public ri_default
integer, parameter, public evgw0
integer, parameter, public bse_abba
integer, parameter, public do_potential_coulomb
integer, parameter, public gaussian
integer, parameter, public ri_rpa_g0w0_crossing_z_shot
integer, parameter, public rpa_exchange_axk
integer, parameter, public do_potential_short
integer, parameter, public z_solver_richardson
integer, parameter, public gw_no_print_exx
integer, parameter, public kp_weights_w_tailored
integer, parameter, public ot_precond_s_inverse
integer, parameter, public do_potential_long
integer, parameter, public gw_two_pole_model
integer, parameter, public do_eri_gpw
integer, parameter, public do_potential_tshpsc
integer, parameter, public ri_rpa_g0w0_crossing_newton
integer, parameter, public numerical
integer, parameter, public ot_precond_full_all
integer, parameter, public soc_none
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
function that build the kpoints section of the input
subroutine, public create_kpoint_set_section(section, section_name)
...
input section for MP2
subroutine, public create_mp2_section(section)
creates the input section for the mp2 part
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, deprecation_notice)
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 logical_t
integer, parameter, public char_t
integer, parameter, public integer_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Utilities for string manipulations.
character(len=1), parameter, public newline
represent a keyword in the input
represent a section of the input file