(git:d18deda)
Loading...
Searching...
No Matches
eeq_input.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief Input definition and setup for EEQ model
10!> \author JGH [2024]
11! **************************************************************************************************
21 USE kinds, ONLY: dp
22#include "./base/base_uses.f90"
23
24 IMPLICIT NONE
25 PRIVATE
26
28 LOGICAL :: direct = .false.
29 LOGICAL :: sparse = .false.
30 REAL(kind=dp) :: eps_diis = 1.0e-09_dp
31 REAL(kind=dp) :: alpha = 0.75_dp
32 INTEGER :: mdiis = 12
33 INTEGER :: sdiis = 3
34 INTEGER :: max_diis = 500
35 END TYPE eeq_solver_type
36
37 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'eeq_input'
38
39 PUBLIC :: eeq_solver_type
40 PUBLIC :: read_eeq_param
42
43CONTAINS
44
45! **************************************************************************************************
46!> \brief ...
47!> \param section ...
48! **************************************************************************************************
49 SUBROUTINE create_eeq_control_section(section)
50 TYPE(section_type), POINTER :: section
51
52 TYPE(keyword_type), POINTER :: keyword
53
54 cpassert(.NOT. ASSOCIATED(section))
55 CALL section_create(section, __location__, name="EEQ", &
56 description="Parameters needed for EEQ method and solver", &
57 n_keywords=1, n_subsections=1, repeats=.false.)
58
59 NULLIFY (keyword)
60 CALL keyword_create(keyword, __location__, name="DIRECT", &
61 description="Use a direct method to solve the EEQ equations in PBC (matrix solver)", &
62 usage="DIRECT", default_l_val=.false., lone_keyword_l_val=.true.)
63 CALL section_add_keyword(section, keyword)
64 CALL keyword_release(keyword)
65
66 CALL keyword_create(keyword, __location__, name="SPARSE", &
67 description="Use a sparse method to solve the EEQ equations. (NYA)", &
68 usage="SPARSE", default_l_val=.false., lone_keyword_l_val=.true.)
69 CALL section_add_keyword(section, keyword)
70 CALL keyword_release(keyword)
71
72 CALL keyword_create(keyword, __location__, name="EPS_DIIS", &
73 description="Accuracy for the iterative solver.", &
74 usage="EPS_DIIS 1.0E-10", default_r_val=1.0e-10_dp)
75 CALL section_add_keyword(section, keyword)
76 CALL keyword_release(keyword)
77
78 CALL keyword_create(keyword, __location__, name="ALPHA", &
79 description="Step length of initial steepest descent steps.", &
80 usage="ALPHA 1.0", default_r_val=0.75_dp)
81 CALL section_add_keyword(section, keyword)
82 CALL keyword_release(keyword)
83
84 CALL keyword_create(keyword, __location__, name="MAX_DIIS", &
85 description="Max. number of iterations for EEQ solver.", &
86 usage="MAX_DIIS 100", default_i_val=500)
87 CALL section_add_keyword(section, keyword)
88 CALL keyword_release(keyword)
89
90 CALL keyword_create(keyword, __location__, name="MDIIS", &
91 description="Max. number of DIIS vectors used.", &
92 usage="MDIIS 10", default_i_val=12)
93 CALL section_add_keyword(section, keyword)
94 CALL keyword_release(keyword)
95
96 CALL keyword_create(keyword, __location__, name="SDIIS", &
97 description="Number of vectors accumulated before starting DIIS.", &
98 usage="SDIIS 4", default_i_val=3)
99 CALL section_add_keyword(section, keyword)
100 CALL keyword_release(keyword)
101
102 END SUBROUTINE create_eeq_control_section
103
104! **************************************************************************************************
105!> \brief ...
106!> \param eeq_section ...
107!> \param eeq_sparam ...
108! **************************************************************************************************
109 SUBROUTINE read_eeq_param(eeq_section, eeq_sparam)
110
111 TYPE(section_vals_type), POINTER :: eeq_section
112 TYPE(eeq_solver_type), INTENT(INOUT) :: eeq_sparam
113
114 CALL section_vals_val_get(eeq_section, "DIRECT", l_val=eeq_sparam%direct)
115 CALL section_vals_val_get(eeq_section, "SPARSE", l_val=eeq_sparam%sparse)
116 CALL section_vals_val_get(eeq_section, "EPS_DIIS", r_val=eeq_sparam%eps_diis)
117 CALL section_vals_val_get(eeq_section, "ALPHA", r_val=eeq_sparam%alpha)
118 CALL section_vals_val_get(eeq_section, "MAX_DIIS", i_val=eeq_sparam%max_diis)
119 CALL section_vals_val_get(eeq_section, "MDIIS", i_val=eeq_sparam%mdiis)
120 CALL section_vals_val_get(eeq_section, "SDIIS", i_val=eeq_sparam%sdiis)
121
122 END SUBROUTINE read_eeq_param
123
124END MODULE eeq_input
Input definition and setup for EEQ model.
Definition eeq_input.F:12
subroutine, public create_eeq_control_section(section)
...
Definition eeq_input.F:50
subroutine, public read_eeq_param(eeq_section, eeq_sparam)
...
Definition eeq_input.F:110
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_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
represent a keyword in the input
represent a section of the input file