68#include "./base/base_uses.f90" 
   73   LOGICAL, 
PRIVATE, 
PARAMETER :: debug_this_module = .true.
 
   74   CHARACTER(len=*), 
PARAMETER, 
PRIVATE :: moduleN = 
'input_cp2k_properties_dft' 
   91      cpassert(.NOT. 
ASSOCIATED(section))
 
   93                          description=
"This section is used to set up the PROPERTIES calculation.", &
 
   94                          n_keywords=0, n_subsections=6, repeats=.false.)
 
   96      NULLIFY (subsection, keyword)
 
   98      CALL create_linres_section(subsection, create_subsections=.true.)
 
  102      CALL create_et_coupling_section(subsection)
 
  115                                       description=
"This section is used to print the density derived atomic point charges. "// &
 
  116                                       "The fit of the charges is controlled through the DENSITY_FITTING section", &
 
  118      CALL keyword_create(keyword, __location__, name=
"TYPE_OF_DENSITY", &
 
  119                          description=
"Specifies the type of density used for the fitting", &
 
  120                          usage=
"TYPE_OF_DENSITY (FULL|SPIN)", &
 
  121                          enum_c_vals=
s2a(
"FULL", 
"SPIN"), &
 
  123                          enum_desc=
s2a(
"Full density", 
"Spin density"), &
 
  130      CALL create_tddfpt2_section(subsection)
 
  134      CALL create_rixs_section(subsection)
 
  138      CALL create_bandstructure_section(subsection)
 
  142      CALL create_tipscan_section(subsection)
 
 
  153   SUBROUTINE create_rixs_section(section)
 
  158      cpassert(.NOT. 
ASSOCIATED(section))
 
  160      NULLIFY (keyword, subsection, print_key)
 
  163                          description=
"Resonant Inelastic Xray Scattering using XAS_TDP and TDDFPT.", &
 
  164                          n_keywords=1, n_subsections=3, repeats=.false., &
 
  167      CALL create_tddfpt2_section(subsection)
 
  175      CALL section_create(subsection, __location__, 
"PRINT", 
"Controls the printing of information "// &
 
  176                          "during RIXS calculations", repeats=.false.)
 
  179                                       description=
"Controles the printing of the RIXS spectrum "// &
 
  182                                       common_iter_levels=3)
 
  189   END SUBROUTINE create_rixs_section
 
  200   SUBROUTINE create_linres_section(section, create_subsections, default_set_tdlr)
 
  202      LOGICAL, 
INTENT(in)                                :: create_subsections
 
  203      LOGICAL, 
INTENT(IN), 
OPTIONAL                      :: default_set_tdlr
 
  205      INTEGER                                            :: def_max_iter, def_precond
 
  206      REAL(kind=
dp)                                      :: def_egap, def_eps, def_eps_filter
 
  210      CHARACTER(len=256)                      :: desc
 
  212      NULLIFY (keyword, print_key)
 
  214      IF (
PRESENT(default_set_tdlr)) 
THEN 
  217         def_eps_filter = 1.0e-15_dp
 
  220         desc = 
"Controls the parameters of the LINRES force calculations for excited states." 
  224         def_eps_filter = 0.0_dp
 
  227         desc = 
"The linear response is used to calculate one of the following properties: nmr, epr, raman, ..." 
  230      cpassert(.NOT. 
ASSOCIATED(section))
 
  232                          description=desc, n_keywords=5, n_subsections=2, repeats=.false., &
 
  236                          description=
"target accuracy for the convergence of the conjugate gradient.", &
 
  237                          usage=
"EPS 1.e-6", default_r_val=def_eps)
 
  242                          description=
"Filter threshold for response density matrix.", &
 
  243                          usage=
"EPS_FILTER 1.e-8", default_r_val=def_eps_filter)
 
  248                          description=
"Maximum number of conjugate gradient iteration to be performed for one optimization.", &
 
  249                          usage=
"MAX_ITER 200", default_i_val=def_max_iter)
 
  253      CALL keyword_create(keyword, __location__, name=
"RESTART_EVERY", &
 
  254                          description=
"Restart the conjugate gradient after the specified number of iterations.", &
 
  255                          usage=
"RESTART_EVERY 200", default_i_val=50)
 
  260         keyword, __location__, name=
"PRECONDITIONER", &
 
  261         description=
"Type of preconditioner to be used with all minimization schemes. "// &
 
  262         "They differ in effectiveness, cost of construction, cost of application. "// &
 
  263         "Properly preconditioned minimization can be orders of magnitude faster than doing nothing.", &
 
  264         usage=
"PRECONDITIONER FULL_ALL", &
 
  265         default_i_val=def_precond, &
 
  266         enum_c_vals=
s2a(
"FULL_ALL", 
"FULL_SINGLE_INVERSE", 
"FULL_SINGLE", 
"FULL_KINETIC", 
"FULL_S_INVERSE", &
 
  268         enum_desc=
s2a(
"Most effective state selective preconditioner based on diagonalization, "// &
 
  269                       "requires the ENERGY_GAP parameter to be an underestimate of the HOMO-LUMO gap. "// &
 
  270                       "This preconditioner is recommended for almost all systems, except very large systems where "// &
 
  271                       "make_preconditioner would dominate the total computational cost.", &
 
  272                       "Based on H-eS cholesky inversion, similar to FULL_SINGLE in preconditioning efficiency "// &
 
  273                       "but cheaper to construct, "// &
 
  274                       "might be somewhat less robust. Recommended for large systems.", &
 
  275                       "Based on H-eS diagonalisation, not as good as FULL_ALL, but somewhat cheaper to apply. ", &
 
  276                       "Cholesky inversion of S and T, fast construction, robust, and relatively good, "// &
 
  277                       "use for very large systems.", &
 
  278                       "Cholesky inversion of S, not as good as FULL_KINETIC, yet equally expensive.", &
 
  279                       "skip preconditioning"), &
 
  286                          description=
"Energy gap estimate [a.u.] for preconditioning", &
 
  287                          usage=
"ENERGY_GAP 0.1", &
 
  288                          default_r_val=def_egap)
 
  293                          description=
"Perform a linear response calculation every N-th step for MD run", &
 
  294                          usage=
"EVERY_N_STEP 50", default_i_val=1)
 
  299                          description=
"Restart the response calculation if the restart file exists", &
 
  301                          default_l_val=.false., lone_keyword_l_val=.true.)
 
  305      CALL keyword_create(keyword, __location__, name=
"WFN_RESTART_FILE_NAME", &
 
  306                          variants=(/
"RESTART_FILE_NAME"/), &
 
  307                          description=
"Root of the file names where to read the response functions from "// &
 
  308                          "which to restart the calculation of the linear response", &
 
  309                          usage=
"WFN_RESTART_FILE_NAME <FILENAME>", &
 
  314      IF (create_subsections) 
THEN 
  321         CALL create_current_section(subsection)
 
  325         CALL create_nmr_section(subsection)
 
  329         CALL create_spin_spin_section(subsection)
 
  333         CALL create_epr_section(subsection)
 
  337         CALL create_polarizability_section(subsection)
 
  341         CALL create_dcdr_section(subsection)
 
  345         CALL create_vcd_section(subsection)
 
  350                             description=
"printing of information during the linear response calculation", &
 
  354            print_key, __location__, 
"program_run_info", &
 
  355            description=
"Controls the printing of basic iteration information during the LINRES calculation", &
 
  361                                          description=
"Controls the dumping of restart file of the response wavefunction. "// &
 
  362                                          "For each set of response functions, i.e. for each perturbation, "// &
 
  363                                          "one different restart file is dumped. These restart files should be "// &
 
  364                                          "employed only to restart the same type of LINRES calculation, "// &
 
  365                                          "i.e. with the same perturbation.", &
 
  376   END SUBROUTINE create_linres_section
 
  384   SUBROUTINE create_dcdr_section(section)
 
  393      NULLIFY (keyword, print_key, subsection)
 
  395      cpassert(.NOT. 
ASSOCIATED(section))
 
  397      IF (.NOT. failure) 
THEN 
  399                             description=
"Compute analytical gradients the dipole moments.", &
 
  400                             n_keywords=50, n_subsections=1, repeats=.false.)
 
  402         CALL keyword_create(keyword, __location__, name=
"_SECTION_PARAMETERS_", &
 
  403                             description=
"controls the activation of the APT calculation", &
 
  405                             default_l_val=.false., &
 
  406                             lone_keyword_l_val=.true.)
 
  410         CALL keyword_create(keyword, __location__, name=
"LIST_OF_ATOMS", &
 
  411                             description=
"Specifies a list of atoms.", &
 
  412                             usage=
"LIST_OF_ATOMS {integer} {integer} .. {integer}", repeats=.true., &
 
  417         CALL keyword_create(keyword, __location__, name=
"DISTRIBUTED_ORIGIN", &
 
  418                             variants=(/
"DO_GAUGE"/), &
 
  419                             description=
"Use the distributed origin (DO) gauge?", &
 
  420                             usage=
"DISTRIBUTED_ORIGIN T", &
 
  421                             default_l_val=.false., lone_keyword_l_val=.true.)
 
  425         CALL keyword_create(keyword, __location__, name=
"ORBITAL_CENTER", &
 
  426                             description=
"The orbital center.", &
 
  427                             usage=
"ORBITAL_CENTER WANNIER", &
 
  429                             enum_c_vals=
s2a(
"WANNIER", 
"COMMON", 
"ATOM", 
"BOX"), &
 
  430                             enum_desc=
s2a(
"Use the Wannier centers.", &
 
  431                                           "Use a common center (works only for an isolate molecule).", &
 
  432                                           "Use the atoms as center.", &
 
  440                             description=
"Gauge origin of the velocity gauge factor.", &
 
  441                             enum_c_vals=
s2a(
"COM", 
"COAC", 
"USER_DEFINED", 
"ZERO"), &
 
  442                             enum_desc=
s2a(
"Use Center of Mass", &
 
  443                                           "Use Center of Atomic Charges", &
 
  444                                           "Use User-defined Point", &
 
  445                                           "Use Origin of Coordinate System"), &
 
  454         CALL keyword_create(keyword, __location__, name=
"REFERENCE_POINT", &
 
  455                             description=
"User-defined reference point of the velocity gauge factor.", &
 
  456                             usage=
"REFERENCE_POINT x y z", &
 
  457                             repeats=.false., n_var=3, type_of_var=
real_t, unit_str=
'bohr')
 
  461         CALL keyword_create(keyword, __location__, name=
"Z_MATRIX_METHOD", &
 
  462                             description=
"Use Z_matrix method to solve the response equation", &
 
  463                             usage=
"Z_MATRIX_METHOD T", &
 
  464                             default_l_val=.false., lone_keyword_l_val=.true.)
 
  469                             description=
"Use numerical differentiation to compute the APT, "// &
 
  470                             "switches off the calculation of dcdr analytical derivatives. "// &
 
  471                             "Requires RUN_TYPE = ENERGY_FORCE or MD.", &
 
  473                             default_l_val=.false., lone_keyword_l_val=.true.)
 
  478                             description=
"Electric field strength (atomic units) to use for finite differences", &
 
  482                             default_r_val=0.0003_dp, &
 
  483                             usage=
"APT_FD_DE 1.0E-4")
 
  487         CALL keyword_create(keyword, __location__, name=
"APT_FD_METHOD", &
 
  488                             description=
"Numerical differentiation method", &
 
  489                             usage=
"APT_FD_METHOD FD", &
 
  492                             enum_c_vals=
s2a(
"2PNT"), &
 
  495                             enum_desc=
s2a(
"Symmetric two-point differences."), &
 
  503                             description=
"print results of the magnetic dipole moment calculation", &
 
  507                                          description=
"Controls the printing of the electric dipole gradient", &
 
  522   END SUBROUTINE create_dcdr_section
 
  530   SUBROUTINE create_vcd_section(section)
 
  537      NULLIFY (keyword, print_key, subsection)
 
  539      cpassert(.NOT. 
ASSOCIATED(section))
 
  542                          description=
"Carry out a VCD calculation.", &
 
  543                          n_keywords=50, n_subsections=1, repeats=.false.)
 
  545      CALL keyword_create(keyword, __location__, name=
"_SECTION_PARAMETERS_", &
 
  546                          description=
"controls the activation of the APT/AAT calculation", &
 
  548                          default_l_val=.false., &
 
  549                          lone_keyword_l_val=.true.)
 
  553      CALL keyword_create(keyword, __location__, name=
"LIST_OF_ATOMS", &
 
  554                          description=
"Specifies a list of atoms.", &
 
  555                          usage=
"LIST_OF_ATOMS {integer} {integer} .. {integer}", repeats=.true., &
 
  560      CALL keyword_create(keyword, __location__, name=
"DISTRIBUTED_ORIGIN", &
 
  561                          variants=(/
"DO_GAUGE"/), &
 
  562                          description=
"Use the distributed origin (DO) gauge?", &
 
  563                          usage=
"DISTRIBUTED_ORIGIN T", &
 
  564                          default_l_val=.false., lone_keyword_l_val=.true.)
 
  568      CALL keyword_create(keyword, __location__, name=
"ORIGIN_DEPENDENT_MFP", &
 
  569                          description=
"Use the origin dependent MFP operator.", &
 
  570                          usage=
"ORIGIN_DEPENDENT_MFP T", &
 
  571                          default_l_val=.false., lone_keyword_l_val=.true.)
 
  575      CALL keyword_create(keyword, __location__, name=
"ORBITAL_CENTER", &
 
  576                          description=
"The orbital center.", &
 
  577                          usage=
"ORBITAL_CENTER WANNIER", &
 
  579                          enum_c_vals=
s2a(
"WANNIER", 
"COMMON", 
"ATOM", 
"BOX"), &
 
  580                          enum_desc=
s2a(
"Use the Wannier centers.", &
 
  581                                        "Use a common center (works only for an isolate molecule).", &
 
  582                                        "Use the atoms as center.", &
 
  590      CALL keyword_create(keyword, __location__, name=
"MAGNETIC_ORIGIN", &
 
  591                          description=
"Gauge origin of the magnetic dipole operator.", &
 
  592                          enum_c_vals=
s2a(
"COM", 
"COAC", 
"USER_DEFINED", 
"ZERO"), &
 
  593                          enum_desc=
s2a(
"Use Center of Mass", &
 
  594                                        "Use Center of Atomic Charges", &
 
  595                                        "Use User-defined Point", &
 
  596                                        "Use Origin of Coordinate System"), &
 
  605      CALL keyword_create(keyword, __location__, name=
"MAGNETIC_ORIGIN_REFERENCE", &
 
  606                          description=
"User-defined reference point of the magnetic dipole operator.", &
 
  607                          usage=
"MAGNETIC_ORIGIN_REFERENCE x y z", &
 
  608                          repeats=.false., n_var=3, type_of_var=
real_t, unit_str=
'bohr')
 
  613      CALL keyword_create(keyword, __location__, name=
"SPATIAL_ORIGIN", &
 
  614                          description=
"Gauge origin of the velocity gauge factor/spatial origin.", &
 
  615                          enum_c_vals=
s2a(
"COM", 
"COAC", 
"USER_DEFINED", 
"ZERO"), &
 
  616                          enum_desc=
s2a(
"Use Center of Mass", &
 
  617                                        "Use Center of Atomic Charges", &
 
  618                                        "Use User-defined Point", &
 
  619                                        "Use Origin of Coordinate System"), &
 
  628      CALL keyword_create(keyword, __location__, name=
"SPATIAL_ORIGIN_REFERENCE", &
 
  629                          description=
"User-defined reference point of the velocity gauge factor/spatial origin.", &
 
  630                          usage=
"SPATIAL_ORIGIN_REFERENCE x y z", &
 
  631                          repeats=.false., n_var=3, type_of_var=
real_t, unit_str=
'bohr')
 
  637                          description=
"print results of the magnetic dipole moment calculation", &
 
  641                                       description=
"Controls the printing of the APTs and AATs", &
 
  654   END SUBROUTINE create_vcd_section
 
  663   SUBROUTINE create_current_section(section)
 
  669      NULLIFY (keyword, print_key, subsection)
 
  671      cpassert(.NOT. 
ASSOCIATED(section))
 
  673                          description=
"The induced current density is calculated by DFPT.", &
 
  674                          n_keywords=4, n_subsections=1, repeats=.false., &
 
  677      CALL keyword_create(keyword, __location__, name=
"_SECTION_PARAMETERS_", &
 
  678                          description=
"controls the activation of the induced current calculation", &
 
  679                          usage=
"&CURRENT T", &
 
  680                          default_l_val=.false., &
 
  681                          lone_keyword_l_val=.true.)
 
  686                          description=
"The gauge used to compute the induced current within GAPW.", &
 
  689                          enum_c_vals=
s2a(
"R", 
"R_AND_STEP_FUNCTION", 
"ATOM"), &
 
  690                          enum_desc=
s2a(
"Position gauge (doesnt work well).", &
 
  691                                        "Position and step function for the soft and the local parts, respectively.", &
 
  697      CALL keyword_create(keyword, __location__, name=
"GAUGE_ATOM_RADIUS", &
 
  698                          description=
"Build the gauge=atom using only the atoms within this radius.", &
 
  699                          usage=
"GAUGE_ATOM_RADIUS 10.0", &
 
  706      CALL keyword_create(keyword, __location__, name=
"USE_OLD_GAUGE_ATOM", &
 
  707                          description=
"Use the old way to compute the gauge.", &
 
  708                          usage=
"USE_OLD_GAUGE_ATOM T", &
 
  709                          default_l_val=.true., lone_keyword_l_val=.true.)
 
  713      CALL keyword_create(keyword, __location__, name=
"ORBITAL_CENTER", &
 
  714                          description=
"The orbital center.", &
 
  715                          usage=
"ORBITAL_CENTER WANNIER", &
 
  717                          enum_c_vals=
s2a(
"WANNIER", 
"COMMON", 
"ATOM", 
"BOX"), &
 
  718                          enum_desc=
s2a(
"Use the Wannier centers.", &
 
  719                                        "Use a common center (works only for an isolate molecule).", &
 
  720                                        "Use the atoms as center.", &
 
  727      CALL keyword_create(keyword, __location__, name=
"COMMON_CENTER", &
 
  728                          description=
"The common center ", usage=
"COMMON_CENTER 0.0 1.0 0.0", &
 
  729                          n_var=3, default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/), type_of_var=
real_t, &
 
  735                          description=
"How many boxes along each directions ", usage=
"NBOX 6 6 5", &
 
  736                          n_var=3, default_i_vals=(/4, 4, 4/), type_of_var=
integer_t)
 
  741                          description=
"Calculate the succeptibility correction to the shift with PBC", &
 
  743                          default_l_val=.false., lone_keyword_l_val=.true.)
 
  747      CALL keyword_create(keyword, __location__, name=
"FORCE_NO_FULL", &
 
  748                          description=
"Avoid the calculation of the state dependent perturbation term, "// &
 
  749                          "even if the orbital centers are set at Wannier centers or at Atom centers", &
 
  750                          usage=
"FORCE_NO_FULL T", &
 
  751                          default_l_val=.false., lone_keyword_l_val=.true.)
 
  755      CALL keyword_create(keyword, __location__, name=
"SELECTED_STATES_ON_ATOM_LIST", &
 
  756                          description=
"Indexes of the atoms for selecting"// &
 
  757                          " the states to be used for the response calculations.", &
 
  758                          usage=
"SELECTED_STATES_ON_ATOM_LIST 1 2 10", &
 
  759                          n_var=-1, type_of_var=
integer_t, repeats=.true.)
 
  763      CALL keyword_create(keyword, __location__, name=
"SELECTED_STATES_ATOM_RADIUS", &
 
  764                          description=
"Select all the states included in the given radius around each atoms "// &
 
  765                          "in SELECTED_STATES_ON_ATOM_LIST.", &
 
  766                          usage=
"SELECTED_STATES_ATOM_RADIUS 2.0", &
 
  773      CALL keyword_create(keyword, __location__, name=
"RESTART_CURRENT", &
 
  774                          description=
"Restart the induced current density calculation"// &
 
  775                          " from a previous run (not working yet).", &
 
  776                          usage=
"RESTART_CURRENT", default_l_val=.false., &
 
  777                          lone_keyword_l_val=.true.)
 
  783                          description=
"print results of induced current density calculation", &
 
  787                                       description=
"Controls the printing of the induced current density (not working yet).", &
 
  790                          description=
"The stride (X,Y,Z) used to write the cube file "// &
 
  791                          "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
 
  792                          " 1 number valid for all components (not working yet).", &
 
  793                          usage=
"STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=
integer_t)
 
  797                          description=
"append the cube files when they already exist", &
 
  798                          default_l_val=.false., lone_keyword_l_val=.true.)
 
  806                                       description=
"Controls the printing of the response functions (not working yet).", &
 
  809                          description=
"The stride (X,Y,Z) used to write the cube file "// &
 
  810                          "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
 
  811                          " 1 number valid for all components (not working yet).", &
 
  812                          usage=
"STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=
integer_t)
 
  816      CALL keyword_create(keyword, __location__, name=
"CUBES_LU_BOUNDS", &
 
  817                          variants=(/
"CUBES_LU"/), &
 
  818                          description=
"The lower and upper index of the states to be printed as cube (not working yet).", &
 
  819                          usage=
"CUBES_LU_BOUNDS integer integer", &
 
  820                          n_var=2, default_i_vals=(/0, -2/), type_of_var=
integer_t)
 
  825                          description=
"Indexes of the states to be printed as cube files "// &
 
  826                          "This keyword can be repeated several times "// &
 
  827                          "(useful if you have to specify many indexes) (not working yet).", &
 
  828                          usage=
"CUBES_LIST 1 2", &
 
  829                          n_var=-1, type_of_var=
integer_t, repeats=.true.)
 
  833                          description=
"append the cube files when they already exist", &
 
  834                          default_l_val=.false., lone_keyword_l_val=.true.)
 
  849   END SUBROUTINE create_current_section
 
  859   SUBROUTINE create_nmr_section(section)
 
  865      NULLIFY (keyword, print_key, subsection)
 
  867      cpassert(.NOT. 
ASSOCIATED(section))
 
  869                          description=
"The chemical shift is calculated by DFPT.", &
 
  870                          n_keywords=5, n_subsections=1, repeats=.false., &
 
  873      CALL keyword_create(keyword, __location__, name=
"_SECTION_PARAMETERS_", &
 
  874                          description=
"controls the activation of the nmr calculation", &
 
  876                          default_l_val=.false., &
 
  877                          lone_keyword_l_val=.true.)
 
  881      CALL keyword_create(keyword, __location__, name=
"INTERPOLATE_SHIFT", &
 
  882                          description=
"Calculate the soft part of the chemical shift by interpolation ", &
 
  883                          usage=
"INTERPOLATE_SHIFT T", &
 
  884                          default_l_val=.false., lone_keyword_l_val=.true.)
 
  889                          description=
"Calculate the chemical shift in a set of points"// &
 
  890                          " given from an external file", usage=
"NICS", &
 
  891                          default_l_val=.false., lone_keyword_l_val=.true.)
 
  895      CALL keyword_create(keyword, __location__, name=
"NICS_FILE_NAME", &
 
  896                          description=
"Name of the file with the NICS points coordinates", &
 
  897                          usage=
"NICS_FILE_NAME nics_file", &
 
  898                          default_lc_val=
"nics_file")
 
  903                          description=
"Restart the NMR calculation from a previous run (NOT WORKING YET)", &
 
  904                          usage=
"RESTART_NMR", default_l_val=.false., &
 
  905                          lone_keyword_l_val=.true.)
 
  909      CALL keyword_create(keyword, __location__, name=
"SHIFT_GAPW_RADIUS", &
 
  910                          description=
"While computing the local part of the shift (GAPW), "// &
 
  911                          "the integration is restricted to nuclei that are within this radius.", &
 
  912                          usage=
"SHIFT_GAPW_RADIUS 20.0", &
 
  921                          description=
"print results of nmr calculation", &
 
  925                                       description=
"Controls the printing of the response functions ", &
 
  928                          description=
"The stride (X,Y,Z) used to write the cube file "// &
 
  929                          "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
 
  930                          " 1 number valid for all components.", &
 
  931                          usage=
"STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=
integer_t)
 
  935      CALL keyword_create(keyword, __location__, name=
"CUBES_LU_BOUNDS", &
 
  936                          variants=(/
"CUBES_LU"/), &
 
  937                          description=
"The lower and upper index of the states to be printed as cube", &
 
  938                          usage=
"CUBES_LU_BOUNDS integer integer", &
 
  939                          n_var=2, default_i_vals=(/0, -2/), type_of_var=
integer_t)
 
  944                          description=
"Indexes of the states to be printed as cube files "// &
 
  945                          "This keyword can be repeated several times "// &
 
  946                          "(useful if you have to specify many indexes).", &
 
  947                          usage=
"CUBES_LIST 1 2", &
 
  948                          n_var=-1, type_of_var=
integer_t, repeats=.true.)
 
  952                          description=
"append the cube files when they already exist", &
 
  953                          default_l_val=.false., lone_keyword_l_val=.true.)
 
  961                                       description=
"Controls the printing of susceptibility", &
 
  967                                       description=
"Controls the printing of the chemical shift", &
 
  970      CALL keyword_create(keyword, __location__, name=
"ATOMS_LU_BOUNDS", &
 
  971                          variants=(/
"ATOMS_LU"/), &
 
  972                          description=
"The lower and upper atomic index for which the tensor is printed", &
 
  973                          usage=
"ATOMS_LU_BOUNDS integer integer", &
 
  974                          n_var=2, default_i_vals=(/0, -2/), type_of_var=
integer_t)
 
  979                          description=
"list of atoms for which the shift is printed into a file ", &
 
  980                          usage=
"ATOMS_LIST 1 2", n_var=-1, &
 
  996   END SUBROUTINE create_nmr_section
 
 1005   SUBROUTINE create_spin_spin_section(section)
 
 1011      NULLIFY (keyword, print_key, subsection)
 
 1013      cpassert(.NOT. 
ASSOCIATED(section))
 
 1015                          description=
"Compute indirect spin-spin coupling constants.", &
 
 1016                          n_keywords=5, n_subsections=1, repeats=.false.)
 
 1018      CALL keyword_create(keyword, __location__, name=
"_SECTION_PARAMETERS_", &
 
 1019                          description=
"controls the activation of the nmr calculation", &
 
 1020                          usage=
"&SPINSPIN T", &
 
 1021                          default_l_val=.false., &
 
 1022                          lone_keyword_l_val=.true.)
 
 1026      CALL keyword_create(keyword, __location__, name=
"RESTART_SPINSPIN", &
 
 1027                          description=
"Restart the spin-spin calculation from a previous run (NOT WORKING YET)", &
 
 1028                          usage=
"RESTART_SPINSPIN", default_l_val=.false., &
 
 1029                          lone_keyword_l_val=.true.)
 
 1033      CALL keyword_create(keyword, __location__, name=
"ISSC_ON_ATOM_LIST", &
 
 1034                          description=
"Atoms for which the issc is computed.", &
 
 1035                          usage=
"ISSC_ON_ATOM_LIST 1 2 10", &
 
 1036                          n_var=-1, type_of_var=
integer_t, repeats=.true.)
 
 1041                          description=
"Compute the Fermi contact contribution", &
 
 1043                          default_l_val=.true., lone_keyword_l_val=.true.)
 
 1048                          description=
"Compute the spin-dipolar contribution", &
 
 1050                          default_l_val=.true., lone_keyword_l_val=.true.)
 
 1055                          description=
"Compute the paramagnetic spin-orbit contribution", &
 
 1057                          default_l_val=.true., lone_keyword_l_val=.true.)
 
 1062                          description=
"Compute the diamagnetic spin-orbit contribution (NOT YET IMPLEMENTED)", &
 
 1064                          default_l_val=.true., lone_keyword_l_val=.true.)
 
 1068      NULLIFY (subsection)
 
 1070                          description=
"print results of the indirect spin-spin calculation", &
 
 1074                                       description=
"Controls the printing of the indirect spin-spin matrix", &
 
 1078                          description=
"list of atoms for which the indirect spin-spin is printed into a file ", &
 
 1079                          usage=
"ATOMS_LIST 1 2", n_var=-1, &
 
 1090      NULLIFY (subsection)
 
 1095   END SUBROUTINE create_spin_spin_section
 
 1105   SUBROUTINE create_epr_section(section)
 
 1109      TYPE(
section_type), 
POINTER                        :: print_key, subsection, subsubsection
 
 1111      NULLIFY (keyword, print_key, subsection, subsubsection)
 
 1113      cpassert(.NOT. 
ASSOCIATED(section))
 
 1115                          description=
"The g tensor is calculated by DFPT ", &
 
 1116                          n_keywords=5, n_subsections=1, repeats=.false., &
 
 1119      CALL keyword_create(keyword, __location__, name=
"_SECTION_PARAMETERS_", &
 
 1120                          description=
"controls the activation of the epr calculation", &
 
 1122                          default_l_val=.false., &
 
 1123                          lone_keyword_l_val=.true.)
 
 1128                          description=
"Restart the EPR calculation from a previous run (NOT WORKING)", &
 
 1129                          usage=
"RESTART_EPR", default_l_val=.false., &
 
 1130                          lone_keyword_l_val=.true.)
 
 1134      NULLIFY (subsection)
 
 1136                          description=
"print results of epr calculation", &
 
 1140                                       description=
"Controls the printing of the components of nabla v_ks ", &
 
 1143                          description=
"The stride (X,Y,Z) used to write the cube file "// &
 
 1144                          "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
 
 1145                          " 1 number valid for all components.", &
 
 1146                          usage=
"STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=
integer_t)
 
 1150                          description=
"append the cube files when they already exist", &
 
 1151                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1159                                       description=
"Controls the printing of the g tensor", &
 
 1165      CALL keyword_create(keyword, __location__, name=
"GAPW_MAX_ALPHA", &
 
 1166                          description=
"Maximum alpha of GTH potentials allowed on the soft grids ", &
 
 1167                          usage=
"GAPW_MAX_ALPHA real", default_r_val=5.0_dp)
 
 1171      CALL keyword_create(keyword, __location__, name=
"SOO_RHO_HARD", &
 
 1172                          description=
"Whether or not to include the atomic parts of the density "// &
 
 1173                          "in the SOO part of the g tensor", usage=
"SOO_RHO_HARD", &
 
 1174                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1182                                       description=
"Controls the printing of the response functions ", &
 
 1185                          description=
"The stride (X,Y,Z) used to write the cube file "// &
 
 1186                          "(larger values result in smaller cube files). You can provide 3 numbers (for X,Y,Z) or"// &
 
 1187                          " 1 number valid for all components.", &
 
 1188                          usage=
"STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=
integer_t)
 
 1192      CALL keyword_create(keyword, __location__, name=
"CUBES_LU_BOUNDS", &
 
 1193                          variants=(/
"CUBES_LU"/), &
 
 1194                          description=
"The lower and upper index of the states to be printed as cube", &
 
 1195                          usage=
"CUBES_LU_BOUNDS integer integer", &
 
 1196                          n_var=2, default_i_vals=(/0, -2/), type_of_var=
integer_t)
 
 1201                          description=
"Indexes of the states to be printed as cube files "// &
 
 1202                          "This keyword can be repeated several times "// &
 
 1203                          "(useful if you have to specify many indexes).", &
 
 1204                          usage=
"CUBES_LIST 1 2", &
 
 1205                          n_var=-1, type_of_var=
integer_t, repeats=.true.)
 
 1209                          description=
"append the cube files when they already exist", &
 
 1210                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1220      NULLIFY (subsection)
 
 1225   END SUBROUTINE create_epr_section
 
 1234   SUBROUTINE create_polarizability_section(section)
 
 1241      NULLIFY (keyword, print_key, subsection)
 
 1243      cpassert(.NOT. 
ASSOCIATED(section))
 
 1245                          description=
"Compute polarizabilities.", &
 
 1246                          n_keywords=5, n_subsections=1, repeats=.false., &
 
 1249      CALL keyword_create(keyword, __location__, name=
"_SECTION_PARAMETERS_", &
 
 1250                          description=
"controls the activation of the polarizability calculation", &
 
 1252                          default_l_val=.false., &
 
 1253                          lone_keyword_l_val=.true.)
 
 1258                          description=
"Compute the electric-dipole--electric-dipole polarizability", &
 
 1259                          usage=
"DO_RAMAN F", &
 
 1261                          default_l_val=.true., lone_keyword_l_val=.true.)
 
 1265      CALL keyword_create(keyword, __location__, name=
"PERIODIC_DIPOLE_OPERATOR", &
 
 1266                          description=
"Type of dipole operator: Berry phase(T) or Local(F)", &
 
 1267                          usage=
"PERIODIC_DIPOLE_OPERATOR T", &
 
 1268                          default_l_val=.true., lone_keyword_l_val=.true.)
 
 1272      NULLIFY (subsection)
 
 1274                          description=
"print results of the polarizability calculation", &
 
 1278                                       description=
"Controls the printing of the polarizabilities", &
 
 1286      NULLIFY (subsection)
 
 1291   END SUBROUTINE create_polarizability_section
 
 1298   SUBROUTINE create_et_coupling_section(section)
 
 1305      cpassert(.NOT. 
ASSOCIATED(section))
 
 1307                          description=
"specifies the two constraints/restraints for extracting ET coupling elements", &
 
 1310      NULLIFY (subsection)
 
 1315      NULLIFY (subsection)
 
 1320      NULLIFY (subsection)
 
 1321      CALL create_projection(subsection, 
"PROJECTION")
 
 1325      CALL keyword_create(keyword, __location__, name=
"TYPE_OF_CONSTRAINT", &
 
 1326                          description=
"Specifies the type of constraint", &
 
 1327                          usage=
"TYPE_OF_CONSTRAINT DDAPC", &
 
 1328                          enum_c_vals=
s2a(
"NONE", 
"DDAPC"), &
 
 1330                          enum_desc=
s2a(
"NONE", 
"DDAPC Constraint"), &
 
 1337                                       description=
"Controls the printing basic info about the method", &
 
 1342   END SUBROUTINE create_et_coupling_section
 
 1351   SUBROUTINE create_projection(section, section_name)
 
 1355      CHARACTER(len=*), 
INTENT(in)                       :: section_name
 
 1358      TYPE(
section_type), 
POINTER                        :: print_key, section_block, section_print
 
 1363      cpassert(.NOT. 
ASSOCIATED(section))
 
 1368      NULLIFY (section_block)
 
 1369      NULLIFY (section_print)
 
 1372      CALL section_create(section, __location__, name=trim(adjustl(section_name)), &
 
 1373                          description=
"Projection-operator approach fo ET coupling calculation", &
 
 1374                          n_keywords=0, n_subsections=2, repeats=.false.)
 
 1378                                       description=
"Controls printing of data and informations to log file", &
 
 1385                          description=
"Part of the system (donor, acceptor, bridge,...)", &
 
 1386                          n_keywords=2, n_subsections=1, repeats=.true.)
 
 1391                          description=
"Array of atom IDs in the system part", &
 
 1392                          usage=
"ATOMS {integer} {integer} .. {integer}", &
 
 1393                          n_var=-1, type_of_var=
integer_t, repeats=.false.)
 
 1399                          description=
"Number of electrons expected in the system part", &
 
 1400                          usage=
"NELECTRON {integer}", default_i_val=0)
 
 1406                          description=
"Possible printing options in ET system part", &
 
 1407                          n_keywords=0, n_subsections=0, repeats=.false.)
 
 1411      CALL keyword_create(keyword, __location__, name=
'MO_COEFF_ATOM', &
 
 1412                          description=
"Print out MO coeffiecients on given atom", &
 
 1413                          usage=
"MO_COEFF_ATOM {integer} {integer} .. {integer}", &
 
 1414                          type_of_var=
integer_t, n_var=-1, repeats=.true.)
 
 1419      CALL keyword_create(keyword, __location__, name=
'MO_COEFF_ATOM_STATE', &
 
 1420                          description=
"Print out MO coeffiecients of specific state", &
 
 1421                          usage=
"MO_COEFF_ATOM_STATE {integer} {integer} .. {integer}", &
 
 1422                          type_of_var=
integer_t, n_var=-1, repeats=.true.)
 
 1428                                       description=
"Controls saving of MO cube files", &
 
 1433                          description=
"The stride (X,Y,Z) used to write the cube file", &
 
 1434                          usage=
"STRIDE {integer} {integer} {integer}", n_var=-1, &
 
 1435                          default_i_vals=(/2, 2, 2/), type_of_var=
integer_t)
 
 1441                          description=
"Indices of molecular orbitals to save", &
 
 1442                          usage=
"MO_LIST {integer} {integer} .. {integer}", &
 
 1443                          type_of_var=
integer_t, n_var=-1, repeats=.true.)
 
 1449                          description=
"Number of unoccupied molecular orbitals to save", &
 
 1450                          usage=
"NLUMO {integer}", default_i_val=1)
 
 1456                          description=
"Number of occupied molecular orbitals to save", &
 
 1457                          usage=
"NHOMO {integer}", default_i_val=1)
 
 1472                          description=
"Possible printing options in ET", &
 
 1473                          n_keywords=0, n_subsections=0, repeats=.false.)
 
 1478                                       description=
"Controls printing couplings onto file", &
 
 1482                          description=
"append the files when they already exist", &
 
 1483                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1492   END SUBROUTINE create_projection
 
 1501   SUBROUTINE create_tddfpt2_section(section)
 
 1507      cpassert(.NOT. 
ASSOCIATED(section))
 
 1509                          description=
"Parameters needed to set up the Time-Dependent "// &
 
 1510                          "Density Functional Perturbation Theory. "// &
 
 1511                          "Current implementation works for hybrid functionals. "// &
 
 1512                          "Can be used with Gaussian and Plane Waves (GPW) method only.", &
 
 1513                          n_keywords=14, n_subsections=4, repeats=.false., &
 
 1516      NULLIFY (keyword, print_key, subsection)
 
 1519                          name=
"_SECTION_PARAMETERS_", &
 
 1520                          description=
"Controls the activation of the TDDFPT procedure", &
 
 1521                          default_l_val=.false., &
 
 1522                          lone_keyword_l_val=.true.)
 
 1528                          description=
"Number of excited states to converge.", &
 
 1535                          description=
"Maximal number of iterations to be performed.", &
 
 1542                          description=
"Maximal number of Krylov space vectors. "// &
 
 1543                          "Davidson iterations will be restarted upon reaching this limit.", &
 
 1550                          description=
"Number of unoccupied orbitals to consider. "// &
 
 1551                          "Default is to use all unoccupied orbitals (-1).", &
 
 1558                          description=
"Number of MPI processes to be used per excited state. "// &
 
 1559                          "Default is to use all processors (0).", &
 
 1567                          description=
"Options to compute the kernel", &
 
 1568                          usage=
"KERNEL FULL", &
 
 1569                          enum_c_vals=
s2a(
"FULL", 
"sTDA", 
"NONE"), &
 
 1577                          description=
"Selects the type of spin-flip TDDFPT kernel", &
 
 1578                          usage=
"SPINFLIP NONCOLLINEAR", &
 
 1579                          enum_c_vals=
s2a(
"NONE", 
"COLLINEAR", 
"NONCOLLINEAR"), &
 
 1586                          description=
"Orbital energy correction potential.", &
 
 1587                          enum_c_vals=
s2a(
"NONE", 
"LB94", 
"GLLB", 
"SAOP", 
"SHIFT"), &
 
 1589                          enum_desc=
s2a(
"No orbital correction scheme is used", &
 
 1590                                        "van Leeuwen and Baerends. PRA, 49:2421, 1994", &
 
 1591                                        "Gritsenko, van Leeuwen, van Lenthe, Baerends. PRA, 51:1944, 1995", &
 
 1592                                        "Gritsenko, Schipper, Baerends. Chem. Phys. Lett., 302:199, 1999", &
 
 1593                                        "Constant shift of virtual and/or open-shell orbitals"), &
 
 1600                          variants=
s2a(
"VIRTUAL_SHIFT"), &
 
 1601                          description=
"Constant shift of virtual state eigenvalues.", &
 
 1602                          usage=
"EV_SHIFT 0.500", &
 
 1603                          n_var=1, type_of_var=
real_t, &
 
 1605                          default_r_val=0.0_dp)
 
 1610                          variants=
s2a(
"OPEN_SHELL_SHIFT"), &
 
 1611                          description=
"Constant shift of open shell eigenvalues.", &
 
 1612                          usage=
"EOS_SHIFT 0.200", &
 
 1613                          n_var=1, type_of_var=
real_t, &
 
 1615                          default_r_val=0.0_dp)
 
 1621                          description=
"Target accuracy for excited state energies.", &
 
 1622                          n_var=1, type_of_var=
real_t, unit_str=
"hartree", &
 
 1623                          default_r_val=1.0e-5_dp)
 
 1627      CALL keyword_create(keyword, __location__, name=
"MIN_AMPLITUDE", &
 
 1628                          description=
"The smallest excitation amplitude to print.", &
 
 1629                          n_var=1, type_of_var=
real_t, &
 
 1630                          default_r_val=5.0e-2_dp)
 
 1634      CALL keyword_create(keyword, __location__, name=
"ORTHOGONAL_EPS", &
 
 1635                          description=
"The largest possible overlap between the ground state and "// &
 
 1636                          "orthogonalised excited state wave-functions. Davidson iterations "// &
 
 1637                          "will be restarted when the overlap goes beyond this threshold in "// &
 
 1638                          "order to prevent numerical instability.", &
 
 1639                          n_var=1, type_of_var=
real_t, &
 
 1640                          default_r_val=1.0e-4_dp)
 
 1646                          description=
"Restart the TDDFPT calculation if a restart file exists", &
 
 1648                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1652      CALL keyword_create(keyword, __location__, name=
"RKS_TRIPLETS", &
 
 1653                          description=
"Compute triplet excited states using spin-unpolarised molecular orbitals.", &
 
 1655                          default_l_val=.false.)
 
 1659      CALL keyword_create(keyword, __location__, name=
"ADMM_KERNEL_XC_CORRECTION", &
 
 1660                          description=
"Use/Ignore ADMM correction xc functional for TD kernel. "// &
 
 1661                          "XC correction functional is defined in ground state XC section.", &
 
 1663                          default_l_val=.true., lone_keyword_l_val=.true.)
 
 1667      CALL keyword_create(keyword, __location__, name=
"ADMM_KERNEL_CORRECTION_SYMMETRIC", &
 
 1668                          description=
"ADMM correction functional in kernel is applied symmetrically. "// &
 
 1669                          "Original implementation is using a non-symmetric formula.", &
 
 1671                          default_l_val=.true., lone_keyword_l_val=.true.)
 
 1676                          description=
"Local resolution of identity for Coulomb contribution.", &
 
 1678                          default_l_val=.false.)
 
 1683                          description=
"Specify size of automatically generated auxiliary basis sets: "// &
 
 1684                          "Options={small,medium,large,huge}", &
 
 1685                          usage=
"AUTO_BASIS {basis_type} {basis_size}", &
 
 1686                          type_of_var=
char_t, repeats=.true., n_var=-1, default_c_vals=(/
"X", 
"X"/))
 
 1691                          description=
"Implying smeared occupation. ", &
 
 1693                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1697      CALL keyword_create(keyword, __location__, name=
"EXCITON_DESCRIPTORS", &
 
 1698                          description=
"Compute exciton descriptors. "// &
 
 1699                          "Details given in Manual section about Bethe Salpeter equation.", &
 
 1701                          default_l_val=.false.)
 
 1705      CALL keyword_create(keyword, __location__, name=
"DIRECTIONAL_EXCITON_DESCRIPTORS", &
 
 1706                          description=
"Print cartesian components of exciton descriptors.", &
 
 1708                          default_l_val=.false.)
 
 1713      CALL keyword_create(keyword, __location__, name=
"WFN_RESTART_FILE_NAME", &
 
 1714                          variants=(/
"RESTART_FILE_NAME"/), &
 
 1715                          description=
"Name of the wave function restart file, may include a path."// &
 
 1716                          " If no file is specified, the default is to open the file as generated by"// &
 
 1717                          " the wave function restart print key.", &
 
 1718                          usage=
"WFN_RESTART_FILE_NAME <FILENAME>", &
 
 1724      CALL section_create(subsection, __location__, name=
"DIPOLE_MOMENTS", &
 
 1725                          description=
"Parameters to compute oscillator strengths in the dipole approximation.", &
 
 1726                          n_keywords=3, n_subsections=0, repeats=.false.)
 
 1729                          description=
"Form of dipole transition integrals.", &
 
 1730                          enum_c_vals=
s2a(
"BERRY", 
"LENGTH", 
"VELOCITY"), &
 
 1731                          enum_desc=
s2a(
"Based on Berry phase formula (valid for fully periodic molecular systems only)", &
 
 1732                                        "Length form ⟨ i | r | j ⟩ (valid for non-periodic molecular systems only)", &
 
 1733                                        "Velocity form ⟨ i | d/dr | j ⟩"), &
 
 1740                          description=
"Reference point to calculate electric "// &
 
 1741                          "dipole moments using the dipole integrals in the length form.", &
 
 1742                          enum_c_vals=
s2a(
"COM", 
"COAC", 
"USER_DEFINED", 
"ZERO"), &
 
 1743                          enum_desc=
s2a(
"Use Center of Mass", &
 
 1744                                        "Use Center of Atomic Charges", &
 
 1745                                        "Use User-defined Point", &
 
 1746                                        "Use Origin of Coordinate System"), &
 
 1755      CALL keyword_create(keyword, __location__, name=
"REFERENCE_POINT", &
 
 1756                          description=
"User-defined reference point.", &
 
 1757                          usage=
"REFERENCE_POINT x y z", &
 
 1758                          repeats=.false., n_var=3, type_of_var=
real_t, unit_str=
'bohr')
 
 1768                          description=
"Is jet to be implemented", &
 
 1769                          n_keywords=2, n_subsections=0, repeats=.false.)
 
 1772                          variants=
s2a(
"EPS_FILTER_MATRIX"), &
 
 1773                          description=
"The threshold used for sparse matrix operations", &
 
 1774                          usage=
"EPS_FILTER {real}", &
 
 1776                          default_r_val=1.0e-10_dp)
 
 1781                          variants=(/
"ATOMIC_GRID"/), &
 
 1782                          description=
"Specification of the atomic angular and radial grids for "// &
 
 1783                          "a atomic kind. This keyword must be repeated for all kinds!  "// &
 
 1784                          "Usage: GRID < LEBEDEV_GRID > < RADIAL_GRID >", &
 
 1785                          usage=
"GRID {string} {integer} {integer}", &
 
 1786                          n_var=3, type_of_var=
char_t, repeats=.true.)
 
 1804      CALL create_stda_section(subsection)
 
 1809                          description=
"Choosing BSE kernel.", &
 
 1810                          usage=
"DO_BSE", default_l_val=.false., lone_keyword_l_val=.true.)
 
 1820      CALL create_linres_section(subsection, create_subsections=.false., default_set_tdlr=.true.)
 
 1826                          description=
"Printing of information during the TDDFT run.", repeats=.false.)
 
 1829                                       description=
"Controls the printing of the banner for TDDFPT program", &
 
 1835                                       description=
"Controls the printing of initial guess vectors.", &
 
 1841                                       description=
"Controls the printing of basic iteration information "// &
 
 1842                                       "during the TDDFT run.", &
 
 1848                                       description=
"Controls the printing of detailed energy information "// &
 
 1849                                       "during the TDDFT run.", &
 
 1855                                       description=
"Controls the printing of a file with all basis sets used.", &
 
 1861                                       description=
"Controls the dumping of the MO restart file during TDDFPT. "// &
 
 1862                                       "By default keeps a short history of three restarts.", &
 
 1864                                       each_iter_names=
s2a(
"TDDFT_SCF"), each_iter_values=(/10/), &
 
 1866      CALL keyword_create(keyword, __location__, name=
"BACKUP_COPIES", &
 
 1867                          description=
"Specifies the maximum number of backup copies.", &
 
 1868                          usage=
"BACKUP_COPIES {int}", &
 
 1876                                       description=
"Perform a natural transition orbital analysis.", &
 
 1879                          description=
"Threshold for sum of NTO eigenvalues considered", &
 
 1880                          usage=
"Threshold 0.95", &
 
 1883                          default_r_val=0.975_dp)
 
 1886      CALL keyword_create(keyword, __location__, name=
"INTENSITY_THRESHOLD", &
 
 1887                          description=
"Threshold for oscillator strength to screen states.", &
 
 1888                          usage=
"Intensity_threshold 0.01", &
 
 1891                          default_r_val=0.0_dp)
 
 1895                          description=
"Specifies a list of states for the NTO calculations.", &
 
 1896                          usage=
"STATE_LIST {integer} {integer} .. {integer}", &
 
 1901                          description=
"Print NTOs on Cube Files", &
 
 1902                          usage=
"CUBE_FILES {logical}", repeats=.false., n_var=1, &
 
 1903                          default_l_val=.false., lone_keyword_l_val=.true., type_of_var=
logical_t)
 
 1907                          description=
"The stride (X,Y,Z) used to write the cube file "// &
 
 1908                          "(larger values result in smaller cube files). Provide 3 numbers (for X,Y,Z) or"// &
 
 1909                          " 1 number valid for all components.", &
 
 1910                          usage=
"STRIDE 2 2 2", n_var=-1, default_i_vals=(/2, 2, 2/), type_of_var=
integer_t)
 
 1914                          description=
"append the cube files when they already exist", &
 
 1915                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1922                                       description=
"Write the NTO in Molden file format, for visualisation.", &
 
 1925                          description=
"Specifies the number of significant digits retained. 3 is OK for visualization.", &
 
 1926                          usage=
"NDIGITS {int}", &
 
 1931                          description=
"Representation of Gaussian-type orbitals", &
 
 1933                          enum_c_vals=
s2a(
"CARTESIAN", 
"SPHERICAL"), &
 
 1935                          "Cartesian Gaussian orbitals. Use with caution", &
 
 1936                          "Spherical Gaussian orbitals. Incompatible with VMD"), &
 
 1944                                       description=
"Controls the printout required for NAMD with NEWTONX.", &
 
 1946      CALL keyword_create(keyword, __location__, name=
"PRINT_VIRTUALS", &
 
 1947                          description=
"Print occupied AND virtual molecular orbital coefficients", &
 
 1948                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1951      CALL keyword_create(keyword, __location__, name=
"PRINT_PHASES", &
 
 1952                          description=
"Print phases of occupied and virtuals MOs.", &
 
 1953                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1956      CALL keyword_create(keyword, __location__, name=
"SCALE_WITH_PHASES", &
 
 1957                          description=
"Scale ES eigenvectors with phases of occupied and virtuals MOs.", &
 
 1958                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1966                                       description=
"Controls the printout of the tddfpt2_soc modul", &
 
 1969                          description=
"Will detrement if output in eVolt will be printef.", &
 
 1970                          default_l_val=.true., lone_keyword_l_val=.true.)
 
 1974                          description=
"Will detrement if output in wavenumbers will be printed.", &
 
 1975                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1979                          description=
"Will add the SOC-Splitting as additional output", &
 
 1980                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1984                          description=
"Will add the SOC-Matrix as additional output in a different file", &
 
 1985                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 1992                                       description=
"Controls the calculation and printing of excited state forces. "// &
 
 1993                                       "This needs a RUN_TYPE that includes force evaluation, e.g. ENERGY_FORCE", &
 
 1996                          description=
"Specifies a list of states for the force calculations.", &
 
 1997                          usage=
"LIST {integer} {integer} .. {integer}", repeats=.true., &
 
 2002                          description=
"Threshold for oszillator strength to screen states.", &
 
 2003                          usage=
"Threshold 0.01", &
 
 2006                          default_r_val=0.0_dp)
 
 2015   END SUBROUTINE create_tddfpt2_section
 
 2021   SUBROUTINE create_stda_section(section)
 
 2026      cpassert(.NOT. 
ASSOCIATED(section))
 
 2028                          description=
"parameters needed and setup for sTDA calculations", &
 
 2029                          n_keywords=3, n_subsections=0, repeats=.false.)
 
 2033                          variants=(/
"HFX_FRACTION"/), &
 
 2034                          description=
"The fraction of TB Hartree-Fock exchange to use in the Kernel. "// &
 
 2035                          "0.0 implies no HFX part is used in the kernel. ", &
 
 2036                          usage=
"FRACTION 0.0", default_r_val=0.0_dp)
 
 2043                          description=
"Explicitly including or switching off sTDA exchange", &
 
 2044                          usage=
"DO_EXCHANGE", default_l_val=.true., lone_keyword_l_val=.true.)
 
 2049                          description=
"Use Ewald type method for Coulomb interaction", &
 
 2050                          usage=
"DO_EWALD", default_l_val=.false., lone_keyword_l_val=.true.)
 
 2054      CALL keyword_create(keyword, __location__, name=
"EPS_TD_FILTER", &
 
 2055                          description=
"Threshold for filtering the transition density matrix", &
 
 2056                          usage=
"EPS_TD_FILTER epsf", default_r_val=1.e-10_dp)
 
 2060      CALL keyword_create(keyword, __location__, name=
"MATAGA_NISHIMOTO_CEXP", &
 
 2061                          description=
"Exponent used in Mataga-Nishimoto formula for Coulomb (alpha). "// &
 
 2062                          "Default value is method dependent!", &
 
 2063                          usage=
"MATAGA_NISHIMOTO_CEXP cexp", default_r_val=-99.0_dp)
 
 2067      CALL keyword_create(keyword, __location__, name=
"MATAGA_NISHIMOTO_XEXP", &
 
 2068                          description=
"Exponent used in Mataga-Nishimoto formula for Exchange (beta). "// &
 
 2069                          "Default value is method dependent!", &
 
 2070                          usage=
"MATAGA_NISHIMOTO_XEXP xexp", default_r_val=-99.0_dp)
 
 2074      CALL keyword_create(keyword, __location__, name=
"COULOMB_SR_CUT", &
 
 2075                          description=
"Maximum range of short range part of Coulomb interaction.", &
 
 2076                          usage=
"COULOMB_SR_CUT rcut", default_r_val=20.0_dp)
 
 2080      CALL keyword_create(keyword, __location__, name=
"COULOMB_SR_EPS", &
 
 2081                          description=
"Threshold for short range part of Coulomb interaction.", &
 
 2082                          usage=
"COULOMB_SR_EPS sreps", default_r_val=1.e-03_dp)
 
 2086   END SUBROUTINE create_stda_section
 
 2094   SUBROUTINE create_bandstructure_section(section)
 
 2100      cpassert(.NOT. 
ASSOCIATED(section))
 
 2101      CALL section_create(section, __location__, name=
"BANDSTRUCTURE", &
 
 2102                          description=
"Parameters needed to set up a calculation for "// &
 
 2103                          "electronic level energies of molecules and the electronic band "// &
 
 2104                          "structure of materials from post-SCF schemes (GW, perturbative "// &
 
 2105                          "spin-orbit coupling). Also, the density of states (DOS), "// &
 
 2106                          "projected density of states (PDOS), local density of states (LDOS), "// &
 
 2107                          "local valence band maximum (LVBM), local conduction band minimum "// &
 
 2108                          "(LCBM) and local band gap can be calculated. Please note that "// &
 
 2109                          "all methods in this section start from a Gamma-only DFT SCF. "// &
 
 2110                          "You need to make sure that the cell chosen in the DFT SCF is "// &
 
 2111                          "converged in the cell size. Band structures are computed "// &
 
 2112                          "for the primitive cell (i.e. the smallest possible unit cell of "// &
 
 2113                          "the input structure which is detected automatically). Moreover, "// &
 
 2114                          "spin-orbit coupling (SOC) on eigenvalues and band structures is "// &
 
 2115                          "available using Hartwigsen-Goedecker-Hutter "// &
 
 2116                          "pseudopotentials.", &
 
 2117                          n_keywords=1, n_subsections=1, repeats=.false.)
 
 2119      NULLIFY (keyword, subsection)
 
 2121                          name=
"_SECTION_PARAMETERS_", &
 
 2122                          description=
"Controls the activation of the band structure calculation.", &
 
 2123                          default_l_val=.false., &
 
 2124                          lone_keyword_l_val=.true.)
 
 2133      CALL create_gw_section(subsection)
 
 2137      CALL create_soc_section(subsection)
 
 2141      CALL create_dos_section(subsection)
 
 2145   END SUBROUTINE create_bandstructure_section
 
 2153   SUBROUTINE create_gw_section(section)
 
 2159      cpassert(.NOT. 
ASSOCIATED(section))
 
 2161                          description=
"Parameters needed to set up a GW calculation for "// &
 
 2162                          "electronic level energies $\varepsilon_{n\mathbf{k}}^{G_0W_0}$ "// &
 
 2163                          "of molecules and the band structure of materials: "// &
 
 2164                          "$\varepsilon_{n\mathbf{k}}^{G_0W_0}=  "// &
 
 2165                          "\varepsilon_{n\mathbf{k}}^\text{DFT}+\Sigma_{n\mathbf{k}} "// &
 
 2166                          "-v^\text{xc}_{n\mathbf{k}}$. "// &
 
 2167                          "For the GW algorithm for molecules, see "// &
 
 2168                          "<https://doi.org/10.1021/acs.jctc.0c01282>. "// &
 
 2169                          "For 2D materials, see <https://doi.org/10.1021/acs.jctc.3c01230>.", &
 
 2170                          n_keywords=1, n_subsections=1, repeats=.false.)
 
 2174                          name=
"_SECTION_PARAMETERS_", &
 
 2175                          description=
"Controls the activation of the GW calculation.", &
 
 2176                          default_l_val=.false., &
 
 2177                          lone_keyword_l_val=.true.)
 
 2181      CALL keyword_create(keyword, __location__, name=
"NUM_TIME_FREQ_POINTS", &
 
 2182                          description=
"Number of discrete points for the imaginary-time "// &
 
 2183                          "grid and the imaginary-frequency grid. The more points, the more "// &
 
 2184                          "precise is the calculation. Typically, 10 points are good "// &
 
 2185                          "for 0.1 eV precision of band structures and molecular energy "// &
 
 2186                          "levels, 20 points for 0.03 eV precision, "// &
 
 2187                          "and 30 points for 0.01 eV precision, see Table I in "// &
 
 2188                          "<https://doi.org/10.1021/acs.jctc.0c01282>. GW computation time "// &
 
 2189                          "increases linearly with `NUM_TIME_FREQ_POINTS`.", &
 
 2190                          usage=
"NUM_TIME_FREQ_POINTS 30", &
 
 2196                          description=
"Determines a threshold for the DBCSR based sparse "// &
 
 2197                          "multiplications. Normally, `EPS_FILTER` determines accuracy "// &
 
 2198                          "and timing of low-scaling GW calculations. (Lower filter means "// &
 
 2199                          "higher numerical precision, but higher computational cost.)", &
 
 2200                          usage=
"EPS_FILTER 1.0E-6", &
 
 2201                          default_r_val=1.0e-8_dp)
 
 2205      CALL keyword_create(keyword, __location__, name=
"REGULARIZATION_MINIMAX", &
 
 2206                          description=
"Parameter to regularize the Fourier transformation with minimax grids. "// &
 
 2207                          "In case the parameter 0.0 is chosen, no regularization is performed.", &
 
 2208                          usage=
"REGULARIZATION_MINIMAX 1.0E-4", &
 
 2209                          default_r_val=-1.0_dp)
 
 2213      CALL keyword_create(keyword, __location__, name=
"REGULARIZATION_RI", &
 
 2214                          description=
"Parameter for RI regularization, setting a negative "// &
 
 2215                          "value triggers the default value. Affects RI basis set convergence "// &
 
 2216                          "but in any case large RI basis will give RI basis set convergence.", &
 
 2217                          usage=
"REGULARIZATION_RI 1.0E-4", &
 
 2218                          default_r_val=-1.0_dp)
 
 2222      CALL keyword_create(keyword, __location__, name=
"CUTOFF_RADIUS_RI", &
 
 2223                          description=
"The cutoff radius (in Angstrom) for the truncated  "// &
 
 2224                          "Coulomb operator. The larger the cutoff radius, the faster "// &
 
 2225                          "converges the resolution of the identity (RI) with respect to the "// &
 
 2226                          "RI basis set size. Larger cutoff radius means higher computational "// &
 
 2228                          usage=
"CUTOFF_RADIUS_RI 3.0", &
 
 2230                          type_of_var=
real_t, unit_str=
"angstrom")
 
 2234      CALL keyword_create(keyword, __location__, name=
"MEMORY_PER_PROC", &
 
 2235                          description=
"Specify the available memory per MPI process. Set "// &
 
 2236                          "`MEMORY_PER_PROC` as accurately as possible for good performance. If "// &
 
 2237                          "`MEMORY_PER_PROC` is set lower as the actually available "// &
 
 2238                          "memory per MPI process, the performance will be "// &
 
 2239                          "bad; if `MEMORY_PER_PROC` is set higher as the actually "// &
 
 2240                          "available memory per MPI process, the program might run out of "// &
 
 2241                          "memory. You can calculate `MEMORY_PER_PROC` as follows: "// &
 
 2242                          "Get the memory per node on your machine, mem_per_node "// &
 
 2243                          "(for example, from a supercomputer website, typically between "// &
 
 2244                          "100 GB and 2 TB), get the number of "// &
 
 2245                          "MPI processes per node, n_MPI_proc_per_node"// &
 
 2246                          " (for example from your run-script; if you "// &
 
 2247                          "use slurm, the number behind '--ntasks-per-node' is the number "// &
 
 2248                          "of MPI processes per node). Then calculate "// &
 
 2249                          "`MEMORY_PER_PROC` = mem_per_node / n_MPI_proc_per_node "// &
 
 2250                          "(typically between 2 GB and 50 GB). Unit of keyword: Gigabyte (GB).", &
 
 2251                          usage=
"MEMORY_PER_PROC 16", &
 
 2252                          default_r_val=2.0_dp)
 
 2256      CALL keyword_create(keyword, __location__, name=
"APPROX_KP_EXTRAPOL", &
 
 2257                          description=
"If true, use only a 4x4 kpoint mesh for frequency "// &
 
 2258                          "points $\omega_j, j \ge 2$ (instead of a 4x4 and 6x6 k-point mesh). "// &
 
 2259                          "The k-point extrapolation of $W_{PQ}(i\omega_j,\mathbf{q})$ "// &
 
 2260                          "is done approximately from $W_{PQ}(i\omega_1,\mathbf{q})$.", &
 
 2261                          usage=
"APPROX_KP_EXTRAPOL", &
 
 2262                          default_l_val=.false., lone_keyword_l_val=.true.)
 
 2266      CALL keyword_create(keyword, __location__, name=
"SIZE_LATTICE_SUM", &
 
 2267                          description=
"Parameter determines how many neighbor cells $\mathbf{R}$ "// &
 
 2268                          "are used for computing "// &
 
 2269                          "$V_{PQ}(\mathbf{k}) = "// &
 
 2270                          "\sum_{\mathbf{R}} e^{i\mathbf{k}\cdot\mathbf{R}}\,\langle P, "// &
 
 2271                          "\text{cell}{=}\mathbf{0}|1/r|Q,\text{cell}{=}\mathbf{R}\rangle$. "// &
 
 2272                          "Normally, parameter does not need to be touched.", &
 
 2273                          usage=
"SIZE_LATTICE_SUM 4", &
 
 2279         keyword, __location__, name=
"KPOINTS_W", &
 
 2280         description=
"Monkhorst-Pack k-point mesh of size N_x, N_y, N_z for calculating "// &
 
 2281         "$W_{PQ}^\mathbf{R}=\int_\text{BZ}\frac{d\mathbf{k}}{\Omega_\text{BZ}}\, "// &
 
 2282         "e^{-i\mathbf{k}\cdot\mathbf{R}}\,W_{PQ}(\mathbf{k})$. "// &
 
 2283         αα
"For non-periodic directions , choose N_ = 1. "// &
 
 2284         "Automatic choice of the k-point mesh for negative "// &
 
 2285         "values, i.e. KPOINTS_W -1 -1 -1. "// &
 
 2286         "K-point extrapolation of W is automatically switched on.", &
 
 2287         usage=
"KPOINTS_W N_x  N_y  N_z", &
 
 2288         n_var=3, type_of_var=
integer_t, default_i_vals=(/-1, -1, -1/))
 
 2293                          description=
"If true, use Hedin's shift in G0W0, evGW and evGW0. "// &
 
 2294                          "Details see in Li et al. JCTC 18, 7570 "// &
 
 2295                          "(2022), Figure 1. G0W0 with Hedin's shift should give "// &
 
 2296                          "similar GW eigenvalues as evGW0; at a lower "// &
 
 2297                          "computational cost.", &
 
 2298                          usage=
"HEDIN_SHIFT", &
 
 2299                          default_l_val=.false., &
 
 2300                          lone_keyword_l_val=.true.)
 
 2304      CALL keyword_create(keyword, __location__, name=
"FREQ_MAX_FIT", &
 
 2305                          description=Σω
"For analytic continuation, a fit on (i) is performed. "// &
 
 2306                          Σω
"This fit is then evaluated at a real frequency, (), which is used "// &
 
 2307                          "in the quasiparticle equation "// &
 
 2308                          "$\varepsilon_{n\mathbf{k}}^{G_0W_0}=  "// &
 
 2309                          "\varepsilon_{n\mathbf{k}}^\text{DFT}+\Sigma_{n\mathbf{k}} "// &
 
 2310                          "-v^\text{xc}_{n\mathbf{k}}$. The keyword FREQ_MAX_FIT "// &
 
 2311                          Σω
"determines fitting range for the self-energy (i) on "// &
 
 2312                          ωω
"imaginary axis: i*[0, _max] for empty orbitals/bands, i*[-_max,0] "// &
 
 2313                          ω
"for occ orbitals. A smaller _max might lead to better numerical "// &
 
 2314                          "stability (i.e., if you observe clearly wrong GW eigenvalues/bands "// &
 
 2315                          ω
"around HOMO/LUMO, decreasing _max might fix this issue). "// &
 
 2316                          ω
"A small benchmark of _max is contained in Fig. 5 of "// &
 
 2317                          "J. Wilhelm et al., JCTC 12, 3623-3635 (2016). "// &
 
 2318                          ω
"Note that we used _max = 1 Ha = 27.211 eV in the benchmark "// &
 
 2319                          "M. Azizi et al., PRB 109, 245101 (2024).", &
 
 2321                          usage=
"FREQ_MAX_FIT 20.0", &
 
 2326      NULLIFY (subsection, print_key)
 
 2328                          description=
"Printing of GW restarts.", &
 
 2329                          n_keywords=0, n_subsections=1, repeats=.false.)
 
 2331                                       description=
"Controls the printing of restart files "// &
 
 2334                                       common_iter_levels=3)
 
 2341   END SUBROUTINE create_gw_section
 
 2349   SUBROUTINE create_soc_section(section)
 
 2354      cpassert(.NOT. 
ASSOCIATED(section))
 
 2356                          description=
"Switch on or off spin-orbit coupling. Use SOC "// &
 
 2357                          "parameters from non-local pseudopotentials as given in "// &
 
 2358                          "Hartwigsen, Goedecker, Hutter, Eq.(18), (19), "// &
 
 2359                          "<https://doi.org/10.1103/PhysRevB.58.3641>, "// &
 
 2360                          "$V_{\mu\nu}^{\mathrm{SOC}, (\alpha)} = "// &
 
 2361                          "(\hbar/2) \langle \phi_\mu | \sum_l \Delta "// &
 
 2362                          "V_l^\mathrm{SO}(\mathbf{r},\mathbf{r}') "// &
 
 2363                          "L^{(\alpha)} | \phi_\nu \rangle, "// &
 
 2364                          "\alpha = x, y, z$.", &
 
 2365                          n_keywords=1, n_subsections=1, repeats=.false.)
 
 2369                          name=
"_SECTION_PARAMETERS_", &
 
 2370                          description=
"Controls the activation of the SOC calculation.", &
 
 2371                          default_l_val=.false., &
 
 2372                          lone_keyword_l_val=.true.)
 
 2376      CALL keyword_create(keyword, __location__, name=
"ENERGY_WINDOW", &
 
 2377                          description=
"Apply SOC only for states with eigenvalues in the "// &
 
 2378                          "interval $[\varepsilon_\mathrm{VBM}-E_\mathrm{window}/2, "// &
 
 2379                          "\varepsilon_\mathrm{CBM}+E_\mathrm{window}/2]$. Might be necessary "// &
 
 2380                          "to use for large systems to prevent numerical instabilities.", &
 
 2381                          usage=
"ENERGY_WINDOW 5.0", &
 
 2387   END SUBROUTINE create_soc_section
 
 2395   SUBROUTINE create_dos_section(section)
 
 2401      cpassert(.NOT. 
ASSOCIATED(section))
 
 2403                          description=
"Parameters needed to calculate the density of states "// &
 
 2404                          "(DOS) and the projected density of states (PDOS).", &
 
 2405                          n_keywords=1, n_subsections=1, repeats=.false.)
 
 2409                          name=
"_SECTION_PARAMETERS_", &
 
 2410                          description=
"Controls the activation of the DOS calculation.", &
 
 2411                          default_l_val=.false., &
 
 2412                          lone_keyword_l_val=.true.)
 
 2416      CALL keyword_create(keyword, __location__, name=
"ENERGY_WINDOW", &
 
 2417                          description=
"Print DOS and PDOS in the energy window "// &
 
 2418                          "$[\varepsilon_\mathrm{VBM}-E_\mathrm{window}/2,  "// &
 
 2419                          "\varepsilon_\mathrm{CBM}+E_\mathrm{window}/2]$,"// &
 
 2420                          " where VBM is the valence "// &
 
 2421                          "band maximum (or highest occupied molecular orbital, HOMO, for "// &
 
 2422                          "molecules) and CBM the conduction band minimum (or lowest "// &
 
 2423                          "unoccupied molecular orbital, LUMO, for molecules).", &
 
 2424                          usage=
"ENERGY_WINDOW 5.0", &
 
 2431                          description=
"Resolution of the energy E when computing the $\rho(E)$.", &
 
 2432                          usage=
"ENERGY_STEP 0.01", &
 
 2439                          description=α
"Broadening  in Gaussians used in the DOS; "// &
 
 2440                          "$\rho(E) = \sum_n \exp(((E-\varepsilon_n)/\alpha)^2)/("// &
 
 2441                          " \sqrt{2\pi} \alpha)$.", &
 
 2442                          usage=
"BROADENING 0.01", &
 
 2449         keyword, __location__, name=
"KPOINTS", &
 
 2450         description=
"Monkhorst-Pack k-point mesh of size N_x, N_y, N_z for calculating "// &
 
 2451         "the density of states (DOS). In GW, the KPOINT_DOS mesh is thus used as k-point "// &
 
 2452         αα
"mesh for the self-energy. For non-periodic directions , choose N_ = 1. "// &
 
 2453         "Automatic choice of the k-point mesh for negative "// &
 
 2454         α
"values, i.e. KPOINTS_DOS -1 -1 -1 (automatic choice: N_ = 1 in non-periodic "// &
 
 2455         "direction, 8 k-points in periodic direction). If you like to compute a "// &
 
 2456         "band structure along a k-path, you can specify the k-path in "// &
 
 2458         usage=
"KPOINTS N_x  N_y  N_z", &
 
 2459         n_var=3, type_of_var=
integer_t, default_i_vals=(/-1, -1, -1/))
 
 2463      NULLIFY (subsection)
 
 2464      CALL create_ldos_section(subsection)
 
 2468   END SUBROUTINE create_dos_section
 
 2474   SUBROUTINE create_ldos_section(section)
 
 2479      cpassert(.NOT. 
ASSOCIATED(section))
 
 2481                          description=
"Parameters needed to calculate the local density "// &
 
 2482                          "of states (LDOS).  "// &
 
 2483                          "The LDOS is computed as $\rho(\mathbf{r},E) = "// &
 
 2484                          "\sum\limits_{n,\mathbf{k}}"// &
 
 2485                          " |\psi_{n\mathbf{k}}(r)|^2\, w_\mathbf{k}\, g(E-\varepsilon_{n\mathbf{k}})$ "// &
 
 2486                          "using the Gaussian weight function "// &
 
 2487                          "$g(x) = \exp(x^2/\alpha^2)/(\sqrt{2\pi}\alpha)$, $\alpha$ is the broadening "// &
 
 2488                          "from the &DOS section, and the k-point weight "// &
 
 2489                          "$w_\mathbf{k}$. The k-mesh is taken from the &DOS section.", &
 
 2490                          n_keywords=2, repeats=.false.)
 
 2494                          name=
"_SECTION_PARAMETERS_", &
 
 2495                          description=
"Activates the local VBM CBM gap calculation.", &
 
 2496                          default_l_val=.false., &
 
 2497                          lone_keyword_l_val=.true.)
 
 2502                          description=
"Defines whether the LDOS is integrated along a "// &
 
 2503                          "coordinate. As an example, for INTEGRATION Z, the LDOS "// &
 
 2504                          "$\rho(x,y,E) = \int dz\, \rho(x,y,z,E)$ is computed.", &
 
 2505                          usage=
"INTEGRATION Z", &
 
 2506                          enum_c_vals=
s2a(
"X", 
"Y", 
"Z", 
"NONE"), &
 
 2508                          enum_desc=
s2a(
"Integrate over x coordinate (not yet implemented).", &
 
 2509                                        "Integrate over y coordinate (not yet implemented).", &
 
 2510                                        "Integrate over z coordinate.", &
 
 2511                                        "No integration, print cube file as function "// &
 
 2512                                        "of x,y,z (not yet implemented)."), &
 
 2518         keyword, __location__, name=
"BIN_MESH", &
 
 2519         description=
"Mesh of size n x m for binning the space coordinates x and y of "// &
 
 2520         "the LDOS $\rho(x,y,E)$. If -1, no binning is performed and the "// &
 
 2521         "fine x, y resolution of the electron density from SCF is used.", &
 
 2522         usage=
"BIN_MESH  n m", &
 
 2523         n_var=2, type_of_var=
integer_t, default_i_vals=(/10, 10/))
 
 2527   END SUBROUTINE create_ldos_section
 
 2535   SUBROUTINE create_tipscan_section(section)
 
 2540      cpassert(.NOT. 
ASSOCIATED(section))
 
 2542                          description=
"Parameters needed to set up a Tip Scan. "// &
 
 2543                          "Needs external definition of tip induced field.", &
 
 2544                          n_keywords=1, n_subsections=1, repeats=.false.)
 
 2549                          name=
"_SECTION_PARAMETERS_", &
 
 2550                          description=
"Controls the activation of the Tip Scan procedure", &
 
 2551                          default_l_val=.false., &
 
 2552                          lone_keyword_l_val=.true.)
 
 2556      CALL keyword_create(keyword, __location__, name=
"SCAN_DIRECTION", &
 
 2557                          description=
"Defines scan direction and scan type(line, plane).", &
 
 2558                          usage=
"SCAN_DIRECTION XY", &
 
 2559                          enum_c_vals=
s2a(
"X", 
"Y", 
"Z", 
"XY", 
"XZ", 
"YZ", 
"XYZ"), &
 
 2565      CALL keyword_create(keyword, __location__, name=
"REFERENCE_POINT", &
 
 2566                          description=
"The reference point to define the absolute position of the scan. ", &
 
 2567                          usage=
"REFERENCE_POINT 0.0 0.0 1.0", &
 
 2568                          n_var=3, default_r_vals=(/0.0_dp, 0.0_dp, 0.0_dp/), type_of_var=
real_t, &
 
 2569                          unit_str=
"angstrom")
 
 2574                          description=
"Number of points calculated for each scan direction.", &
 
 2575                          usage=
"SCAN_POINTS 20 20", &
 
 2581                          description=
"Step size for each scan direction.", &
 
 2582                          usage=
"SCAN_STEP 0.01 0.01", &
 
 2583                          n_var=-1, type_of_var=
real_t, unit_str=
"angstrom")
 
 2587      CALL keyword_create(keyword, __location__, name=
"TIP_FILENAME", &
 
 2588                          description=
"Filename of tip potential defined in cube file format.", &
 
 2589                          usage=
"TIP_FILENAME <filename>", &
 
 2594   END SUBROUTINE create_tipscan_section
 
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 vazdacruz2021
 
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
 
real(kind=dp) function, public cp_unit_to_cp2k(value, unit_str, defaults, power)
converts to the internal cp2k units to the given unit
 
Defines the basic variable types.
 
integer, parameter, public dp
 
Utilities for string manipulations.