(git:ed6f26b)
Loading...
Searching...
No Matches
input_cp2k_properties_dft.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 function that build the dft section of the input
10!> \par History
11!> 01.2013 moved out of input_cp2k_dft [MI]
12!> \author MI
13! **************************************************************************************************
15 USE bibliography, ONLY: futera2017, &
17 kondov2007, &
18 luber2014, &
30 USE cp_units, ONLY: cp_unit_to_cp2k
31 USE input_constants, ONLY: &
59 USE input_val_types, ONLY: char_t, &
60 integer_t, &
61 lchar_t, &
62 logical_t, &
63 real_t
64 USE kinds, ONLY: dp
65 USE string_utilities, ONLY: s2a
66#include "./base/base_uses.f90"
67
68 IMPLICIT NONE
69 PRIVATE
70
71 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
72 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_properties_dft'
73
75
76CONTAINS
77
78! **************************************************************************************************
79!> \brief Create the PROPERTIES section
80!> \param section the section to create
81!> \author teo
82! **************************************************************************************************
83 SUBROUTINE create_properties_section(section)
84 TYPE(section_type), POINTER :: section
85
86 TYPE(keyword_type), POINTER :: keyword
87 TYPE(section_type), POINTER :: subsection
88
89 cpassert(.NOT. ASSOCIATED(section))
90 CALL section_create(section, __location__, name="PROPERTIES", &
91 description="This section is used to set up the PROPERTIES calculation.", &
92 n_keywords=0, n_subsections=6, repeats=.false.)
93
94 NULLIFY (subsection, keyword)
95
96 CALL create_linres_section(subsection, create_subsections=.true.)
97 CALL section_add_subsection(section, subsection)
98 CALL section_release(subsection)
99
100 CALL create_et_coupling_section(subsection)
101 CALL section_add_subsection(section, subsection)
102 CALL section_release(subsection)
103
104 CALL create_resp_section(subsection)
105 CALL section_add_subsection(section, subsection)
106 CALL section_release(subsection)
107
108 CALL create_atprop_section(subsection)
109 CALL section_add_subsection(section, subsection)
110 CALL section_release(subsection)
111
112 CALL cp_print_key_section_create(subsection, __location__, name="FIT_CHARGE", &
113 description="This section is used to print the density derived atomic point charges. "// &
114 "The fit of the charges is controlled through the DENSITY_FITTING section", &
115 print_level=high_print_level, filename="__STD_OUT__")
116 CALL keyword_create(keyword, __location__, name="TYPE_OF_DENSITY", &
117 description="Specifies the type of density used for the fitting", &
118 usage="TYPE_OF_DENSITY (FULL|SPIN)", &
119 enum_c_vals=s2a("FULL", "SPIN"), &
120 enum_i_vals=(/do_full_density, do_spin_density/), &
121 enum_desc=s2a("Full density", "Spin density"), &
122 default_i_val=do_full_density)
123 CALL section_add_keyword(subsection, keyword)
124 CALL keyword_release(keyword)
125 CALL section_add_subsection(section, subsection)
126 CALL section_release(subsection)
127
128 CALL create_tddfpt2_section(subsection)
129 CALL section_add_subsection(section, subsection)
130 CALL section_release(subsection)
131
132 CALL create_bandstructure_section(subsection)
133 CALL section_add_subsection(section, subsection)
134 CALL section_release(subsection)
135
136 CALL create_tipscan_section(subsection)
137 CALL section_add_subsection(section, subsection)
138 CALL section_release(subsection)
139
140 END SUBROUTINE create_properties_section
141
142! **************************************************************************************************
143!> \brief creates the input structure used to activate
144!> a linear response calculation
145!> Available properties : none
146!> \param section the section to create
147!> \param create_subsections indicates whether or not subsections should be created
148!> \param default_set_tdlr default parameters to be used if called from TDDFPT
149!> \author MI
150! **************************************************************************************************
151 SUBROUTINE create_linres_section(section, create_subsections, default_set_tdlr)
152 TYPE(section_type), POINTER :: section
153 LOGICAL, INTENT(in) :: create_subsections
154 LOGICAL, INTENT(IN), OPTIONAL :: default_set_tdlr
155
156 INTEGER :: def_max_iter, def_precond
157 REAL(kind=dp) :: def_egap, def_eps, def_eps_filter
158 TYPE(keyword_type), POINTER :: keyword
159 TYPE(section_type), POINTER :: print_key, subsection
160
161 NULLIFY (keyword, print_key)
162
163 IF (PRESENT(default_set_tdlr)) THEN
164 def_egap = 0.02_dp
165 def_eps = 1.0e-10_dp
166 def_eps_filter = 1.0e-15_dp
167 def_max_iter = 100
169 ELSE
170 def_egap = 0.2_dp
171 def_eps = 1.e-6_dp
172 def_eps_filter = 0.0_dp
173 def_max_iter = 50
174 def_precond = ot_precond_none
175 END IF
176
177 cpassert(.NOT. ASSOCIATED(section))
178 CALL section_create(section, __location__, name="linres", &
179 description="The linear response is used to calculate one of the "// &
180 "following properties: nmr, epr, raman, ... ", &
181 n_keywords=5, n_subsections=2, repeats=.false., &
182 citations=(/putrino2000/))
183
184 CALL keyword_create(keyword, __location__, name="EPS", &
185 description="target accuracy for the convergence of the conjugate gradient.", &
186 usage="EPS 1.e-6", default_r_val=def_eps)
187 CALL section_add_keyword(section, keyword)
188 CALL keyword_release(keyword)
189
190 CALL keyword_create(keyword, __location__, name="EPS_FILTER", &
191 description="Filter threshold for response density matrix.", &
192 usage="EPS_FILTER 1.e-8", default_r_val=def_eps_filter)
193 CALL section_add_keyword(section, keyword)
194 CALL keyword_release(keyword)
195
196 CALL keyword_create(keyword, __location__, name="MAX_ITER", &
197 description="Maximum number of conjugate gradient iteration to be performed for one optimization.", &
198 usage="MAX_ITER 200", default_i_val=def_max_iter)
199 CALL section_add_keyword(section, keyword)
200 CALL keyword_release(keyword)
201
202 CALL keyword_create(keyword, __location__, name="RESTART_EVERY", &
203 description="Restart the conjugate gradient after the specified number of iterations.", &
204 usage="RESTART_EVERY 200", default_i_val=50)
205 CALL section_add_keyword(section, keyword)
206 CALL keyword_release(keyword)
207
208 CALL keyword_create( &
209 keyword, __location__, name="PRECONDITIONER", &
210 description="Type of preconditioner to be used with all minimization schemes. "// &
211 "They differ in effectiveness, cost of construction, cost of application. "// &
212 "Properly preconditioned minimization can be orders of magnitude faster than doing nothing.", &
213 usage="PRECONDITIONER FULL_ALL", &
214 default_i_val=def_precond, &
215 enum_c_vals=s2a("FULL_ALL", "FULL_SINGLE_INVERSE", "FULL_SINGLE", "FULL_KINETIC", "FULL_S_INVERSE", &
216 "NONE"), &
217 enum_desc=s2a("Most effective state selective preconditioner based on diagonalization, "// &
218 "requires the ENERGY_GAP parameter to be an underestimate of the HOMO-LUMO gap. "// &
219 "This preconditioner is recommended for almost all systems, except very large systems where "// &
220 "make_preconditioner would dominate the total computational cost.", &
221 "Based on H-eS cholesky inversion, similar to FULL_SINGLE in preconditioning efficiency "// &
222 "but cheaper to construct, "// &
223 "might be somewhat less robust. Recommended for large systems.", &
224 "Based on H-eS diagonalisation, not as good as FULL_ALL, but somewhat cheaper to apply. ", &
225 "Cholesky inversion of S and T, fast construction, robust, and relatively good, "// &
226 "use for very large systems.", &
227 "Cholesky inversion of S, not as good as FULL_KINETIC, yet equally expensive.", &
228 "skip preconditioning"), &
231 CALL section_add_keyword(section, keyword)
232 CALL keyword_release(keyword)
233
234 CALL keyword_create(keyword, __location__, name="ENERGY_GAP", &
235 description="Energy gap estimate [a.u.] for preconditioning", &
236 usage="ENERGY_GAP 0.1", &
237 default_r_val=def_egap)
238 CALL section_add_keyword(section, keyword)
239 CALL keyword_release(keyword)
240
241 CALL keyword_create(keyword, __location__, name="EVERY_N_STEP", &
242 description="Perform a linear response calculation every N-th step for MD run", &
243 usage="EVERY_N_STEP 50", default_i_val=1)
244 CALL section_add_keyword(section, keyword)
245 CALL keyword_release(keyword)
246
247 CALL keyword_create(keyword, __location__, name="RESTART", &
248 description="Restart the response calculation if the restart file exists", &
249 usage="RESTART", &
250 default_l_val=.false., lone_keyword_l_val=.true.)
251 CALL section_add_keyword(section, keyword)
252 CALL keyword_release(keyword)
253
254 CALL keyword_create(keyword, __location__, name="WFN_RESTART_FILE_NAME", &
255 variants=(/"RESTART_FILE_NAME"/), &
256 description="Root of the file names where to read the response functions from "// &
257 "which to restart the calculation of the linear response", &
258 usage="WFN_RESTART_FILE_NAME <FILENAME>", &
259 type_of_var=lchar_t)
260 CALL section_add_keyword(section, keyword)
261 CALL keyword_release(keyword)
262
263 IF (create_subsections) THEN
264 NULLIFY (subsection)
265
266 CALL create_localize_section(subsection)
267 CALL section_add_subsection(section, subsection)
268 CALL section_release(subsection)
269
270 CALL create_current_section(subsection)
271 CALL section_add_subsection(section, subsection)
272 CALL section_release(subsection)
273
274 CALL create_nmr_section(subsection)
275 CALL section_add_subsection(section, subsection)
276 CALL section_release(subsection)
277
278 CALL create_spin_spin_section(subsection)
279 CALL section_add_subsection(section, subsection)
280 CALL section_release(subsection)
281
282 CALL create_epr_section(subsection)
283 CALL section_add_subsection(section, subsection)
284 CALL section_release(subsection)
285
286 CALL create_polarizability_section(subsection)
287 CALL section_add_subsection(section, subsection)
288 CALL section_release(subsection)
289
290 CALL create_dcdr_section(subsection)
291 CALL section_add_subsection(section, subsection)
292 CALL section_release(subsection)
293
294 CALL create_vcd_section(subsection)
295 CALL section_add_subsection(section, subsection)
296 CALL section_release(subsection)
297
298 CALL section_create(subsection, __location__, name="PRINT", &
299 description="printing of information during the linear response calculation", &
300 repeats=.false.)
301
303 print_key, __location__, "program_run_info", &
304 description="Controls the printing of basic iteration information during the LINRES calculation", &
305 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
306 CALL section_add_subsection(subsection, print_key)
307 CALL section_release(print_key)
308
309 CALL cp_print_key_section_create(print_key, __location__, "RESTART", &
310 description="Controls the dumping of restart file of the response wavefunction. "// &
311 "For each set of response functions, i.e. for each perturbation, "// &
312 "one different restart file is dumped. These restart files should be "// &
313 "employed only to restart the same type of LINRES calculation, "// &
314 "i.e. with the same perturbation.", &
315 print_level=low_print_level, common_iter_levels=3, each_iter_names=s2a("ITER"), &
316 add_last=add_last_numeric, each_iter_values=(/3/), filename="")
317 CALL section_add_subsection(subsection, print_key)
318 CALL section_release(print_key)
319
320 CALL section_add_subsection(section, subsection)
321 CALL section_release(subsection)
322
323 END IF
324
325 END SUBROUTINE create_linres_section
326
327! **************************************************************************************************
328!> \brief creates the input structure used to activate
329!> calculation of position perturbation DFPT
330!> \param section ...
331!> \author Sandra Luber, Edward Ditler
332! **************************************************************************************************
333 SUBROUTINE create_dcdr_section(section)
334
335 TYPE(section_type), POINTER :: section
336
337 LOGICAL :: failure
338 TYPE(keyword_type), POINTER :: keyword
339 TYPE(section_type), POINTER :: print_key, subsection
340
341 failure = .false.
342 NULLIFY (keyword, print_key, subsection)
343
344 cpassert(.NOT. ASSOCIATED(section))
345
346 IF (.NOT. failure) THEN
347 CALL section_create(section, __location__, name="DCDR", &
348 description="Compute analytical gradients the dipole moments.", &
349 n_keywords=50, n_subsections=1, repeats=.false.)
350
351 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
352 description="controls the activation of the APT calculation", &
353 usage="&DCDR T", &
354 default_l_val=.false., &
355 lone_keyword_l_val=.true.)
356 CALL section_add_keyword(section, keyword)
357 CALL keyword_release(keyword)
358
359 CALL keyword_create(keyword, __location__, name="LIST_OF_ATOMS", &
360 description="Specifies a list of atoms.", &
361 usage="LIST_OF_ATOMS {integer} {integer} .. {integer}", repeats=.true., &
362 n_var=-1, type_of_var=integer_t)
363 CALL section_add_keyword(section, keyword)
364 CALL keyword_release(keyword)
365
366 CALL keyword_create(keyword, __location__, name="DISTRIBUTED_ORIGIN", &
367 variants=(/"DO_GAUGE"/), &
368 description="Use the distributed origin (DO) gauge?", &
369 usage="DISTRIBUTED_ORIGIN T", &
370 default_l_val=.false., lone_keyword_l_val=.true.)
371 CALL section_add_keyword(section, keyword)
372 CALL keyword_release(keyword)
373
374 CALL keyword_create(keyword, __location__, name="ORBITAL_CENTER", &
375 description="The orbital center.", &
376 usage="ORBITAL_CENTER WANNIER", &
377 default_i_val=current_orb_center_wannier, &
378 enum_c_vals=s2a("WANNIER", "COMMON", "ATOM", "BOX"), &
379 enum_desc=s2a("Use the Wannier centers.", &
380 "Use a common center (works only for an isolate molecule).", &
381 "Use the atoms as center.", &
382 "Boxing."), &
385 CALL section_add_keyword(section, keyword)
386 CALL keyword_release(keyword)
387
388 CALL keyword_create(keyword, __location__, name="REFERENCE", &
389 description="Gauge origin of the velocity gauge factor.", &
390 enum_c_vals=s2a("COM", "COAC", "USER_DEFINED", "ZERO"), &
391 enum_desc=s2a("Use Center of Mass", &
392 "Use Center of Atomic Charges", &
393 "Use User-defined Point", &
394 "Use Origin of Coordinate System"), &
395 enum_i_vals=(/use_mom_ref_com, &
399 default_i_val=use_mom_ref_zero)
400 CALL section_add_keyword(section, keyword)
401 CALL keyword_release(keyword)
402
403 CALL keyword_create(keyword, __location__, name="REFERENCE_POINT", &
404 description="User-defined reference point of the velocity gauge factor.", &
405 usage="REFERENCE_POINT x y z", &
406 repeats=.false., n_var=3, type_of_var=real_t, unit_str='bohr')
407 CALL section_add_keyword(section, keyword)
408 CALL keyword_release(keyword)
409
410 CALL keyword_create(keyword, __location__, name="Z_MATRIX_METHOD", &
411 description="Use Z_matrix method to solve the response equation", &
412 usage="Z_MATRIX_METHOD T", &
413 default_l_val=.false., lone_keyword_l_val=.true.)
414 CALL section_add_keyword(section, keyword)
415 CALL keyword_release(keyword)
416
417 NULLIFY (subsection)
418 CALL section_create(subsection, __location__, name="PRINT", &
419 description="print results of the magnetic dipole moment calculation", &
420 repeats=.false.)
421
422 CALL cp_print_key_section_create(print_key, __location__, "APT", &
423 description="Controls the printing of the electric dipole gradient", &
424 print_level=low_print_level, add_last=add_last_numeric, filename="")
425 CALL section_add_subsection(subsection, print_key)
426 CALL section_release(print_key)
427
428 CALL section_add_subsection(section, subsection)
429 CALL section_release(subsection)
430
431 NULLIFY (subsection)
432 CALL create_interp_section(subsection)
433 CALL section_add_subsection(section, subsection)
434 CALL section_release(subsection)
435
436 END IF
437
438 END SUBROUTINE create_dcdr_section
439
440! **************************************************************************************************
441!> \brief creates the input structure used to activate
442!> calculation of VCD spectra using DFPT
443!> \param section ...
444!> \author Sandra Luber, Tomas Zimmermann, Edward Ditler
445! **************************************************************************************************
446 SUBROUTINE create_vcd_section(section)
447
448 TYPE(section_type), POINTER :: section
449
450 TYPE(keyword_type), POINTER :: keyword
451 TYPE(section_type), POINTER :: print_key, subsection
452
453 NULLIFY (keyword, print_key, subsection)
454
455 cpassert(.NOT. ASSOCIATED(section))
456
457 CALL section_create(section, __location__, name="VCD", &
458 description="Carry out a VCD calculation.", &
459 n_keywords=50, n_subsections=1, repeats=.false.)
460
461 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
462 description="controls the activation of the APT/AAT calculation", &
463 usage="&VCD T", &
464 default_l_val=.false., &
465 lone_keyword_l_val=.true.)
466 CALL section_add_keyword(section, keyword)
467 CALL keyword_release(keyword)
468
469 CALL keyword_create(keyword, __location__, name="LIST_OF_ATOMS", &
470 description="Specifies a list of atoms.", &
471 usage="LIST_OF_ATOMS {integer} {integer} .. {integer}", repeats=.true., &
472 n_var=-1, type_of_var=integer_t)
473 CALL section_add_keyword(section, keyword)
474 CALL keyword_release(keyword)
475
476 CALL keyword_create(keyword, __location__, name="DISTRIBUTED_ORIGIN", &
477 variants=(/"DO_GAUGE"/), &
478 description="Use the distributed origin (DO) gauge?", &
479 usage="DISTRIBUTED_ORIGIN T", &
480 default_l_val=.false., lone_keyword_l_val=.true.)
481 CALL section_add_keyword(section, keyword)
482 CALL keyword_release(keyword)
483
484 CALL keyword_create(keyword, __location__, name="ORIGIN_DEPENDENT_MFP", &
485 description="Use the origin dependent MFP operator.", &
486 usage="ORIGIN_DEPENDENT_MFP T", &
487 default_l_val=.false., lone_keyword_l_val=.true.)
488 CALL section_add_keyword(section, keyword)
489 CALL keyword_release(keyword)
490
491 CALL keyword_create(keyword, __location__, name="ORBITAL_CENTER", &
492 description="The orbital center.", &
493 usage="ORBITAL_CENTER WANNIER", &
494 default_i_val=current_orb_center_wannier, &
495 enum_c_vals=s2a("WANNIER", "COMMON", "ATOM", "BOX"), &
496 enum_desc=s2a("Use the Wannier centers.", &
497 "Use a common center (works only for an isolate molecule).", &
498 "Use the atoms as center.", &
499 "Boxing."), &
502 CALL section_add_keyword(section, keyword)
503 CALL keyword_release(keyword)
504
505 ! The origin of the magnetic dipole operator (r - MAGNETIC_ORIGIN) x momentum
506 CALL keyword_create(keyword, __location__, name="MAGNETIC_ORIGIN", &
507 description="Gauge origin of the magnetic dipole operator.", &
508 enum_c_vals=s2a("COM", "COAC", "USER_DEFINED", "ZERO"), &
509 enum_desc=s2a("Use Center of Mass", &
510 "Use Center of Atomic Charges", &
511 "Use User-defined Point", &
512 "Use Origin of Coordinate System"), &
513 enum_i_vals=(/use_mom_ref_com, &
517 default_i_val=use_mom_ref_zero)
518 CALL section_add_keyword(section, keyword)
519 CALL keyword_release(keyword)
520
521 CALL keyword_create(keyword, __location__, name="MAGNETIC_ORIGIN_REFERENCE", &
522 description="User-defined reference point of the magnetic dipole operator.", &
523 usage="MAGNETIC_ORIGIN_REFERENCE x y z", &
524 repeats=.false., n_var=3, type_of_var=real_t, unit_str='bohr')
525 CALL section_add_keyword(section, keyword)
526 CALL keyword_release(keyword)
527
528 ! The origin of the coordinate system
529 CALL keyword_create(keyword, __location__, name="SPATIAL_ORIGIN", &
530 description="Gauge origin of the velocity gauge factor/spatial origin.", &
531 enum_c_vals=s2a("COM", "COAC", "USER_DEFINED", "ZERO"), &
532 enum_desc=s2a("Use Center of Mass", &
533 "Use Center of Atomic Charges", &
534 "Use User-defined Point", &
535 "Use Origin of Coordinate System"), &
536 enum_i_vals=(/use_mom_ref_com, &
540 default_i_val=use_mom_ref_zero)
541 CALL section_add_keyword(section, keyword)
542 CALL keyword_release(keyword)
543
544 CALL keyword_create(keyword, __location__, name="SPATIAL_ORIGIN_REFERENCE", &
545 description="User-defined reference point of the velocity gauge factor/spatial origin.", &
546 usage="SPATIAL_ORIGIN_REFERENCE x y z", &
547 repeats=.false., n_var=3, type_of_var=real_t, unit_str='bohr')
548 CALL section_add_keyword(section, keyword)
549 CALL keyword_release(keyword)
550
551 NULLIFY (subsection)
552 CALL section_create(subsection, __location__, name="PRINT", &
553 description="print results of the magnetic dipole moment calculation", &
554 repeats=.false.)
555
556 CALL cp_print_key_section_create(print_key, __location__, "VCD", &
557 description="Controls the printing of the APTs and AATs", &
558 print_level=low_print_level, add_last=add_last_numeric, filename="")
559 CALL section_add_subsection(subsection, print_key)
560 CALL section_release(print_key)
561
562 CALL section_add_subsection(section, subsection)
563 CALL section_release(subsection)
564
565 NULLIFY (subsection)
566 CALL create_interp_section(subsection)
567 CALL section_add_subsection(section, subsection)
568 CALL section_release(subsection)
569
570 END SUBROUTINE create_vcd_section
571
572! **************************************************************************************************
573!> \brief creates the input structure used to activate
574!> calculation of induced current DFPT
575!> Available properties : none
576!> \param section the section to create
577!> \author MI/VW
578! **************************************************************************************************
579 SUBROUTINE create_current_section(section)
580 TYPE(section_type), POINTER :: section
581
582 TYPE(keyword_type), POINTER :: keyword
583 TYPE(section_type), POINTER :: print_key, subsection
584
585 NULLIFY (keyword, print_key, subsection)
586
587 cpassert(.NOT. ASSOCIATED(section))
588 CALL section_create(section, __location__, name="current", &
589 description="The induced current density is calculated by DFPT.", &
590 n_keywords=4, n_subsections=1, repeats=.false., &
591 citations=(/sebastiani2001, weber2009/))
592
593 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
594 description="controls the activation of the induced current calculation", &
595 usage="&CURRENT T", &
596 default_l_val=.false., &
597 lone_keyword_l_val=.true.)
598 CALL section_add_keyword(section, keyword)
599 CALL keyword_release(keyword)
600
601 CALL keyword_create(keyword, __location__, name="GAUGE", &
602 description="The gauge used to compute the induced current within GAPW.", &
603 usage="GAUGE R", &
604 default_i_val=current_gauge_r_and_step_func, &
605 enum_c_vals=s2a("R", "R_AND_STEP_FUNCTION", "ATOM"), &
606 enum_desc=s2a("Position gauge (doesnt work well).", &
607 "Position and step function for the soft and the local parts, respectively.", &
608 "Atoms."), &
610 CALL section_add_keyword(section, keyword)
611 CALL keyword_release(keyword)
612
613 CALL keyword_create(keyword, __location__, name="GAUGE_ATOM_RADIUS", &
614 description="Build the gauge=atom using only the atoms within this radius.", &
615 usage="GAUGE_ATOM_RADIUS 10.0", &
616 type_of_var=real_t, &
617 default_r_val=cp_unit_to_cp2k(value=4.0_dp, unit_str="angstrom"), &
618 unit_str="angstrom")
619 CALL section_add_keyword(section, keyword)
620 CALL keyword_release(keyword)
621
622 CALL keyword_create(keyword, __location__, name="USE_OLD_GAUGE_ATOM", &
623 description="Use the old way to compute the gauge.", &
624 usage="USE_OLD_GAUGE_ATOM T", &
625 default_l_val=.true., lone_keyword_l_val=.true.)
626 CALL section_add_keyword(section, keyword)
627 CALL keyword_release(keyword)
628
629 CALL keyword_create(keyword, __location__, name="ORBITAL_CENTER", &
630 description="The orbital center.", &
631 usage="ORBITAL_CENTER WANNIER", &
632 default_i_val=current_orb_center_wannier, &
633 enum_c_vals=s2a("WANNIER", "COMMON", "ATOM", "BOX"), &
634 enum_desc=s2a("Use the Wannier centers.", &
635 "Use a common center (works only for an isolate molecule).", &
636 "Use the atoms as center.", &
637 "Boxing."), &
640 CALL section_add_keyword(section, keyword)
641 CALL keyword_release(keyword)
642
643 CALL keyword_create(keyword, __location__, name="COMMON_CENTER", &
644 description="The common center ", usage="COMMON_CENTER 0.0 1.0 0.0", &
645 n_var=3, default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/), type_of_var=real_t, &
646 unit_str="angstrom")
647 CALL section_add_keyword(section, keyword)
648 CALL keyword_release(keyword)
649
650 CALL keyword_create(keyword, __location__, name="NBOX", &
651 description="How many boxes along each directions ", usage="NBOX 6 6 5", &
652 n_var=3, default_i_vals=(/4, 4, 4/), type_of_var=integer_t)
653 CALL section_add_keyword(section, keyword)
654 CALL keyword_release(keyword)
655
656 CALL keyword_create(keyword, __location__, name="CHI_PBC", &
657 description="Calculate the succeptibility correction to the shift with PBC", &
658 usage="CHI_PBC T", &
659 default_l_val=.false., lone_keyword_l_val=.true.)
660 CALL section_add_keyword(section, keyword)
661 CALL keyword_release(keyword)
662
663 CALL keyword_create(keyword, __location__, name="FORCE_NO_FULL", &
664 description="Avoid the calculation of the state dependent perturbation term, "// &
665 "even if the orbital centers are set at Wannier centers or at Atom centers", &
666 usage="FORCE_NO_FULL T", &
667 default_l_val=.false., lone_keyword_l_val=.true.)
668 CALL section_add_keyword(section, keyword)
669 CALL keyword_release(keyword)
670
671 CALL keyword_create(keyword, __location__, name="SELECTED_STATES_ON_ATOM_LIST", &
672 description="Indexes of the atoms for selecting"// &
673 " the states to be used for the response calculations.", &
674 usage="SELECTED_STATES_ON_ATOM_LIST 1 2 10", &
675 n_var=-1, type_of_var=integer_t, repeats=.true.)
676 CALL section_add_keyword(section, keyword)
677 CALL keyword_release(keyword)
678
679 CALL keyword_create(keyword, __location__, name="SELECTED_STATES_ATOM_RADIUS", &
680 description="Select all the states included in the given radius around each atoms "// &
681 "in SELECTED_STATES_ON_ATOM_LIST.", &
682 usage="SELECTED_STATES_ATOM_RADIUS 2.0", &
683 type_of_var=real_t, &
684 default_r_val=cp_unit_to_cp2k(value=4.0_dp, unit_str="angstrom"), &
685 unit_str="angstrom")
686 CALL section_add_keyword(section, keyword)
687 CALL keyword_release(keyword)
688
689 CALL keyword_create(keyword, __location__, name="RESTART_CURRENT", &
690 description="Restart the induced current density calculation"// &
691 " from a previous run (not working yet).", &
692 usage="RESTART_CURRENT", default_l_val=.false., &
693 lone_keyword_l_val=.true.)
694 CALL section_add_keyword(section, keyword)
695 CALL keyword_release(keyword)
696
697 NULLIFY (subsection)
698 CALL section_create(subsection, __location__, name="PRINT", &
699 description="print results of induced current density calculation", &
700 repeats=.false.)
701
702 CALL cp_print_key_section_create(print_key, __location__, "CURRENT_CUBES", &
703 description="Controls the printing of the induced current density (not working yet).", &
704 print_level=high_print_level, add_last=add_last_numeric, filename="")
705 CALL keyword_create(keyword, __location__, name="stride", &
706 description="The stride (X,Y,Z) used to write the cube file "// &
707 "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
708 " 1 number valid for all components (not working yet).", &
709 usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
710 CALL section_add_keyword(print_key, keyword)
711 CALL keyword_release(keyword)
712 CALL keyword_create(keyword, __location__, name="APPEND", &
713 description="append the cube files when they already exist", &
714 default_l_val=.false., lone_keyword_l_val=.true.)
715 CALL section_add_keyword(print_key, keyword)
716 CALL keyword_release(keyword)
717
718 CALL section_add_subsection(subsection, print_key)
719 CALL section_release(print_key)
720
721 CALL cp_print_key_section_create(print_key, __location__, "RESPONSE_FUNCTION_CUBES", &
722 description="Controls the printing of the response functions (not working yet).", &
723 print_level=high_print_level, add_last=add_last_numeric, filename="")
724 CALL keyword_create(keyword, __location__, name="stride", &
725 description="The stride (X,Y,Z) used to write the cube file "// &
726 "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
727 " 1 number valid for all components (not working yet).", &
728 usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
729 CALL section_add_keyword(print_key, keyword)
730 CALL keyword_release(keyword)
731
732 CALL keyword_create(keyword, __location__, name="CUBES_LU_BOUNDS", &
733 variants=(/"CUBES_LU"/), &
734 description="The lower and upper index of the states to be printed as cube (not working yet).", &
735 usage="CUBES_LU_BOUNDS integer integer", &
736 n_var=2, default_i_vals=(/0, -2/), type_of_var=integer_t)
737 CALL section_add_keyword(print_key, keyword)
738 CALL keyword_release(keyword)
739
740 CALL keyword_create(keyword, __location__, name="CUBES_LIST", &
741 description="Indexes of the states to be printed as cube files "// &
742 "This keyword can be repeated several times "// &
743 "(useful if you have to specify many indexes) (not working yet).", &
744 usage="CUBES_LIST 1 2", &
745 n_var=-1, type_of_var=integer_t, repeats=.true.)
746 CALL section_add_keyword(print_key, keyword)
747 CALL keyword_release(keyword)
748 CALL keyword_create(keyword, __location__, name="APPEND", &
749 description="append the cube files when they already exist", &
750 default_l_val=.false., lone_keyword_l_val=.true.)
751 CALL section_add_keyword(print_key, keyword)
752 CALL keyword_release(keyword)
753
754 CALL section_add_subsection(subsection, print_key)
755 CALL section_release(print_key)
756
757 CALL section_add_subsection(section, subsection)
758 CALL section_release(subsection)
759
760 NULLIFY (subsection)
761 CALL create_interp_section(subsection)
762 CALL section_add_subsection(section, subsection)
763 CALL section_release(subsection)
764
765 END SUBROUTINE create_current_section
766
767! **************************************************************************************************
768!> \brief creates the input structure used to activate
769!> calculation of NMR chemical shift using
770!> the induced current obtained from DFPT
771!> Available properties : none
772!> \param section the section to create
773!> \author MI/VW
774! **************************************************************************************************
775 SUBROUTINE create_nmr_section(section)
776 TYPE(section_type), POINTER :: section
777
778 TYPE(keyword_type), POINTER :: keyword
779 TYPE(section_type), POINTER :: print_key, subsection
780
781 NULLIFY (keyword, print_key, subsection)
782
783 cpassert(.NOT. ASSOCIATED(section))
784 CALL section_create(section, __location__, name="nmr", &
785 description="The chemical shift is calculated by DFPT.", &
786 n_keywords=5, n_subsections=1, repeats=.false., &
787 citations=(/weber2009/))
788
789 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
790 description="controls the activation of the nmr calculation", &
791 usage="&NMR T", &
792 default_l_val=.false., &
793 lone_keyword_l_val=.true.)
794 CALL section_add_keyword(section, keyword)
795 CALL keyword_release(keyword)
796
797 CALL keyword_create(keyword, __location__, name="INTERPOLATE_SHIFT", &
798 description="Calculate the soft part of the chemical shift by interpolation ", &
799 usage="INTERPOLATE_SHIFT T", &
800 default_l_val=.false., lone_keyword_l_val=.true.)
801 CALL section_add_keyword(section, keyword)
802 CALL keyword_release(keyword)
803
804 CALL keyword_create(keyword, __location__, name="NICS", &
805 description="Calculate the chemical shift in a set of points"// &
806 " given from an external file", usage="NICS", &
807 default_l_val=.false., lone_keyword_l_val=.true.)
808 CALL section_add_keyword(section, keyword)
809 CALL keyword_release(keyword)
810
811 CALL keyword_create(keyword, __location__, name="NICS_FILE_NAME", &
812 description="Name of the file with the NICS points coordinates", &
813 usage="NICS_FILE_NAME nics_file", &
814 default_lc_val="nics_file")
815 CALL section_add_keyword(section, keyword)
816 CALL keyword_release(keyword)
817
818 CALL keyword_create(keyword, __location__, name="RESTART_NMR", &
819 description="Restart the NMR calculation from a previous run (NOT WORKING YET)", &
820 usage="RESTART_NMR", default_l_val=.false., &
821 lone_keyword_l_val=.true.)
822 CALL section_add_keyword(section, keyword)
823 CALL keyword_release(keyword)
824
825 CALL keyword_create(keyword, __location__, name="SHIFT_GAPW_RADIUS", &
826 description="While computing the local part of the shift (GAPW), "// &
827 "the integration is restricted to nuclei that are within this radius.", &
828 usage="SHIFT_GAPW_RADIUS 20.0", &
829 type_of_var=real_t, &
830 default_r_val=cp_unit_to_cp2k(value=60.0_dp, unit_str="angstrom"), &
831 unit_str="angstrom")
832 CALL section_add_keyword(section, keyword)
833 CALL keyword_release(keyword)
834
835 NULLIFY (subsection)
836 CALL section_create(subsection, __location__, name="PRINT", &
837 description="print results of nmr calculation", &
838 repeats=.false.)
839
840 CALL cp_print_key_section_create(print_key, __location__, "RESPONSE_FUNCTION_CUBES", &
841 description="Controls the printing of the response functions ", &
842 print_level=high_print_level, add_last=add_last_numeric, filename="")
843 CALL keyword_create(keyword, __location__, name="stride", &
844 description="The stride (X,Y,Z) used to write the cube file "// &
845 "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
846 " 1 number valid for all components.", &
847 usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
848 CALL section_add_keyword(print_key, keyword)
849 CALL keyword_release(keyword)
850
851 CALL keyword_create(keyword, __location__, name="CUBES_LU_BOUNDS", &
852 variants=(/"CUBES_LU"/), &
853 description="The lower and upper index of the states to be printed as cube", &
854 usage="CUBES_LU_BOUNDS integer integer", &
855 n_var=2, default_i_vals=(/0, -2/), type_of_var=integer_t)
856 CALL section_add_keyword(print_key, keyword)
857 CALL keyword_release(keyword)
858
859 CALL keyword_create(keyword, __location__, name="CUBES_LIST", &
860 description="Indexes of the states to be printed as cube files "// &
861 "This keyword can be repeated several times "// &
862 "(useful if you have to specify many indexes).", &
863 usage="CUBES_LIST 1 2", &
864 n_var=-1, type_of_var=integer_t, repeats=.true.)
865 CALL section_add_keyword(print_key, keyword)
866 CALL keyword_release(keyword)
867 CALL keyword_create(keyword, __location__, name="APPEND", &
868 description="append the cube files when they already exist", &
869 default_l_val=.false., lone_keyword_l_val=.true.)
870 CALL section_add_keyword(print_key, keyword)
871 CALL keyword_release(keyword)
872
873 CALL section_add_subsection(subsection, print_key)
874 CALL section_release(print_key)
875
876 CALL cp_print_key_section_create(print_key, __location__, "CHI_TENSOR", &
877 description="Controls the printing of susceptibility", &
878 print_level=high_print_level, add_last=add_last_numeric, filename="")
879 CALL section_add_subsection(subsection, print_key)
880 CALL section_release(print_key)
881
882 CALL cp_print_key_section_create(print_key, __location__, "SHIELDING_TENSOR", &
883 description="Controls the printing of the chemical shift", &
884 print_level=low_print_level, add_last=add_last_numeric, filename="")
885
886 CALL keyword_create(keyword, __location__, name="ATOMS_LU_BOUNDS", &
887 variants=(/"ATOMS_LU"/), &
888 description="The lower and upper atomic index for which the tensor is printed", &
889 usage="ATOMS_LU_BOUNDS integer integer", &
890 n_var=2, default_i_vals=(/0, -2/), type_of_var=integer_t)
891 CALL section_add_keyword(print_key, keyword)
892 CALL keyword_release(keyword)
893
894 CALL keyword_create(keyword, __location__, name="ATOMS_LIST", &
895 description="list of atoms for which the shift is printed into a file ", &
896 usage="ATOMS_LIST 1 2", n_var=-1, &
897 type_of_var=integer_t, repeats=.true.)
898 CALL section_add_keyword(print_key, keyword)
899 CALL keyword_release(keyword)
900
901 CALL section_add_subsection(subsection, print_key)
902 CALL section_release(print_key)
903
904 CALL section_add_subsection(section, subsection)
905 CALL section_release(subsection)
906
907 NULLIFY (subsection)
908 CALL create_interp_section(subsection)
909 CALL section_add_subsection(section, subsection)
910 CALL section_release(subsection)
911
912 END SUBROUTINE create_nmr_section
913
914! **************************************************************************************************
915!> \brief creates the input structure used to activate
916!> calculation of NMR spin-spin coupling (implementation not operating)
917!> Available properties : none
918!> \param section the section to create
919!> \author VW
920! **************************************************************************************************
921 SUBROUTINE create_spin_spin_section(section)
922 TYPE(section_type), POINTER :: section
923
924 TYPE(keyword_type), POINTER :: keyword
925 TYPE(section_type), POINTER :: print_key, subsection
926
927 NULLIFY (keyword, print_key, subsection)
928
929 cpassert(.NOT. ASSOCIATED(section))
930 CALL section_create(section, __location__, name="spinspin", &
931 description="Compute indirect spin-spin coupling constants.", &
932 n_keywords=5, n_subsections=1, repeats=.false.)
933
934 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
935 description="controls the activation of the nmr calculation", &
936 usage="&SPINSPIN T", &
937 default_l_val=.false., &
938 lone_keyword_l_val=.true.)
939 CALL section_add_keyword(section, keyword)
940 CALL keyword_release(keyword)
941
942 CALL keyword_create(keyword, __location__, name="RESTART_SPINSPIN", &
943 description="Restart the spin-spin calculation from a previous run (NOT WORKING YET)", &
944 usage="RESTART_SPINSPIN", default_l_val=.false., &
945 lone_keyword_l_val=.true.)
946 CALL section_add_keyword(section, keyword)
947 CALL keyword_release(keyword)
948
949 CALL keyword_create(keyword, __location__, name="ISSC_ON_ATOM_LIST", &
950 description="Atoms for which the issc is computed.", &
951 usage="ISSC_ON_ATOM_LIST 1 2 10", &
952 n_var=-1, type_of_var=integer_t, repeats=.true.)
953 CALL section_add_keyword(section, keyword)
954 CALL keyword_release(keyword)
955
956 CALL keyword_create(keyword, __location__, name="DO_FC", &
957 description="Compute the Fermi contact contribution", &
958 usage="DO_FC F", &
959 default_l_val=.true., lone_keyword_l_val=.true.)
960 CALL section_add_keyword(section, keyword)
961 CALL keyword_release(keyword)
962
963 CALL keyword_create(keyword, __location__, name="DO_SD", &
964 description="Compute the spin-dipolar contribution", &
965 usage="DO_SD F", &
966 default_l_val=.true., lone_keyword_l_val=.true.)
967 CALL section_add_keyword(section, keyword)
968 CALL keyword_release(keyword)
969
970 CALL keyword_create(keyword, __location__, name="DO_PSO", &
971 description="Compute the paramagnetic spin-orbit contribution", &
972 usage="DO_PSO F", &
973 default_l_val=.true., lone_keyword_l_val=.true.)
974 CALL section_add_keyword(section, keyword)
975 CALL keyword_release(keyword)
976
977 CALL keyword_create(keyword, __location__, name="DO_DSO", &
978 description="Compute the diamagnetic spin-orbit contribution (NOT YET IMPLEMENTED)", &
979 usage="DO_DSO F", &
980 default_l_val=.true., lone_keyword_l_val=.true.)
981 CALL section_add_keyword(section, keyword)
982 CALL keyword_release(keyword)
983
984 NULLIFY (subsection)
985 CALL section_create(subsection, __location__, name="PRINT", &
986 description="print results of the indirect spin-spin calculation", &
987 repeats=.false.)
988
989 CALL cp_print_key_section_create(print_key, __location__, "K_MATRIX", &
990 description="Controls the printing of the indirect spin-spin matrix", &
991 print_level=low_print_level, add_last=add_last_numeric, filename="")
992
993 CALL keyword_create(keyword, __location__, name="ATOMS_LIST", &
994 description="list of atoms for which the indirect spin-spin is printed into a file ", &
995 usage="ATOMS_LIST 1 2", n_var=-1, &
996 type_of_var=integer_t, repeats=.true.)
997 CALL section_add_keyword(print_key, keyword)
998 CALL keyword_release(keyword)
999
1000 CALL section_add_subsection(subsection, print_key)
1001 CALL section_release(print_key)
1002
1003 CALL section_add_subsection(section, subsection)
1004 CALL section_release(subsection)
1005
1006 NULLIFY (subsection)
1007 CALL create_interp_section(subsection)
1008 CALL section_add_subsection(section, subsection)
1009 CALL section_release(subsection)
1010
1011 END SUBROUTINE create_spin_spin_section
1012
1013! **************************************************************************************************
1014!> \brief creates the input structure used to activate
1015!> calculation of EPR using
1016!> the induced current obtained from DFPT
1017!> Available properties : none
1018!> \param section the section to create
1019!> \author VW
1020! **************************************************************************************************
1021 SUBROUTINE create_epr_section(section)
1022 TYPE(section_type), POINTER :: section
1023
1024 TYPE(keyword_type), POINTER :: keyword
1025 TYPE(section_type), POINTER :: print_key, subsection, subsubsection
1026
1027 NULLIFY (keyword, print_key, subsection, subsubsection)
1028
1029 cpassert(.NOT. ASSOCIATED(section))
1030 CALL section_create(section, __location__, name="EPR", &
1031 description="The g tensor is calculated by DFPT ", &
1032 n_keywords=5, n_subsections=1, repeats=.false., &
1033 citations=(/weber2009/))
1034
1035 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
1036 description="controls the activation of the epr calculation", &
1037 usage="&EPR T", &
1038 default_l_val=.false., &
1039 lone_keyword_l_val=.true.)
1040 CALL section_add_keyword(section, keyword)
1041 CALL keyword_release(keyword)
1042
1043 CALL keyword_create(keyword, __location__, name="RESTART_EPR", &
1044 description="Restart the EPR calculation from a previous run (NOT WORKING)", &
1045 usage="RESTART_EPR", default_l_val=.false., &
1046 lone_keyword_l_val=.true.)
1047 CALL section_add_keyword(section, keyword)
1048 CALL keyword_release(keyword)
1049
1050 NULLIFY (subsection)
1051 CALL section_create(subsection, __location__, name="PRINT", &
1052 description="print results of epr calculation", &
1053 repeats=.false.)
1054
1055 CALL cp_print_key_section_create(print_key, __location__, "NABLAVKS_CUBES", &
1056 description="Controls the printing of the components of nabla v_ks ", &
1057 print_level=high_print_level, add_last=add_last_numeric, filename="")
1058 CALL keyword_create(keyword, __location__, name="stride", &
1059 description="The stride (X,Y,Z) used to write the cube file "// &
1060 "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
1061 " 1 number valid for all components.", &
1062 usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
1063 CALL section_add_keyword(print_key, keyword)
1064 CALL keyword_release(keyword)
1065 CALL keyword_create(keyword, __location__, name="APPEND", &
1066 description="append the cube files when they already exist", &
1067 default_l_val=.false., lone_keyword_l_val=.true.)
1068 CALL section_add_keyword(print_key, keyword)
1069 CALL keyword_release(keyword)
1070
1071 CALL section_add_subsection(subsection, print_key)
1072 CALL section_release(print_key)
1073
1074 CALL cp_print_key_section_create(print_key, __location__, "G_TENSOR", &
1075 description="Controls the printing of the g tensor", &
1076 print_level=high_print_level, add_last=add_last_numeric, filename="")
1077 CALL create_xc_section(subsubsection)
1078 CALL section_add_subsection(print_key, subsubsection)
1079 CALL section_release(subsubsection)
1080
1081 CALL keyword_create(keyword, __location__, name="GAPW_MAX_ALPHA", &
1082 description="Maximum alpha of GTH potentials allowed on the soft grids ", &
1083 usage="GAPW_MAX_ALPHA real", default_r_val=5.0_dp)
1084 CALL section_add_keyword(print_key, keyword)
1085 CALL keyword_release(keyword)
1086
1087 CALL keyword_create(keyword, __location__, name="SOO_RHO_HARD", &
1088 description="Whether or not to include the atomic parts of the density "// &
1089 "in the SOO part of the g tensor", usage="SOO_RHO_HARD", &
1090 default_l_val=.false., lone_keyword_l_val=.true.)
1091 CALL section_add_keyword(print_key, keyword)
1092 CALL keyword_release(keyword)
1093
1094 CALL section_add_subsection(subsection, print_key)
1095 CALL section_release(print_key)
1096
1097 CALL cp_print_key_section_create(print_key, __location__, "RESPONSE_FUNCTION_CUBES", &
1098 description="Controls the printing of the response functions ", &
1099 print_level=high_print_level, add_last=add_last_numeric, filename="")
1100 CALL keyword_create(keyword, __location__, name="stride", &
1101 description="The stride (X,Y,Z) used to write the cube file "// &
1102 "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
1103 " 1 number valid for all components.", &
1104 usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
1105 CALL section_add_keyword(print_key, keyword)
1106 CALL keyword_release(keyword)
1107
1108 CALL keyword_create(keyword, __location__, name="CUBES_LU_BOUNDS", &
1109 variants=(/"CUBES_LU"/), &
1110 description="The lower and upper index of the states to be printed as cube", &
1111 usage="CUBES_LU_BOUNDS integer integer", &
1112 n_var=2, default_i_vals=(/0, -2/), type_of_var=integer_t)
1113 CALL section_add_keyword(print_key, keyword)
1114 CALL keyword_release(keyword)
1115
1116 CALL keyword_create(keyword, __location__, name="CUBES_LIST", &
1117 description="Indexes of the states to be printed as cube files "// &
1118 "This keyword can be repeated several times "// &
1119 "(useful if you have to specify many indexes).", &
1120 usage="CUBES_LIST 1 2", &
1121 n_var=-1, type_of_var=integer_t, repeats=.true.)
1122 CALL section_add_keyword(print_key, keyword)
1123 CALL keyword_release(keyword)
1124 CALL keyword_create(keyword, __location__, name="APPEND", &
1125 description="append the cube files when they already exist", &
1126 default_l_val=.false., lone_keyword_l_val=.true.)
1127 CALL section_add_keyword(print_key, keyword)
1128 CALL keyword_release(keyword)
1129
1130 CALL section_add_subsection(subsection, print_key)
1131 CALL section_release(print_key)
1132
1133 CALL section_add_subsection(section, subsection)
1134 CALL section_release(subsection)
1135
1136 NULLIFY (subsection)
1137 CALL create_interp_section(subsection)
1138 CALL section_add_subsection(section, subsection)
1139 CALL section_release(subsection)
1140
1141 END SUBROUTINE create_epr_section
1142
1143! **************************************************************************************************
1144!> \brief creates the input structure used to activate
1145!> calculation of polarizability tensor DFPT
1146!> Available properties : none
1147!> \param section the section to create
1148!> \author SL
1149! **************************************************************************************************
1150 SUBROUTINE create_polarizability_section(section)
1151
1152 TYPE(section_type), POINTER :: section
1153
1154 TYPE(keyword_type), POINTER :: keyword
1155 TYPE(section_type), POINTER :: print_key, subsection
1156
1157 NULLIFY (keyword, print_key, subsection)
1158
1159 cpassert(.NOT. ASSOCIATED(section))
1160 CALL section_create(section, __location__, name="POLAR", &
1161 description="Compute polarizabilities.", &
1162 n_keywords=5, n_subsections=1, repeats=.false., &
1163 citations=(/putrino2002/))
1164
1165 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
1166 description="controls the activation of the polarizability calculation", &
1167 usage="&POLAR T", &
1168 default_l_val=.false., &
1169 lone_keyword_l_val=.true.)
1170 CALL section_add_keyword(section, keyword)
1171 CALL keyword_release(keyword)
1172
1173 CALL keyword_create(keyword, __location__, name="DO_RAMAN", &
1174 description="Compute the electric-dipole--electric-dipole polarizability", &
1175 usage="DO_RAMAN F", &
1176 citations=(/luber2014/), &
1177 default_l_val=.true., lone_keyword_l_val=.true.)
1178 CALL section_add_keyword(section, keyword)
1179 CALL keyword_release(keyword)
1180
1181 CALL keyword_create(keyword, __location__, name="PERIODIC_DIPOLE_OPERATOR", &
1182 description="Type of dipole operator: Berry phase(T) or Local(F)", &
1183 usage="PERIODIC_DIPOLE_OPERATOR T", &
1184 default_l_val=.true., lone_keyword_l_val=.true.)
1185 CALL section_add_keyword(section, keyword)
1186 CALL keyword_release(keyword)
1187
1188 NULLIFY (subsection)
1189 CALL section_create(subsection, __location__, name="PRINT", &
1190 description="print results of the polarizability calculation", &
1191 repeats=.false.)
1192
1193 CALL cp_print_key_section_create(print_key, __location__, "POLAR_MATRIX", &
1194 description="Controls the printing of the polarizabilities", &
1195 print_level=low_print_level, add_last=add_last_numeric, filename="")
1196
1197 CALL section_add_subsection(subsection, print_key)
1198 CALL section_release(print_key)
1199 CALL section_add_subsection(section, subsection)
1200 CALL section_release(subsection)
1201
1202 NULLIFY (subsection)
1203 CALL create_interp_section(subsection)
1204 CALL section_add_subsection(section, subsection)
1205 CALL section_release(subsection)
1206
1207 END SUBROUTINE create_polarizability_section
1208
1209! **************************************************************************************************
1210!> \brief creates the section for electron transfer coupling
1211!> \param section ...
1212!> \author fschiff
1213! **************************************************************************************************
1214 SUBROUTINE create_et_coupling_section(section)
1215 TYPE(section_type), POINTER :: section
1216
1217 TYPE(keyword_type), POINTER :: keyword
1218 TYPE(section_type), POINTER :: print_key, subsection
1219
1220 NULLIFY (keyword)
1221 cpassert(.NOT. ASSOCIATED(section))
1222 CALL section_create(section, __location__, name="ET_COUPLING", &
1223 description="specifies the two constraints/restraints for extracting ET coupling elements", &
1224 n_keywords=1, n_subsections=4, repeats=.false., citations=(/kondov2007, futera2017/))
1225
1226 NULLIFY (subsection)
1227 CALL create_ddapc_restraint_section(subsection, "DDAPC_RESTRAINT_A")
1228 CALL section_add_subsection(section, subsection)
1229 CALL section_release(subsection)
1230
1231 NULLIFY (subsection)
1232 CALL create_ddapc_restraint_section(subsection, "DDAPC_RESTRAINT_B")
1233 CALL section_add_subsection(section, subsection)
1234 CALL section_release(subsection)
1235
1236 NULLIFY (subsection)
1237 CALL create_projection(subsection, "PROJECTION")
1238 CALL section_add_subsection(section, subsection)
1239 CALL section_release(subsection)
1240
1241 CALL keyword_create(keyword, __location__, name="TYPE_OF_CONSTRAINT", &
1242 description="Specifies the type of constraint", &
1243 usage="TYPE_OF_CONSTRAINT DDAPC", &
1244 enum_c_vals=s2a("NONE", "DDAPC"), &
1245 enum_i_vals=(/do_no_et, do_et_ddapc/), &
1246 enum_desc=s2a("NONE", "DDAPC Constraint"), &
1247 default_i_val=do_no_et)
1248 CALL section_add_keyword(section, keyword)
1249 CALL keyword_release(keyword)
1250
1251 NULLIFY (print_key)
1252 CALL cp_print_key_section_create(print_key, __location__, "PROGRAM_RUN_INFO", &
1253 description="Controls the printing basic info about the method", &
1254 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
1255 CALL section_add_subsection(section, print_key)
1256 CALL section_release(print_key)
1257
1258 END SUBROUTINE create_et_coupling_section
1259
1260! **************************************************************************************************
1261!> \brief defines input sections for specification of Hilbert space partitioning
1262!> in projection-operator approach of electronic coupling calulation
1263!> \param section pointer to the section data structure
1264!> \param section_name name of the projection section
1265!> \author Z. Futera (02.2017)
1266! **************************************************************************************************
1267 SUBROUTINE create_projection(section, section_name)
1268
1269 ! Routine arguments
1270 TYPE(section_type), POINTER :: section
1271 CHARACTER(len=*), INTENT(in) :: section_name
1272
1273 TYPE(keyword_type), POINTER :: keyword
1274 TYPE(section_type), POINTER :: print_key, section_block, section_print
1275
1276! Routine name for dubug purposes
1277
1278 ! Sanity check
1279 cpassert(.NOT. ASSOCIATED(section))
1280
1281 ! Initialization
1282 NULLIFY (keyword)
1283 NULLIFY (print_key)
1284 NULLIFY (section_block)
1285 NULLIFY (section_print)
1286
1287 ! Input-file section definition
1288 CALL section_create(section, __location__, name=trim(adjustl(section_name)), &
1289 description="Projection-operator approach fo ET coupling calculation", &
1290 n_keywords=0, n_subsections=2, repeats=.false.)
1291
1292 ! Subsection #0: Log printing
1293 CALL cp_print_key_section_create(print_key, __location__, 'PROGRAM_RUN_INFO', &
1294 description="Controls printing of data and informations to log file", &
1295 print_level=low_print_level, filename="__STD_OUT__")
1296 CALL section_add_subsection(section, print_key)
1297 CALL section_release(print_key)
1298
1299 ! Subsection #1: Atomic blocks
1300 CALL section_create(section_block, __location__, name='BLOCK', &
1301 description="Part of the system (donor, acceptor, bridge,...)", &
1302 n_keywords=2, n_subsections=1, repeats=.true.)
1303 CALL section_add_subsection(section, section_block)
1304
1305 ! S#1 - Keyword #1: Atom IDs defining a Hilbert space block
1306 CALL keyword_create(keyword, __location__, name='ATOMS', &
1307 description="Array of atom IDs in the system part", &
1308 usage="ATOMS {integer} {integer} .. {integer}", &
1309 n_var=-1, type_of_var=integer_t, repeats=.false.)
1310 CALL section_add_keyword(section_block, keyword)
1311 CALL keyword_release(keyword)
1312
1313 ! S#1 - Keyword #1: Atom IDs defining a Hilbert space block
1314 CALL keyword_create(keyword, __location__, name='NELECTRON', &
1315 description="Number of electrons expected in the system part", &
1316 usage="NELECTRON {integer}", default_i_val=0)
1317 CALL section_add_keyword(section_block, keyword)
1318 CALL keyword_release(keyword)
1319
1320 ! S#1 - Subsection #1: Printing setting
1321 CALL section_create(section_print, __location__, name='PRINT', &
1322 description="Possible printing options in ET system part", &
1323 n_keywords=0, n_subsections=0, repeats=.false.)
1324 CALL section_add_subsection(section_block, section_print)
1325
1326 ! S#1 - S#1 - Keyword #1: MO coefficient on specific atom
1327 CALL keyword_create(keyword, __location__, name='MO_COEFF_ATOM', &
1328 description="Print out MO coeffiecients on given atom", &
1329 usage="MO_COEFF_ATOM {integer} {integer} .. {integer}", &
1330 type_of_var=integer_t, n_var=-1, repeats=.true.)
1331 CALL section_add_keyword(section_print, keyword)
1332 CALL keyword_release(keyword)
1333
1334 ! S#1 - S#1 - Keyword #1: MO coefficient of specific state
1335 CALL keyword_create(keyword, __location__, name='MO_COEFF_ATOM_STATE', &
1336 description="Print out MO coeffiecients of specific state", &
1337 usage="MO_COEFF_ATOM_STATE {integer} {integer} .. {integer}", &
1338 type_of_var=integer_t, n_var=-1, repeats=.true.)
1339 CALL section_add_keyword(section_print, keyword)
1340 CALL keyword_release(keyword)
1341
1342 ! S#1 - S#1 - Subsection #1: Saving MOs to CUBE files
1343 CALL cp_print_key_section_create(print_key, __location__, 'MO_CUBES', &
1344 description="Controls saving of MO cube files", &
1345 print_level=high_print_level, filename="")
1346
1347 ! S#1 - S#1 - S#1 - Keyword #1: Stride
1348 CALL keyword_create(keyword, __location__, name='STRIDE', &
1349 description="The stride (X,Y,Z) used to write the cube file", &
1350 usage="STRIDE {integer} {integer} {integer}", n_var=-1, &
1351 default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
1352 CALL section_add_keyword(print_key, keyword)
1353 CALL keyword_release(keyword)
1354
1355 ! S#1 - S#1 - S#1 - Keyword #2: List of MO IDs
1356 CALL keyword_create(keyword, __location__, name='MO_LIST', &
1357 description="Indices of molecular orbitals to save", &
1358 usage="MO_LIST {integer} {integer} .. {integer}", &
1359 type_of_var=integer_t, n_var=-1, repeats=.true.)
1360 CALL section_add_keyword(print_key, keyword)
1361 CALL keyword_release(keyword)
1362
1363 ! S#1 - S#1 - S#1 - Keyword #2: Number of unoccupied states
1364 CALL keyword_create(keyword, __location__, name='NLUMO', &
1365 description="Number of unoccupied molecular orbitals to save", &
1366 usage="NLUMO {integer}", default_i_val=1)
1367 CALL section_add_keyword(print_key, keyword)
1368 CALL keyword_release(keyword)
1369
1370 ! S#1 - S#1 - S#1 - Keyword #3: Number of occupied states
1371 CALL keyword_create(keyword, __location__, name='NHOMO', &
1372 description="Number of occupied molecular orbitals to save", &
1373 usage="NHOMO {integer}", default_i_val=1)
1374 CALL section_add_keyword(print_key, keyword)
1375 CALL keyword_release(keyword)
1376
1377 CALL section_add_subsection(section_print, print_key)
1378 CALL section_release(print_key)
1379
1380 ! S#1 - S#1 - Clean
1381 CALL section_release(section_print)
1382
1383 ! S#1 - Clean
1384 CALL section_release(section_block)
1385
1386 ! S#1 - Subsection #1: Printing setting
1387 CALL section_create(section_print, __location__, name='PRINT', &
1388 description="Possible printing options in ET", &
1389 n_keywords=0, n_subsections=0, repeats=.false.)
1390 CALL section_add_subsection(section, section_print)
1391
1392 ! Print couplings
1393 CALL cp_print_key_section_create(print_key, __location__, 'COUPLINGS', &
1394 description="Controls printing couplings onto file", &
1395 print_level=low_print_level, filename="")
1396
1397 CALL keyword_create(keyword, __location__, name="APPEND", &
1398 description="append the files when they already exist", &
1399 default_l_val=.false., lone_keyword_l_val=.true.)
1400 CALL section_add_keyword(print_key, keyword)
1401 CALL keyword_release(keyword)
1402
1403 CALL section_add_subsection(section_print, print_key)
1404 CALL section_release(print_key)
1405
1406 CALL section_release(section_print)
1407
1408 END SUBROUTINE create_projection
1409
1410! **************************************************************************************************
1411!> \brief creates an input section for tddfpt calculation
1412!> \param section section to create
1413!> \par History
1414!> * 05.2016 forked from create_tddfpt_section [Sergey Chulkov]
1415!> * 08.2016 moved from module input_cp2k_dft [Sergey Chulkov]
1416! **************************************************************************************************
1417 SUBROUTINE create_tddfpt2_section(section)
1418 TYPE(section_type), POINTER :: section
1419
1420 TYPE(keyword_type), POINTER :: keyword
1421 TYPE(section_type), POINTER :: print_key, subsection
1422
1423 cpassert(.NOT. ASSOCIATED(section))
1424 CALL section_create(section, __location__, name="TDDFPT", &
1425 description="Parameters needed to set up the Time-Dependent "// &
1426 "Density Functional Perturbation Theory. "// &
1427 "Current implementation works for hybrid functionals. "// &
1428 "Can be used with Gaussian and Plane Waves (GPW) method only.", &
1429 n_keywords=12, n_subsections=4, repeats=.false., &
1430 citations=(/iannuzzi2005/))
1431
1432 NULLIFY (keyword, print_key, subsection)
1433
1434 CALL keyword_create(keyword, __location__, &
1435 name="_SECTION_PARAMETERS_", &
1436 description="Controls the activation of the TDDFPT procedure", &
1437 default_l_val=.false., &
1438 lone_keyword_l_val=.true.)
1439 CALL section_add_keyword(section, keyword)
1440 CALL keyword_release(keyword)
1441
1442 ! Integer
1443 CALL keyword_create(keyword, __location__, name="NSTATES", &
1444 description="Number of excited states to converge.", &
1445 n_var=1, type_of_var=integer_t, &
1446 default_i_val=1)
1447 CALL section_add_keyword(section, keyword)
1448 CALL keyword_release(keyword)
1449
1450 CALL keyword_create(keyword, __location__, name="MAX_ITER", &
1451 description="Maximal number of iterations to be performed.", &
1452 n_var=1, type_of_var=integer_t, &
1453 default_i_val=50)
1454 CALL section_add_keyword(section, keyword)
1455 CALL keyword_release(keyword)
1456
1457 CALL keyword_create(keyword, __location__, name="MAX_KV", &
1458 description="Maximal number of Krylov space vectors. "// &
1459 "Davidson iterations will be restarted upon reaching this limit.", &
1460 n_var=1, type_of_var=integer_t, &
1461 default_i_val=5000)
1462 CALL section_add_keyword(section, keyword)
1463 CALL keyword_release(keyword)
1464
1465 CALL keyword_create(keyword, __location__, name="NLUMO", &
1466 description="Number of unoccupied orbitals to consider. "// &
1467 "Default is to use all unoccupied orbitals (-1).", &
1468 n_var=1, type_of_var=integer_t, &
1469 default_i_val=-1)
1470 CALL section_add_keyword(section, keyword)
1471 CALL keyword_release(keyword)
1472
1473 CALL keyword_create(keyword, __location__, name="NPROC_STATE", &
1474 description="Number of MPI processes to be used per excited state. "// &
1475 "Default is to use all processors (0).", &
1476 n_var=1, type_of_var=integer_t, &
1477 default_i_val=0)
1478 CALL section_add_keyword(section, keyword)
1479 CALL keyword_release(keyword)
1480
1481 ! kernel type
1482 CALL keyword_create(keyword, __location__, name="KERNEL", &
1483 description="Options to compute the kernel", &
1484 usage="KERNEL FULL", &
1485 enum_c_vals=s2a("FULL", "sTDA", "NONE"), &
1487 default_i_val=tddfpt_kernel_full)
1488 CALL section_add_keyword(section, keyword)
1489 CALL keyword_release(keyword)
1490
1491 CALL keyword_create(keyword, __location__, name="OE_CORR", &
1492 description="Orbital energy correction potential.", &
1493 enum_c_vals=s2a("NONE", "LB94", "GLLB", "SAOP", "SHIFT"), &
1494 enum_i_vals=(/oe_none, oe_lb, oe_gllb, oe_saop, oe_shift/), &
1495 enum_desc=s2a("No orbital correction scheme is used", &
1496 "van Leeuwen and Baerends. PRA, 49:2421, 1994", &
1497 "Gritsenko, van Leeuwen, van Lenthe, Baerends. PRA, 51:1944, 1995", &
1498 "Gritsenko, Schipper, Baerends. Chem. Phys. Lett., 302:199, 1999", &
1499 "Constant shift of virtual and/or open-shell orbitals"), &
1500 default_i_val=oe_none)
1501 CALL section_add_keyword(section, keyword)
1502 CALL keyword_release(keyword)
1503
1504 ! SHIFTS
1505 CALL keyword_create(keyword, __location__, name="EV_SHIFT", &
1506 variants=s2a("VIRTUAL_SHIFT"), &
1507 description="Constant shift of virtual state eigenvalues.", &
1508 usage="EV_SHIFT 0.500", &
1509 n_var=1, type_of_var=real_t, &
1510 unit_str="eV", &
1511 default_r_val=0.0_dp)
1512 CALL section_add_keyword(section, keyword)
1513 CALL keyword_release(keyword)
1514 !
1515 CALL keyword_create(keyword, __location__, name="EOS_SHIFT", &
1516 variants=s2a("OPEN_SHELL_SHIFT"), &
1517 description="Constant shift of open shell eigenvalues.", &
1518 usage="EOS_SHIFT 0.200", &
1519 n_var=1, type_of_var=real_t, &
1520 unit_str="eV", &
1521 default_r_val=0.0_dp)
1522 CALL section_add_keyword(section, keyword)
1523 CALL keyword_release(keyword)
1524
1525 ! Real
1526 CALL keyword_create(keyword, __location__, name="CONVERGENCE", &
1527 description="Target accuracy for excited state energies.", &
1528 n_var=1, type_of_var=real_t, unit_str="hartree", &
1529 default_r_val=1.0e-5_dp)
1530 CALL section_add_keyword(section, keyword)
1531 CALL keyword_release(keyword)
1532
1533 CALL keyword_create(keyword, __location__, name="MIN_AMPLITUDE", &
1534 description="The smallest excitation amplitude to print.", &
1535 n_var=1, type_of_var=real_t, &
1536 default_r_val=5.0e-2_dp)
1537 CALL section_add_keyword(section, keyword)
1538 CALL keyword_release(keyword)
1539
1540 CALL keyword_create(keyword, __location__, name="ORTHOGONAL_EPS", &
1541 description="The largest possible overlap between the ground state and "// &
1542 "orthogonalised excited state wave-functions. Davidson iterations "// &
1543 "will be restarted when the overlap goes beyond this threshold in "// &
1544 "order to prevent numerical instability.", &
1545 n_var=1, type_of_var=real_t, &
1546 default_r_val=1.0e-4_dp)
1547 CALL section_add_keyword(section, keyword)
1548 CALL keyword_release(keyword)
1549
1550 ! Logical
1551 CALL keyword_create(keyword, __location__, name="RESTART", &
1552 description="Restart the TDDFPT calculation if a restart file exists", &
1553 n_var=1, type_of_var=logical_t, &
1554 default_l_val=.false., lone_keyword_l_val=.true.)
1555 CALL section_add_keyword(section, keyword)
1556 CALL keyword_release(keyword)
1557
1558 CALL keyword_create(keyword, __location__, name="RKS_TRIPLETS", &
1559 description="Compute triplet excited states using spin-unpolarised molecular orbitals.", &
1560 n_var=1, type_of_var=logical_t, &
1561 default_l_val=.false.)
1562 CALL section_add_keyword(section, keyword)
1563 CALL keyword_release(keyword)
1564
1565 CALL keyword_create(keyword, __location__, name="ADMM_KERNEL_XC_CORRECTION", &
1566 description="Use/Ignore ADMM correction xc functional for TD kernel. "// &
1567 "XC correction functional is defined in ground state XC section.", &
1568 n_var=1, type_of_var=logical_t, &
1569 default_l_val=.true., lone_keyword_l_val=.true.)
1570 CALL section_add_keyword(section, keyword)
1571 CALL keyword_release(keyword)
1572
1573 CALL keyword_create(keyword, __location__, name="ADMM_KERNEL_CORRECTION_SYMMETRIC", &
1574 description="ADMM correction functional in kernel is applied symmetrically. "// &
1575 "Original implementation is using a non-symmetric formula.", &
1576 n_var=1, type_of_var=logical_t, &
1577 default_l_val=.true., lone_keyword_l_val=.true.)
1578 CALL section_add_keyword(section, keyword)
1579 CALL keyword_release(keyword)
1580
1581 CALL keyword_create(keyword, __location__, name="DO_LRIGPW", &
1582 description="Local resolution of identity for Coulomb contribution.", &
1583 n_var=1, type_of_var=logical_t, &
1584 default_l_val=.false.)
1585 CALL section_add_keyword(section, keyword)
1586 CALL keyword_release(keyword)
1587
1588 CALL keyword_create(keyword, __location__, name="AUTO_BASIS", &
1589 description="Specify size of automatically generated auxiliary basis sets: "// &
1590 "Options={small,medium,large,huge}", &
1591 usage="AUTO_BASIS {basis_type} {basis_size}", &
1592 type_of_var=char_t, repeats=.true., n_var=-1, default_c_vals=(/"X", "X"/))
1593 CALL section_add_keyword(section, keyword)
1594 CALL keyword_release(keyword)
1595
1596 CALL keyword_create(keyword, __location__, name="DO_SMEARING", &
1597 description="Implying smeared occupation. ", &
1598 n_var=1, type_of_var=logical_t, &
1599 default_l_val=.false., lone_keyword_l_val=.true.)
1600 CALL section_add_keyword(section, keyword)
1601 CALL keyword_release(keyword)
1602
1603 CALL keyword_create(keyword, __location__, name="EXCITON_DESCRIPTORS", &
1604 description="Compute exciton descriptors. "// &
1605 "Details given in Manual section about Bethe Salpeter equation.", &
1606 n_var=1, type_of_var=logical_t, &
1607 default_l_val=.false.)
1608 CALL section_add_keyword(section, keyword)
1609 CALL keyword_release(keyword)
1610
1611 CALL keyword_create(keyword, __location__, name="DIRECTIONAL_EXCITON_DESCRIPTORS", &
1612 description="Print cartesian components of exciton descriptors.", &
1613 n_var=1, type_of_var=logical_t, &
1614 default_l_val=.false.)
1615 CALL section_add_keyword(section, keyword)
1616 CALL keyword_release(keyword)
1617
1618 ! Strings
1619 CALL keyword_create(keyword, __location__, name="WFN_RESTART_FILE_NAME", &
1620 variants=(/"RESTART_FILE_NAME"/), &
1621 description="Name of the wave function restart file, may include a path."// &
1622 " If no file is specified, the default is to open the file as generated by"// &
1623 " the wave function restart print key.", &
1624 usage="WFN_RESTART_FILE_NAME <FILENAME>", &
1625 type_of_var=lchar_t)
1626 CALL section_add_keyword(section, keyword)
1627 CALL keyword_release(keyword)
1628
1629 ! DIPOLE subsection
1630 CALL section_create(subsection, __location__, name="DIPOLE_MOMENTS", &
1631 description="Parameters to compute oscillator strengths in the dipole approximation.", &
1632 n_keywords=3, n_subsections=0, repeats=.false.)
1633
1634 CALL keyword_create(keyword, __location__, name="DIPOLE_FORM", &
1635 description="Form of dipole transition integrals.", &
1636 enum_c_vals=s2a("BERRY", "LENGTH", "VELOCITY"), &
1637 enum_desc=s2a("Based on Berry phase formula (valid for fully periodic molecular systems only)", &
1638 "Length form &lang; i | r | j &rang; (valid for non-periodic molecular systems only)", &
1639 "Velocity form &lang; i | d/dr | j &rang;"), &
1641 default_i_val=tddfpt_dipole_velocity)
1642 CALL section_add_keyword(subsection, keyword)
1643 CALL keyword_release(keyword)
1644
1645 CALL keyword_create(keyword, __location__, name="REFERENCE", &
1646 description="Reference point to calculate electric "// &
1647 "dipole moments using the dipole integrals in the length form.", &
1648 enum_c_vals=s2a("COM", "COAC", "USER_DEFINED", "ZERO"), &
1649 enum_desc=s2a("Use Center of Mass", &
1650 "Use Center of Atomic Charges", &
1651 "Use User-defined Point", &
1652 "Use Origin of Coordinate System"), &
1653 enum_i_vals=(/use_mom_ref_com, &
1656 use_mom_ref_zero/), &
1657 default_i_val=use_mom_ref_com)
1658 CALL section_add_keyword(subsection, keyword)
1659 CALL keyword_release(keyword)
1660
1661 CALL keyword_create(keyword, __location__, name="REFERENCE_POINT", &
1662 description="User-defined reference point.", &
1663 usage="REFERENCE_POINT x y z", &
1664 repeats=.false., n_var=3, type_of_var=real_t, unit_str='bohr')
1665 CALL section_add_keyword(subsection, keyword)
1666 CALL keyword_release(keyword)
1667
1668 CALL section_add_subsection(section, subsection)
1669 CALL section_release(subsection)
1670
1671 ! SOC functional
1672
1673 CALL section_create(subsection, __location__, name="SOC", &
1674 description="Is jet to be implemented", &
1675 n_keywords=2, n_subsections=0, repeats=.false.)
1676
1677 CALL keyword_create(keyword, __location__, name="EPS_FILTER", &
1678 variants=s2a("EPS_FILTER_MATRIX"), &
1679 description="The threshold used for sparse matrix operations", &
1680 usage="EPS_FILTER {real}", &
1681 type_of_var=real_t, &
1682 default_r_val=1.0e-10_dp)
1683 CALL section_add_keyword(subsection, keyword)
1684 CALL keyword_release(keyword)
1685
1686 CALL keyword_create(keyword, __location__, name="GRID", &
1687 variants=(/"ATOMIC_GRID"/), &
1688 description="Specification of the atomic angular and radial grids for "// &
1689 "a atomic kind. This keyword must be repeated for all kinds! "// &
1690 "Usage: GRID < LEBEDEV_GRID > < RADIAL_GRID >", &
1691 usage="GRID {string} {integer} {integer}", &
1692 n_var=3, type_of_var=char_t, repeats=.true.)
1693 CALL section_add_keyword(subsection, keyword)
1694 CALL keyword_release(keyword)
1695
1696 CALL section_add_subsection(section, subsection)
1697 CALL section_release(subsection)
1698
1699 ! kernel XC functional
1700 CALL create_xc_section(subsection)
1701 CALL section_add_subsection(section, subsection)
1702 CALL section_release(subsection)
1703
1704 ! MGRID subsection
1705 CALL create_mgrid_section(subsection, create_subsections=.false.)
1706 CALL section_add_subsection(section, subsection)
1707 CALL section_release(subsection)
1708
1709 ! sTDA subsection
1710 CALL create_stda_section(subsection)
1711 CALL section_add_subsection(section, subsection)
1712 CALL section_release(subsection)
1713
1714 ! LRI subsection
1715 CALL create_lrigpw_section(subsection)
1716 CALL section_add_subsection(section, subsection)
1717 CALL section_release(subsection)
1718
1719 ! LINRES section
1720 CALL create_linres_section(subsection, create_subsections=.false., default_set_tdlr=.true.)
1721 CALL section_add_subsection(section, subsection)
1722 CALL section_release(subsection)
1723
1724 ! PRINT subsection
1725 CALL section_create(subsection, __location__, name="PRINT", &
1726 description="Printing of information during the TDDFT run.", repeats=.false.)
1727
1728 CALL cp_print_key_section_create(print_key, __location__, name="PROGRAM_BANNER", &
1729 description="Controls the printing of the banner for TDDFPT program", &
1730 print_level=silent_print_level, filename="__STD_OUT__")
1731 CALL section_add_subsection(subsection, print_key)
1732 CALL section_release(print_key)
1733
1734 CALL cp_print_key_section_create(print_key, __location__, name="GUESS_VECTORS", &
1735 description="Controls the printing of initial guess vectors.", &
1736 print_level=low_print_level, filename="__STD_OUT__")
1737 CALL section_add_subsection(subsection, print_key)
1738 CALL section_release(print_key)
1739
1740 CALL cp_print_key_section_create(print_key, __location__, name="ITERATION_INFO", &
1741 description="Controls the printing of basic iteration information "// &
1742 "during the TDDFT run.", &
1743 print_level=low_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
1744 CALL section_add_subsection(subsection, print_key)
1745 CALL section_release(print_key)
1746
1747 CALL cp_print_key_section_create(print_key, __location__, name="DETAILED_ENERGY", &
1748 description="Controls the printing of detailed energy information "// &
1749 "during the TDDFT run.", &
1750 print_level=medium_print_level, add_last=add_last_numeric, filename="__STD_OUT__")
1751 CALL section_add_subsection(subsection, print_key)
1752 CALL section_release(print_key)
1753
1754 CALL cp_print_key_section_create(print_key, __location__, name="BASIS_SET_FILE", &
1755 description="Controls the printing of a file with all basis sets used.", &
1756 print_level=debug_print_level, filename="BASIS_SETS")
1757 CALL section_add_subsection(subsection, print_key)
1758 CALL section_release(print_key)
1759
1760 CALL cp_print_key_section_create(print_key, __location__, name="RESTART", &
1761 description="Controls the dumping of the MO restart file during TDDFPT. "// &
1762 "By default keeps a short history of three restarts.", &
1763 print_level=low_print_level, common_iter_levels=3, &
1764 each_iter_names=s2a("TDDFT_SCF"), each_iter_values=(/10/), &
1765 add_last=add_last_numeric, filename="RESTART")
1766 CALL keyword_create(keyword, __location__, name="BACKUP_COPIES", &
1767 description="Specifies the maximum number of backup copies.", &
1768 usage="BACKUP_COPIES {int}", &
1769 default_i_val=1)
1770 CALL section_add_keyword(print_key, keyword)
1771 CALL keyword_release(keyword)
1772 CALL section_add_subsection(subsection, print_key)
1773 CALL section_release(print_key)
1774
1775 CALL cp_print_key_section_create(print_key, __location__, name="NTO_ANALYSIS", &
1776 description="Perform a natural transition orbital analysis.", &
1777 print_level=medium_print_level)
1778 CALL keyword_create(keyword, __location__, name="THRESHOLD", &
1779 description="Threshold for sum of NTO eigenvalues considered", &
1780 usage="Threshold 0.95", &
1781 n_var=1, &
1782 type_of_var=real_t, &
1783 default_r_val=0.975_dp)
1784 CALL section_add_keyword(print_key, keyword)
1785 CALL keyword_release(keyword)
1786 CALL keyword_create(keyword, __location__, name="INTENSITY_THRESHOLD", &
1787 description="Threshold for oscillator strength to screen states.", &
1788 usage="Intensity_threshold 0.01", &
1789 n_var=1, &
1790 type_of_var=real_t, &
1791 default_r_val=0.0_dp)
1792 CALL section_add_keyword(print_key, keyword)
1793 CALL keyword_release(keyword)
1794 CALL keyword_create(keyword, __location__, name="STATE_LIST", &
1795 description="Specifies a list of states for the NTO calculations.", &
1796 usage="STATE_LIST {integer} {integer} .. {integer}", &
1797 n_var=-1, type_of_var=integer_t)
1798 CALL section_add_keyword(print_key, keyword)
1799 CALL keyword_release(keyword)
1800 CALL keyword_create(keyword, __location__, name="CUBE_FILES", &
1801 description="Print NTOs on Cube Files", &
1802 usage="CUBE_FILES {logical}", repeats=.false., n_var=1, &
1803 default_l_val=.false., lone_keyword_l_val=.true., type_of_var=logical_t)
1804 CALL section_add_keyword(print_key, keyword)
1805 CALL keyword_release(keyword)
1806 CALL keyword_create(keyword, __location__, name="STRIDE", &
1807 description="The stride (X,Y,Z) used to write the cube file "// &
1808 "(larger values result in smaller cube files). Provide 3 numbers (for X,Y,Z) or"// &
1809 " 1 number valid for all components.", &
1810 usage="STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=integer_t)
1811 CALL section_add_keyword(print_key, keyword)
1812 CALL keyword_release(keyword)
1813 CALL keyword_create(keyword, __location__, name="APPEND", &
1814 description="append the cube files when they already exist", &
1815 default_l_val=.false., lone_keyword_l_val=.true.)
1816 CALL section_add_keyword(print_key, keyword)
1817 CALL keyword_release(keyword)
1818 CALL section_add_subsection(subsection, print_key)
1819 CALL section_release(print_key)
1820
1821 CALL cp_print_key_section_create(print_key, __location__, "MOS_MOLDEN", &
1822 description="Write the NTO in Molden file format, for visualisation.", &
1823 print_level=debug_print_level + 1, add_last=add_last_numeric, filename="MOS")
1824 CALL keyword_create(keyword, __location__, name="NDIGITS", &
1825 description="Specifies the number of significant digits retained. 3 is OK for visualization.", &
1826 usage="NDIGITS {int}", &
1827 default_i_val=3)
1828 CALL section_add_keyword(print_key, keyword)
1829 CALL keyword_release(keyword)
1830 CALL keyword_create(keyword, __location__, name="GTO_KIND", &
1831 description="Representation of Gaussian-type orbitals", &
1832 default_i_val=gto_spherical, &
1833 enum_c_vals=s2a("CARTESIAN", "SPHERICAL"), &
1834 enum_desc=s2a( &
1835 "Cartesian Gaussian orbitals. Use with caution", &
1836 "Spherical Gaussian orbitals. Incompatible with VMD"), &
1837 enum_i_vals=(/gto_cartesian, gto_spherical/))
1838 CALL section_add_keyword(print_key, keyword)
1839 CALL keyword_release(keyword)
1840 CALL section_add_subsection(subsection, print_key)
1841 CALL section_release(print_key)
1842
1843 CALL cp_print_key_section_create(print_key, __location__, name="NAMD_PRINT", &
1844 description="Controls the printout required for NAMD with NEWTONX.", &
1845 print_level=debug_print_level + 1, filename="CP2K_NEWTONX")
1846 CALL keyword_create(keyword, __location__, name="PRINT_VIRTUALS", &
1847 description="Print occupied AND virtual molecular orbital coefficients", &
1848 default_l_val=.false., lone_keyword_l_val=.true.)
1849 CALL section_add_keyword(print_key, keyword)
1850 CALL keyword_release(keyword)
1851 CALL keyword_create(keyword, __location__, name="PRINT_PHASES", &
1852 description="Print phases of occupied and virtuals MOs.", &
1853 default_l_val=.false., lone_keyword_l_val=.true.)
1854 CALL section_add_keyword(print_key, keyword)
1855 CALL keyword_release(keyword)
1856 CALL keyword_create(keyword, __location__, name="SCALE_WITH_PHASES", &
1857 description="Scale ES eigenvectors with phases of occupied and virtuals MOs.", &
1858 default_l_val=.false., lone_keyword_l_val=.true.)
1859 CALL section_add_keyword(print_key, keyword)
1860 CALL keyword_release(keyword)
1861 CALL section_add_subsection(subsection, print_key)
1862 CALL section_release(print_key)
1863
1864 !! SOC PRINT SECTION
1865 CALL cp_print_key_section_create(print_key, __location__, name="SOC_PRINT", &
1866 description="Controls the printout of the tddfpt2_soc modul", &
1867 print_level=debug_print_level + 1, filename="SOC")
1868 CALL keyword_create(keyword, __location__, name="UNIT_eV", &
1869 description="Will detrement if output in eVolt will be printef.", &
1870 default_l_val=.true., lone_keyword_l_val=.true.)
1871 CALL section_add_keyword(print_key, keyword)
1872 CALL keyword_release(keyword)
1873 CALL keyword_create(keyword, __location__, name="UNIT_wn", &
1874 description="Will detrement if output in wavenumbers will be printed.", &
1875 default_l_val=.false., lone_keyword_l_val=.true.)
1876 CALL section_add_keyword(print_key, keyword)
1877 CALL keyword_release(keyword)
1878 CALL keyword_create(keyword, __location__, name="SPLITTING", &
1879 description="Will add the SOC-Splitting as additional output", &
1880 default_l_val=.false., lone_keyword_l_val=.true.)
1881 CALL section_add_keyword(print_key, keyword)
1882 CALL keyword_release(keyword)
1883 CALL keyword_create(keyword, __location__, name="SOME", &
1884 description="Will add the SOC-Matrix as additional output in a different file", &
1885 default_l_val=.false., lone_keyword_l_val=.true.)
1886 CALL section_add_keyword(print_key, keyword)
1887 CALL keyword_release(keyword)
1888 CALL section_add_subsection(subsection, print_key)
1889 CALL section_release(print_key)
1890
1891 CALL cp_print_key_section_create(print_key, __location__, name="FORCES", &
1892 description="Controls the calculation and printing of excited state forces. "// &
1893 "This needs a RUN_TYPE that includes force evaluation, e.g. ENERGY_FORCE", &
1894 print_level=debug_print_level, filename="TDFORCE")
1895 CALL keyword_create(keyword, __location__, name="LIST", &
1896 description="Specifies a list of states for the force calculations.", &
1897 usage="LIST {integer} {integer} .. {integer}", repeats=.true., &
1898 n_var=-1, type_of_var=integer_t)
1899 CALL section_add_keyword(print_key, keyword)
1900 CALL keyword_release(keyword)
1901 CALL keyword_create(keyword, __location__, name="THRESHOLD", &
1902 description="Threshold for oszillator strength to screen states.", &
1903 usage="Threshold 0.01", &
1904 n_var=1, &
1905 type_of_var=real_t, &
1906 default_r_val=0.0_dp)
1907 CALL section_add_keyword(print_key, keyword)
1908 CALL keyword_release(keyword)
1909 CALL section_add_subsection(subsection, print_key)
1910 CALL section_release(print_key)
1911
1912 CALL section_add_subsection(section, subsection)
1913 CALL section_release(subsection)
1914
1915 END SUBROUTINE create_tddfpt2_section
1916
1917! **************************************************************************************************
1918!> \brief creates the stda input section (simplified Tamm Dancoff Approximation)
1919!> \param section the section to create
1920! **************************************************************************************************
1921 SUBROUTINE create_stda_section(section)
1922 TYPE(section_type), POINTER :: section
1923
1924 TYPE(keyword_type), POINTER :: keyword
1925
1926 cpassert(.NOT. ASSOCIATED(section))
1927 CALL section_create(section, __location__, name="sTDA", &
1928 description="parameters needed and setup for sTDA calculations", &
1929 n_keywords=3, n_subsections=0, repeats=.false.)
1930 NULLIFY (keyword)
1931
1932 CALL keyword_create(keyword, __location__, name="FRACTION", &
1933 variants=(/"HFX_FRACTION"/), &
1934 description="The fraction of TB Hartree-Fock exchange to use in the Kernel. "// &
1935 "0.0 implies no HFX part is used in the kernel. ", &
1936 usage="FRACTION 0.0", default_r_val=0.0_dp)
1937 CALL section_add_keyword(section, keyword)
1938 CALL keyword_release(keyword)
1939
1940 ! even if scaling parameter for exchange FRACTION (see above) is zero, the semi-empirical electron repulsion
1941 ! operator for exchange is not, so that a keyword is required to switch off sTDA exchange (if wanted)
1942 CALL keyword_create(keyword, __location__, name="DO_EXCHANGE", &
1943 description="Explicitly including or switching off sTDA exchange", &
1944 usage="DO_EXCHANGE", default_l_val=.true., lone_keyword_l_val=.true.)
1945 CALL section_add_keyword(section, keyword)
1946 CALL keyword_release(keyword)
1947
1948 CALL keyword_create(keyword, __location__, name="DO_EWALD", &
1949 description="Use Ewald type method for Coulomb interaction", &
1950 usage="DO_EWALD", default_l_val=.false., lone_keyword_l_val=.true.)
1951 CALL section_add_keyword(section, keyword)
1952 CALL keyword_release(keyword)
1953
1954 CALL keyword_create(keyword, __location__, name="EPS_TD_FILTER", &
1955 description="Threshold for filtering the transition density matrix", &
1956 usage="EPS_TD_FILTER epsf", default_r_val=1.e-10_dp)
1957 CALL section_add_keyword(section, keyword)
1958 CALL keyword_release(keyword)
1959
1960 CALL keyword_create(keyword, __location__, name="MATAGA_NISHIMOTO_CEXP", &
1961 description="Exponent used in Mataga-Nishimoto formula for Coulomb (alpha). "// &
1962 "Default value is method dependent!", &
1963 usage="MATAGA_NISHIMOTO_CEXP cexp", default_r_val=-99.0_dp)
1964 CALL section_add_keyword(section, keyword)
1965 CALL keyword_release(keyword)
1966
1967 CALL keyword_create(keyword, __location__, name="MATAGA_NISHIMOTO_XEXP", &
1968 description="Exponent used in Mataga-Nishimoto formula for Exchange (beta). "// &
1969 "Default value is method dependent!", &
1970 usage="MATAGA_NISHIMOTO_XEXP xexp", default_r_val=-99.0_dp)
1971 CALL section_add_keyword(section, keyword)
1972 CALL keyword_release(keyword)
1973
1974 CALL keyword_create(keyword, __location__, name="COULOMB_SR_CUT", &
1975 description="Maximum range of short range part of Coulomb interaction.", &
1976 usage="COULOMB_SR_CUT rcut", default_r_val=20.0_dp)
1977 CALL section_add_keyword(section, keyword)
1978 CALL keyword_release(keyword)
1979
1980 CALL keyword_create(keyword, __location__, name="COULOMB_SR_EPS", &
1981 description="Threshold for short range part of Coulomb interaction.", &
1982 usage="COULOMB_SR_EPS sreps", default_r_val=1.e-03_dp)
1983 CALL section_add_keyword(section, keyword)
1984 CALL keyword_release(keyword)
1985
1986 END SUBROUTINE create_stda_section
1987
1988! **************************************************************************************************
1989!> \brief creates an input section for electronic band structure calculations
1990!> \param section section to create
1991!> \par History
1992!> * 07.2023 created [Jan Wilhelm]
1993! **************************************************************************************************
1994 SUBROUTINE create_bandstructure_section(section)
1995 TYPE(section_type), POINTER :: section
1996
1997 TYPE(keyword_type), POINTER :: keyword
1998 TYPE(section_type), POINTER :: subsection
1999
2000 cpassert(.NOT. ASSOCIATED(section))
2001 CALL section_create(section, __location__, name="BANDSTRUCTURE", &
2002 description="Parameters needed to set up a calculation for "// &
2003 "electronic level energies of molecules and the electronic band "// &
2004 "structure of materials from post-SCF schemes (GW, perturbative "// &
2005 "spin-orbit coupling). Also, the density of states (DOS), "// &
2006 "projected density of states (PDOS), local density of states (LDOS), "// &
2007 "local valence band maximum (LVBM), local conduction band minimum "// &
2008 "(LCBM) and local band gap can be calculated. Please note that "// &
2009 "all methods in this section start from a Gamma-only DFT SCF. "// &
2010 "You need to make sure that the cell chosen in the DFT SCF is "// &
2011 "converged in the cell size. Band structures are computed "// &
2012 "for the primitive cell (i.e. the smallest possible unit cell of "// &
2013 "the input structure which is detected automatically). Moreover, "// &
2014 "spin-orbit coupling (SOC) on eigenvalues and band structures is "// &
2015 "available using Hartwigsen-Goedecker-Hutter "// &
2016 "pseudopotentials.", &
2017 n_keywords=1, n_subsections=1, repeats=.false.)
2018
2019 NULLIFY (keyword, subsection)
2020 CALL keyword_create(keyword, __location__, &
2021 name="_SECTION_PARAMETERS_", &
2022 description="Controls the activation of the band structure calculation.", &
2023 default_l_val=.false., &
2024 lone_keyword_l_val=.true.)
2025 CALL section_add_keyword(section, keyword)
2026 CALL keyword_release(keyword)
2027
2028 ! here we generate a subsection for getting a k-point path for the bandstructure
2029 CALL create_kpoint_set_section(subsection, "BANDSTRUCTURE_PATH")
2030 CALL section_add_subsection(section, subsection)
2031 CALL section_release(subsection)
2032
2033 CALL create_gw_section(subsection)
2034 CALL section_add_subsection(section, subsection)
2035 CALL section_release(subsection)
2036
2037 CALL create_soc_section(subsection)
2038 CALL section_add_subsection(section, subsection)
2039 CALL section_release(subsection)
2040
2041 CALL create_dos_section(subsection)
2042 CALL section_add_subsection(section, subsection)
2043 CALL section_release(subsection)
2044
2045 END SUBROUTINE create_bandstructure_section
2046
2047! **************************************************************************************************
2048!> \brief creates an input section for a GW calculation for the electronic band structure
2049!> \param section section to create
2050!> \par History
2051!> * 07.2023 created [Jan Wilhelm]
2052! **************************************************************************************************
2053 SUBROUTINE create_gw_section(section)
2054 TYPE(section_type), POINTER :: section
2055
2056 TYPE(keyword_type), POINTER :: keyword
2057 TYPE(section_type), POINTER :: print_key, subsection
2058
2059 cpassert(.NOT. ASSOCIATED(section))
2060 CALL section_create(section, __location__, name="GW", &
2061 description="Parameters needed to set up a GW calculation for "// &
2062 "electronic level energies $\varepsilon_{n\mathbf{k}}^{G_0W_0}$ "// &
2063 "of molecules and the band structure of materials: "// &
2064 "$\varepsilon_{n\mathbf{k}}^{G_0W_0}= "// &
2065 "\varepsilon_{n\mathbf{k}}^\text{DFT}+\Sigma_{n\mathbf{k}} "// &
2066 "-v^\text{xc}_{n\mathbf{k}}$. "// &
2067 "For the GW algorithm for molecules, see "// &
2068 "<https://doi.org/10.1021/acs.jctc.0c01282>. "// &
2069 "For 2D materials, see <https://doi.org/10.1021/acs.jctc.3c01230>.", &
2070 n_keywords=1, n_subsections=1, repeats=.false.)
2071
2072 NULLIFY (keyword)
2073 CALL keyword_create(keyword, __location__, &
2074 name="_SECTION_PARAMETERS_", &
2075 description="Controls the activation of the GW calculation.", &
2076 default_l_val=.false., &
2077 lone_keyword_l_val=.true.)
2078 CALL section_add_keyword(section, keyword)
2079 CALL keyword_release(keyword)
2080
2081 CALL keyword_create(keyword, __location__, name="NUM_TIME_FREQ_POINTS", &
2082 description="Number of discrete points for the imaginary-time "// &
2083 "grid and the imaginary-frequency grid. The more points, the more "// &
2084 "precise is the calculation. Typically, 10 points are good "// &
2085 "for 0.1 eV precision of band structures and molecular energy "// &
2086 "levels, 20 points for 0.03 eV precision, "// &
2087 "and 30 points for 0.01 eV precision, see Table I in "// &
2088 "<https://doi.org/10.1021/acs.jctc.0c01282>. GW computation time "// &
2089 "increases linearly with `NUM_TIME_FREQ_POINTS`.", &
2090 usage="NUM_TIME_FREQ_POINTS 30", &
2091 default_i_val=30)
2092 CALL section_add_keyword(section, keyword)
2093 CALL keyword_release(keyword)
2094
2095 CALL keyword_create(keyword, __location__, name="EPS_FILTER", &
2096 description="Determines a threshold for the DBCSR based sparse "// &
2097 "multiplications. Normally, `EPS_FILTER` determines accuracy "// &
2098 "and timing of low-scaling GW calculations. (Lower filter means "// &
2099 "higher numerical precision, but higher computational cost.)", &
2100 usage="EPS_FILTER 1.0E-6", &
2101 default_r_val=1.0e-8_dp)
2102 CALL section_add_keyword(section, keyword)
2103 CALL keyword_release(keyword)
2104
2105 CALL keyword_create(keyword, __location__, name="REGULARIZATION_RI", &
2106 description="Parameter for RI regularization, setting a negative "// &
2107 "value triggers the default value. Affects RI basis set convergence "// &
2108 "but in any case large RI basis will give RI basis set convergence.", &
2109 usage="REGULARIZATION_RI 1.0E-4", &
2110 default_r_val=-1.0_dp)
2111 CALL section_add_keyword(section, keyword)
2112 CALL keyword_release(keyword)
2113
2114 CALL keyword_create(keyword, __location__, name="CUTOFF_RADIUS_RI", &
2115 description="The cutoff radius (in Angstrom) for the truncated "// &
2116 "Coulomb operator. The larger the cutoff radius, the faster "// &
2117 "converges the resolution of the identity (RI) with respect to the "// &
2118 "RI basis set size. Larger cutoff radius means higher computational "// &
2119 "cost.", &
2120 usage="CUTOFF_RADIUS_RI 3.0", &
2121 default_r_val=cp_unit_to_cp2k(value=3.0_dp, unit_str="angstrom"), &
2122 type_of_var=real_t, unit_str="angstrom")
2123 CALL section_add_keyword(section, keyword)
2124 CALL keyword_release(keyword)
2125
2126 CALL keyword_create(keyword, __location__, name="MEMORY_PER_PROC", &
2127 description="Specify the available memory per MPI process. Set "// &
2128 "`MEMORY_PER_PROC` as accurately as possible for good performance. If "// &
2129 "`MEMORY_PER_PROC` is set lower as the actually available "// &
2130 "memory per MPI process, the performance will be "// &
2131 "bad; if `MEMORY_PER_PROC` is set higher as the actually "// &
2132 "available memory per MPI process, the program might run out of "// &
2133 "memory. You can calculate `MEMORY_PER_PROC` as follows: "// &
2134 "Get the memory per node on your machine, mem_per_node "// &
2135 "(for example, from a supercomputer website, typically between "// &
2136 "100 GB and 2 TB), get the number of "// &
2137 "MPI processes per node, n_MPI_proc_per_node"// &
2138 " (for example from your run-script; if you "// &
2139 "use slurm, the number behind '--ntasks-per-node' is the number "// &
2140 "of MPI processes per node). Then calculate "// &
2141 "`MEMORY_PER_PROC` = mem_per_node / n_MPI_proc_per_node "// &
2142 "(typically between 2 GB and 50 GB). Unit of keyword: Gigabyte (GB).", &
2143 usage="MEMORY_PER_PROC 16", &
2144 default_r_val=2.0_dp)
2145 CALL section_add_keyword(section, keyword)
2146 CALL keyword_release(keyword)
2147
2148 CALL keyword_create(keyword, __location__, name="APPROX_KP_EXTRAPOL", &
2149 description="If true, use only a 4x4 kpoint mesh for frequency "// &
2150 "points $\omega_j, j \ge 2$ (instead of a 4x4 and 6x6 k-point mesh). "// &
2151 "The k-point extrapolation of $W_{PQ}(i\omega_j,\mathbf{q})$ "// &
2152 "is done approximately from $W_{PQ}(i\omega_1,\mathbf{q})$.", &
2153 usage="APPROX_KP_EXTRAPOL", &
2154 default_l_val=.false., lone_keyword_l_val=.true.)
2155 CALL section_add_keyword(section, keyword)
2156 CALL keyword_release(keyword)
2157
2158 CALL keyword_create(keyword, __location__, name="SIZE_LATTICE_SUM", &
2159 description="Parameter determines how many neighbor cells $\mathbf{R}$ "// &
2160 "are used for computing "// &
2161 "$V_{PQ}(\mathbf{k}) = "// &
2162 "\sum_{\mathbf{R}} e^{i\mathbf{k}\cdot\mathbf{R}}\,\langle P, "// &
2163 "\text{cell}{=}\mathbf{0}|1/r|Q,\text{cell}{=}\mathbf{R}\rangle$. "// &
2164 "Normally, parameter does not need to be touched.", &
2165 usage="SIZE_LATTICE_SUM 4", &
2166 default_i_val=3)
2167 CALL section_add_keyword(section, keyword)
2168 CALL keyword_release(keyword)
2169
2170 CALL keyword_create( &
2171 keyword, __location__, name="KPOINTS_W", &
2172 description="Monkhorst-Pack k-point mesh of size N_x, N_y, N_z for calculating "// &
2173 "$W_{PQ}^\mathbf{R}=\int_\text{BZ}\frac{d\mathbf{k}}{\Omega_\text{BZ}}\, "// &
2174 "e^{-i\mathbf{k}\cdot\mathbf{R}}\,W_{PQ}(\mathbf{k})$. "// &
2175 αα"For non-periodic directions , choose N_ = 1. "// &
2176 "Automatic choice of the k-point mesh for negative "// &
2177 "values, i.e. KPOINTS_W -1 -1 -1. "// &
2178 "K-point extrapolation of W is automatically switched on.", &
2179 usage="KPOINTS_W N_x N_y N_z", &
2180 n_var=3, type_of_var=integer_t, default_i_vals=(/-1, -1, -1/))
2181 CALL section_add_keyword(section, keyword)
2182 CALL keyword_release(keyword)
2183
2184 CALL keyword_create(keyword, __location__, name="HEDIN_SHIFT", &
2185 description="If true, use Hedin's shift in G0W0, evGW and evGW0. "// &
2186 "Details see in Li et al. JCTC 18, 7570 "// &
2187 "(2022), Figure 1. G0W0 with Hedin's shift should give "// &
2188 "similar GW eigenvalues as evGW0; at a lower "// &
2189 "computational cost.", &
2190 usage="HEDIN_SHIFT", &
2191 default_l_val=.false., &
2192 lone_keyword_l_val=.true.)
2193 CALL section_add_keyword(section, keyword)
2194 CALL keyword_release(keyword)
2195
2196 CALL keyword_create(keyword, __location__, name="FREQ_MAX_FIT", &
2197 description=Σω"For analytic continuation, a fit on (i) is performed. "// &
2198 Σω"This fit is then evaluated at a real frequency, (), which is used "// &
2199 "in the quasiparticle equation "// &
2200 "$\varepsilon_{n\mathbf{k}}^{G_0W_0}= "// &
2201 "\varepsilon_{n\mathbf{k}}^\text{DFT}+\Sigma_{n\mathbf{k}} "// &
2202 "-v^\text{xc}_{n\mathbf{k}}$. The keyword FREQ_MAX_FIT "// &
2203 Σω"determines fitting range for the self-energy (i) on "// &
2204 ωω"imaginary axis: i*[0, _max] for empty orbitals/bands, i*[-_max,0] "// &
2205 ω"for occ orbitals. A smaller _max might lead to better numerical "// &
2206 "stability (i.e., if you observe clearly wrong GW eigenvalues/bands "// &
2207 ω"around HOMO/LUMO, decreasing _max might fix this issue). "// &
2208 ω"A small benchmark of _max is contained in Fig. 5 of "// &
2209 "J. Wilhelm et al., JCTC 12, 3623-3635 (2016). "// &
2210 ω"Note that we used _max = 1 Ha = 27.211 eV in the benchmark "// &
2211 "M. Azizi et al., PRB 109, 245101 (2024).", &
2212 unit_str="eV", &
2213 usage="FREQ_MAX_FIT 20.0", &
2214 default_r_val=cp_unit_to_cp2k(value=10.0_dp, unit_str="eV"))
2215 CALL section_add_keyword(section, keyword)
2216 CALL keyword_release(keyword)
2217
2218 NULLIFY (subsection, print_key)
2219 CALL section_create(subsection, __location__, name="PRINT", &
2220 description="Printing of GW restarts.", &
2221 n_keywords=0, n_subsections=1, repeats=.false.)
2222 CALL cp_print_key_section_create(print_key, __location__, "RESTART", &
2223 description="Controls the printing of restart files "// &
2224 χΣ"for , W, .", &
2225 filename="", print_level=low_print_level, &
2226 common_iter_levels=3)
2227 CALL section_add_subsection(subsection, print_key)
2228 CALL section_release(print_key)
2229
2230 CALL section_add_subsection(section, subsection)
2231 CALL section_release(subsection)
2232
2233 END SUBROUTINE create_gw_section
2234
2235! **************************************************************************************************
2236!> \brief creates an input section for calculation SOC for the electronic band structure
2237!> \param section section to create
2238!> \par History
2239!> * 09.2023 created [Jan Wilhelm]
2240! **************************************************************************************************
2241 SUBROUTINE create_soc_section(section)
2242 TYPE(section_type), POINTER :: section
2243
2244 TYPE(keyword_type), POINTER :: keyword
2245
2246 cpassert(.NOT. ASSOCIATED(section))
2247 CALL section_create(section, __location__, name="SOC", &
2248 description="Switch on or off spin-orbit coupling. Use SOC "// &
2249 "parameters from non-local pseudopotentials as given in "// &
2250 "Hartwigsen, Goedecker, Hutter, Eq.(18), (19), "// &
2251 "<https://doi.org/10.1103/PhysRevB.58.3641>, "// &
2252 "$V_{\mu\nu}^{\mathrm{SOC}, (\alpha)} = "// &
2253 "(\hbar/2) \langle \phi_\mu | \sum_l \Delta "// &
2254 "V_l^\mathrm{SO}(\mathbf{r},\mathbf{r}') "// &
2255 "L^{(\alpha)} | \phi_\nu \rangle, "// &
2256 "\alpha = x, y, z$.", &
2257 n_keywords=1, n_subsections=1, repeats=.false.)
2258
2259 NULLIFY (keyword)
2260 CALL keyword_create(keyword, __location__, &
2261 name="_SECTION_PARAMETERS_", &
2262 description="Controls the activation of the SOC calculation.", &
2263 default_l_val=.false., &
2264 lone_keyword_l_val=.true.)
2265 CALL section_add_keyword(section, keyword)
2266 CALL keyword_release(keyword)
2267
2268 CALL keyword_create(keyword, __location__, name="ENERGY_WINDOW", &
2269 description="Apply SOC only for states with eigenvalues in the "// &
2270 "interval $[\varepsilon_\mathrm{VBM}-E_\mathrm{window}/2, "// &
2271 "\varepsilon_\mathrm{CBM}+E_\mathrm{window}/2]$. Might be necessary "// &
2272 "to use for large systems to prevent numerical instabilities.", &
2273 usage="ENERGY_WINDOW 5.0", &
2274 default_r_val=cp_unit_to_cp2k(value=40.0_dp, unit_str="eV"), &
2275 unit_str="eV")
2276 CALL section_add_keyword(section, keyword)
2277 CALL keyword_release(keyword)
2278
2279 END SUBROUTINE create_soc_section
2280
2281! **************************************************************************************************
2282!> \brief input section for computing the density of states and the projected density of states
2283!> \param section section to create
2284!> \par History
2285!> * 09.2023 created [Jan Wilhelm]
2286! **************************************************************************************************
2287 SUBROUTINE create_dos_section(section)
2288 TYPE(section_type), POINTER :: section
2289
2290 TYPE(keyword_type), POINTER :: keyword
2291 TYPE(section_type), POINTER :: subsection
2292
2293 cpassert(.NOT. ASSOCIATED(section))
2294 CALL section_create(section, __location__, name="DOS", &
2295 description="Parameters needed to calculate the density of states "// &
2296 "(DOS) and the projected density of states (PDOS).", &
2297 n_keywords=1, n_subsections=1, repeats=.false.)
2298
2299 NULLIFY (keyword)
2300 CALL keyword_create(keyword, __location__, &
2301 name="_SECTION_PARAMETERS_", &
2302 description="Controls the activation of the DOS calculation.", &
2303 default_l_val=.false., &
2304 lone_keyword_l_val=.true.)
2305 CALL section_add_keyword(section, keyword)
2306 CALL keyword_release(keyword)
2307
2308 CALL keyword_create(keyword, __location__, name="ENERGY_WINDOW", &
2309 description="Print DOS and PDOS in the energy window "// &
2310 "$[\varepsilon_\mathrm{VBM}-E_\mathrm{window}/2, "// &
2311 "\varepsilon_\mathrm{CBM}+E_\mathrm{window}/2]$,"// &
2312 " where VBM is the valence "// &
2313 "band maximum (or highest occupied molecular orbital, HOMO, for "// &
2314 "molecules) and CBM the conduction band minimum (or lowest "// &
2315 "unoccupied molecular orbital, LUMO, for molecules).", &
2316 usage="ENERGY_WINDOW 5.0", &
2317 default_r_val=cp_unit_to_cp2k(value=10.0_dp, unit_str="eV"), &
2318 unit_str="eV")
2319 CALL section_add_keyword(section, keyword)
2320 CALL keyword_release(keyword)
2321
2322 CALL keyword_create(keyword, __location__, name="ENERGY_STEP", &
2323 description="Resolution of the energy E when computing the $\rho(E)$.", &
2324 usage="ENERGY_STEP 0.01", &
2325 default_r_val=cp_unit_to_cp2k(value=0.01_dp, unit_str="eV"), &
2326 unit_str="eV")
2327 CALL section_add_keyword(section, keyword)
2328 CALL keyword_release(keyword)
2329
2330 CALL keyword_create(keyword, __location__, name="BROADENING", &
2331 description=α"Broadening in Gaussians used in the DOS; "// &
2332 "$\rho(E) = \sum_n \exp(((E-\varepsilon_n)/\alpha)^2)/("// &
2333 " \sqrt{2\pi} \alpha)$.", &
2334 usage="BROADENING 0.01", &
2335 default_r_val=cp_unit_to_cp2k(value=0.01_dp, unit_str="eV"), &
2336 unit_str="eV")
2337 CALL section_add_keyword(section, keyword)
2338 CALL keyword_release(keyword)
2339
2340 CALL keyword_create( &
2341 keyword, __location__, name="KPOINTS", &
2342 description="Monkhorst-Pack k-point mesh of size N_x, N_y, N_z for calculating "// &
2343 "the density of states (DOS). In GW, the KPOINT_DOS mesh is thus used as k-point "// &
2344 αα"mesh for the self-energy. For non-periodic directions , choose N_ = 1. "// &
2345 "Automatic choice of the k-point mesh for negative "// &
2346 α"values, i.e. KPOINTS_DOS -1 -1 -1 (automatic choice: N_ = 1 in non-periodic "// &
2347 "direction, 8 k-points in periodic direction). If you like to compute a "// &
2348 "band structure along a k-path, you can specify the k-path in "// &
2349 "&KPOINT_SET.", &
2350 usage="KPOINTS N_x N_y N_z", &
2351 n_var=3, type_of_var=integer_t, default_i_vals=(/-1, -1, -1/))
2352 CALL section_add_keyword(section, keyword)
2353 CALL keyword_release(keyword)
2354
2355 NULLIFY (subsection)
2356 CALL create_ldos_section(subsection)
2357 CALL section_add_subsection(section, subsection)
2358 CALL section_release(subsection)
2359
2360 END SUBROUTINE create_dos_section
2361
2362! **************************************************************************************************
2363!> \brief ...
2364!> \param section ...
2365! **************************************************************************************************
2366 SUBROUTINE create_ldos_section(section)
2367 TYPE(section_type), POINTER :: section
2368
2369 TYPE(keyword_type), POINTER :: keyword
2370
2371 cpassert(.NOT. ASSOCIATED(section))
2372 CALL section_create(section, __location__, name="LDOS", &
2373 description="Parameters needed to calculate the local density "// &
2374 "of states (LDOS). "// &
2375 "The LDOS is computed as $\rho(\mathbf{r},E) = "// &
2376 "\sum\limits_{n,\mathbf{k}}"// &
2377 " |\psi_{n\mathbf{k}}(r)|^2\, w_\mathbf{k}\, g(E-\varepsilon_{n\mathbf{k}})$ "// &
2378 "using the Gaussian weight function "// &
2379 "$g(x) = \exp(x^2/\alpha^2)/(\sqrt{2\pi}\alpha)$, $\alpha$ is the broadening "// &
2380 "from the &DOS section, and the k-point weight "// &
2381 "$w_\mathbf{k}$. The k-mesh is taken from the &DOS section.", &
2382 n_keywords=2, repeats=.false.)
2383
2384 NULLIFY (keyword)
2385 CALL keyword_create(keyword, __location__, &
2386 name="_SECTION_PARAMETERS_", &
2387 description="Activates the local VBM CBM gap calculation.", &
2388 default_l_val=.false., &
2389 lone_keyword_l_val=.true.)
2390 CALL section_add_keyword(section, keyword)
2391 CALL keyword_release(keyword)
2392
2393 CALL keyword_create(keyword, __location__, name="INTEGRATION", &
2394 description="Defines whether the LDOS is integrated along a "// &
2395 "coordinate. As an example, for INTEGRATION Z, the LDOS "// &
2396 "$\rho(x,y,E) = \int dz\, \rho(x,y,z,E)$ is computed.", &
2397 usage="INTEGRATION Z", &
2398 enum_c_vals=s2a("X", "Y", "Z", "NONE"), &
2399 enum_i_vals=(/int_ldos_x, int_ldos_y, int_ldos_z, int_ldos_none/), &
2400 enum_desc=s2a("Integrate over x coordinate (not yet implemented).", &
2401 "Integrate over y coordinate (not yet implemented).", &
2402 "Integrate over z coordinate.", &
2403 "No integration, print cube file as function "// &
2404 "of x,y,z (not yet implemented)."), &
2405 default_i_val=int_ldos_z)
2406 CALL section_add_keyword(section, keyword)
2407 CALL keyword_release(keyword)
2408
2409 CALL keyword_create( &
2410 keyword, __location__, name="BIN_MESH", &
2411 description="Mesh of size n x m for binning the space coordinates x and y of "// &
2412 "the LDOS $\rho(x,y,E)$. If -1, no binning is performed and the "// &
2413 "fine x, y resolution of the electron density from SCF is used.", &
2414 usage="BIN_MESH n m", &
2415 n_var=2, type_of_var=integer_t, default_i_vals=(/10, 10/))
2416 CALL section_add_keyword(section, keyword)
2417 CALL keyword_release(keyword)
2418
2419 END SUBROUTINE create_ldos_section
2420
2421! **************************************************************************************************
2422!> \brief creates an input section for a tip scan calculation
2423!> \param section section to create
2424!> \par History
2425!> * 04.2021 created [JGH]
2426! **************************************************************************************************
2427 SUBROUTINE create_tipscan_section(section)
2428 TYPE(section_type), POINTER :: section
2429
2430 TYPE(keyword_type), POINTER :: keyword
2431
2432 cpassert(.NOT. ASSOCIATED(section))
2433 CALL section_create(section, __location__, name="TIP_SCAN", &
2434 description="Parameters needed to set up a Tip Scan. "// &
2435 "Needs external definition of tip induced field.", &
2436 n_keywords=1, n_subsections=1, repeats=.false.)
2437
2438 NULLIFY (keyword)
2439
2440 CALL keyword_create(keyword, __location__, &
2441 name="_SECTION_PARAMETERS_", &
2442 description="Controls the activation of the Tip Scan procedure", &
2443 default_l_val=.false., &
2444 lone_keyword_l_val=.true.)
2445 CALL section_add_keyword(section, keyword)
2446 CALL keyword_release(keyword)
2447
2448 CALL keyword_create(keyword, __location__, name="SCAN_DIRECTION", &
2449 description="Defines scan direction and scan type(line, plane).", &
2450 usage="SCAN_DIRECTION XY", &
2451 enum_c_vals=s2a("X", "Y", "Z", "XY", "XZ", "YZ", "XYZ"), &
2452 enum_i_vals=(/scan_x, scan_y, scan_z, scan_xy, scan_xz, scan_yz, scan_xyz/), &
2453 default_i_val=scan_xy)
2454 CALL section_add_keyword(section, keyword)
2455 CALL keyword_release(keyword)
2456
2457 CALL keyword_create(keyword, __location__, name="REFERENCE_POINT", &
2458 description="The reference point to define the absolute position of the scan. ", &
2459 usage="REFERENCE_POINT 0.0 0.0 1.0", &
2460 n_var=3, default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/), type_of_var=real_t, &
2461 unit_str="angstrom")
2462 CALL section_add_keyword(section, keyword)
2463 CALL keyword_release(keyword)
2464
2465 CALL keyword_create(keyword, __location__, name="SCAN_POINTS", &
2466 description="Number of points calculated for each scan direction.", &
2467 usage="SCAN_POINTS 20 20", &
2468 n_var=-1, type_of_var=integer_t)
2469 CALL section_add_keyword(section, keyword)
2470 CALL keyword_release(keyword)
2471
2472 CALL keyword_create(keyword, __location__, name="SCAN_STEP", &
2473 description="Step size for each scan direction.", &
2474 usage="SCAN_STEP 0.01 0.01", &
2475 n_var=-1, type_of_var=real_t, unit_str="angstrom")
2476 CALL section_add_keyword(section, keyword)
2477 CALL keyword_release(keyword)
2478
2479 CALL keyword_create(keyword, __location__, name="TIP_FILENAME", &
2480 description="Filename of tip potential defined in cube file format.", &
2481 usage="TIP_FILENAME <filename>", &
2482 type_of_var=lchar_t)
2483 CALL section_add_keyword(section, keyword)
2484 CALL keyword_release(keyword)
2485
2486 END SUBROUTINE create_tipscan_section
2487
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public putrino2000
integer, save, public weber2009
integer, save, public kondov2007
integer, save, public luber2014
integer, save, public iannuzzi2005
integer, save, public sebastiani2001
integer, save, public putrino2002
integer, save, public futera2017
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 int_ldos_y
integer, parameter, public use_mom_ref_coac
integer, parameter, public tddfpt_dipole_berry
integer, parameter, public oe_saop
integer, parameter, public do_no_et
integer, parameter, public current_orb_center_wannier
integer, parameter, public scan_x
integer, parameter, public scan_xyz
integer, parameter, public use_mom_ref_user
integer, parameter, public tddfpt_kernel_none
integer, parameter, public use_mom_ref_com
integer, parameter, public gto_cartesian
integer, parameter, public gto_spherical
integer, parameter, public current_gauge_atom
integer, parameter, public current_gauge_r
integer, parameter, public oe_none
integer, parameter, public ot_precond_full_kinetic
integer, parameter, public current_gauge_r_and_step_func
integer, parameter, public oe_shift
integer, parameter, public int_ldos_x
integer, parameter, public current_orb_center_box
integer, parameter, public tddfpt_dipole_velocity
integer, parameter, public current_orb_center_common
integer, parameter, public ot_precond_full_single
integer, parameter, public scan_xy
integer, parameter, public scan_xz
integer, parameter, public tddfpt_kernel_full
integer, parameter, public ot_precond_none
integer, parameter, public scan_y
integer, parameter, public int_ldos_z
integer, parameter, public ot_precond_full_single_inverse
integer, parameter, public current_orb_center_atom
integer, parameter, public scan_z
integer, parameter, public do_spin_density
integer, parameter, public tddfpt_dipole_length
integer, parameter, public use_mom_ref_zero
integer, parameter, public oe_lb
integer, parameter, public tddfpt_kernel_stda
integer, parameter, public int_ldos_none
integer, parameter, public do_et_ddapc
integer, parameter, public ot_precond_s_inverse
integer, parameter, public do_full_density
integer, parameter, public scan_yz
integer, parameter, public oe_gllb
integer, parameter, public ot_precond_full_all
input section for atomic properties
subroutine, public create_atprop_section(section)
Creates the ATOMIC section.
function that build the dft section of the input
subroutine, public create_mgrid_section(section, create_subsections)
creates the multigrid
subroutine, public create_interp_section(section)
creates the interpolation section
function that build the kpoints section of the input
subroutine, public create_kpoint_set_section(section, section_name)
...
subroutine, public create_localize_section(section)
parameters fo the localization of wavefunctions
function that build the dft section of the input
subroutine, public create_properties_section(section)
Create the PROPERTIES section.
function that build the QS section of the input
subroutine, public create_lrigpw_section(section)
input section for optional parameters for LRIGPW LRI: local resolution of identity
subroutine, public create_ddapc_restraint_section(section, section_name)
...
function that builds the resp section of the input
subroutine, public create_resp_section(section)
Creates the RESP section.
function that build the xc section of the input
subroutine, public create_xc_section(section)
creates the input section for the xc 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 lchar_t
integer, parameter, public logical_t
integer, parameter, public char_t
integer, parameter, public integer_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Utilities for string manipulations.
represent a keyword in the input
represent a section of the input file