(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_exstate.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief Excited state input section
10!> \par History
11!> 01.2020 created
12!> \author jgh
13! **************************************************************************************************
24 USE kinds, ONLY: dp
25 USE string_utilities, ONLY: s2a
26#include "./base/base_uses.f90"
27
28 IMPLICIT NONE
29 PRIVATE
30
31 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_exstate'
32
34
35CONTAINS
36
37! **************************************************************************************************
38!> \brief creates the EXCITED ENERGY section
39!> \param section ...
40!> \author JGH
41! **************************************************************************************************
42 SUBROUTINE create_exstate_section(section)
43 TYPE(section_type), POINTER :: section
44
45 TYPE(keyword_type), POINTER :: keyword
46
47 cpassert(.NOT. ASSOCIATED(section))
48
49 NULLIFY (keyword)
50 CALL section_create(section, __location__, name="EXCITED_STATES", &
51 description="Sets the various options for Excited State Potential Energy Calculations", &
52 n_keywords=1, n_subsections=0, repeats=.false.)
53
54 CALL keyword_create(keyword, __location__, name="_SECTION_PARAMETERS_", &
55 description="Controls the activation of the excited states", &
56 usage="&EXCITED_STATES T", &
57 default_l_val=.false., &
58 lone_keyword_l_val=.true.)
59 CALL section_add_keyword(section, keyword)
60 CALL keyword_release(keyword)
61
62 CALL keyword_create(keyword, __location__, name="STATE", &
63 description="Excited state to be used in calculation. Negative values indicate state following.", &
64 usage="STATE 2", &
65 default_i_val=1)
66 CALL section_add_keyword(section, keyword)
67 CALL keyword_release(keyword)
68
69 CALL keyword_create(keyword, __location__, name="XC_KERNEL_METHOD", &
70 description="Method to evaluate XC Kernel contributions to forces", &
71 usage="XC_KERNEL_METHOD (BEST_AVAILABLE|ANALYTIC|NUMERIC)", &
72 enum_c_vals=s2a("BEST_AVAILABLE", "ANALYTIC", "NUMERIC"), &
74 default_i_val=xc_kernel_method_best)
75 CALL section_add_keyword(section, keyword)
76 CALL keyword_release(keyword)
77
78 CALL keyword_create(keyword, __location__, name="EPS_DELTA_RHO", &
79 description="Step size for finite difference calculation of functional derivatives.", &
80 usage="EPS_DELTA_RHO 1.E-02", &
81 default_r_val=1.e-03_dp)
82 CALL section_add_keyword(section, keyword)
83 CALL keyword_release(keyword)
84
85 CALL keyword_create(keyword, __location__, name="DIFF_ORDER", &
86 description="Order of finite differentiation formula used for functional derivatives.", &
87 usage="DIFF_ORDER 4", &
88 default_i_val=6)
89 CALL section_add_keyword(section, keyword)
90 CALL keyword_release(keyword)
91
92 CALL keyword_create(keyword, __location__, name="OVERLAP_DELTAT", &
93 description="Keyword for the computation of the overlap matrix between two consecutive time steps.", &
94 usage="OVERLAP_DELTAT", &
95 default_l_val=.false., &
96 lone_keyword_l_val=.true.)
97 CALL section_add_keyword(section, keyword)
98 CALL keyword_release(keyword)
99
100 CALL keyword_create(keyword, __location__, name="DEBUG_FORCES", &
101 description="Activate printing of intermediate forces in excited state force calculations.", &
102 usage="DEBUG_FORCES T", &
103 default_l_val=.false., &
104 lone_keyword_l_val=.true.)
105 CALL section_add_keyword(section, keyword)
106 CALL keyword_release(keyword)
107
108 END SUBROUTINE create_exstate_section
109
110END MODULE input_cp2k_exstate
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public xc_kernel_method_best
integer, parameter, public xc_kernel_method_analytic
integer, parameter, public xc_kernel_method_numeric
Excited state input section.
subroutine, public create_exstate_section(section)
creates the EXCITED ENERGY section
represents keywords in an input
subroutine, public keyword_release(keyword)
releases the given keyword (see doc/ReferenceCounting.html)
subroutine, public keyword_create(keyword, location, name, description, usage, type_of_var, n_var, repeats, variants, default_val, default_l_val, default_r_val, default_lc_val, default_c_val, default_i_val, default_l_vals, default_r_vals, default_c_vals, default_i_vals, lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
creates a keyword object
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_create(section, location, name, description, n_keywords, n_subsections, repeats, citations)
creates a list of keywords
subroutine, public section_add_keyword(section, keyword)
adds a keyword to the given section
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