(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_kpoints.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 function that build the kpoints section of the input
10!> \par History
11!> init [07.2014]
12!> \author JGH
13! **************************************************************************************************
15 USE bibliography, ONLY: macdonald1978,&
23 USE input_val_types, ONLY: char_t,&
24 real_t
25 USE kinds, ONLY: default_path_length,&
26 dp
27 USE string_utilities, ONLY: newline,&
28 s2a
29#include "./base/base_uses.f90"
30
31 IMPLICIT NONE
32 PRIVATE
33
34 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_kpoints'
35
36 INTEGER, PARAMETER :: use_real_wfn = 101, &
37 use_complex_wfn = 100
38
42
43CONTAINS
44
45! **************************************************************************************************
46!> \brief Creates the Kpoints section
47!> SECTION: &kpoint... &end
48!> SCHEME [None, Gamma, Monkhorst-Pack, MacDonald, General]
49!> { nx ny nz }
50!> { nx ny nz sx sy sz }
51!> KPOINT x1 y1 z1 w1
52!> SYMMETRY [on, off]
53!> WAVEFUNCTION [real, complex]
54!> FULL_GRID [on, off]
55!> VERBOSE [on, off]
56!> EPS_GEO value
57!> PARALLEL_GROUP_SIZE [-1,0,n]
58!>
59!> \param section the section to create
60!> \author JGH
61! **************************************************************************************************
62 SUBROUTINE create_kpoints_section(section)
63 TYPE(section_type), POINTER :: section
64
65 TYPE(keyword_type), POINTER :: keyword
66
67 cpassert(.NOT. ASSOCIATED(section))
68 CALL section_create(section, __location__, name="KPOINTS", &
69 description="Sets up the kpoints.", &
70 n_keywords=1, n_subsections=0, repeats=.false.)
71
72 NULLIFY (keyword)
73 CALL keyword_create(keyword, __location__, name="SCHEME", &
74 description="Kpoint scheme to be used. Available options are:"//newline// &
75 "- `NONE`"//newline// &
76 "- `GAMMA`"//newline// &
77 "- `MONKHORST-PACK`"//newline// &
78 "- `MACDONALD`"//newline// &
79 "- `GENERAL`"//newline// &
80 newline// &
81 "For `MONKHORST-PACK` and `MACDONALD` the number of k points in all "// &
82 "3 dimensions has to be supplied along with the keyword. "// &
83 "E.g. `MONKHORST-PACK 12 12 8`", &
84 usage="SCHEME {KPMETHOD} {integer} {integer} ..", &
85 citations=(/monkhorst1976, macdonald1978/), &
86 n_var=-1, type_of_var=char_t)
87 CALL section_add_keyword(section, keyword)
88 CALL keyword_release(keyword)
89
90 CALL keyword_create(keyword, __location__, name="KPOINT", &
91 description="Specify kpoint coordinates and weight. ", &
92 usage="KPOINT x y z w", repeats=.true., &
93 n_var=4, type_of_var=real_t)
94 CALL section_add_keyword(section, keyword)
95 CALL keyword_release(keyword)
96
97 CALL keyword_create(keyword, __location__, name="UNITS", &
98 description="Special k-points are defined either in units"// &
99 " of reciprocal lattice vectors or in Cartesian coordinates in uints of 2Pi/len."// &
100 " B_VECTOR: in multiples of the reciprocal lattice vectors (b)."// &
101 " CART_ANGSTROM: In units of 2*Pi/Angstrom."// &
102 " CART_BOHR: In units of 2*Pi/Bohr.", &
103 usage="UNITS <value>", type_of_var=char_t, default_c_val="B_VECTOR")
104 CALL section_add_keyword(section, keyword)
105 CALL keyword_release(keyword)
106
107 CALL keyword_create(keyword, __location__, name="SYMMETRY", &
108 description="Use symmetry to reduce the number of kpoints.", &
109 usage="SYMMETRY <LOGICAL>", &
110 default_l_val=.false., lone_keyword_l_val=.true.)
111 CALL section_add_keyword(section, keyword)
112 CALL keyword_release(keyword)
113
114 CALL keyword_create(keyword, __location__, name="FULL_GRID", &
115 description="Use full non-reduced kpoint grid.", &
116 usage="FULL_GRID <LOGICAL>", &
117 default_l_val=.false., lone_keyword_l_val=.true.)
118 CALL section_add_keyword(section, keyword)
119 CALL keyword_release(keyword)
120
121 CALL keyword_create(keyword, __location__, name="VERBOSE", &
122 description="Verbose output information.", &
123 usage="VERBOSE <LOGICAL>", &
124 default_l_val=.false., lone_keyword_l_val=.true.)
125 CALL section_add_keyword(section, keyword)
126 CALL keyword_release(keyword)
127
128 CALL keyword_create(keyword, __location__, name="EPS_GEO", &
129 description="Accuracy in symmetry determination.", &
130 usage="EPS_GEO <real>", &
131 default_r_val=1.0e-6_dp)
132 CALL section_add_keyword(section, keyword)
133 CALL keyword_release(keyword)
134
135 CALL keyword_create(keyword, __location__, name="PARALLEL_GROUP_SIZE", &
136 description="Number of processors to be used for a single kpoint."// &
137 " This number must divide the total number of processes."// &
138 " The number of groups must divide the total number of kpoints."// &
139 " Value=-1 (smallest possible number of processes per group, satisfying the constraints)."// &
140 " Value=0 (all processes)."// &
141 " Value=n (exactly n processes).", &
142 usage="PARALLEL_GROUP_SIZE <integer>", &
143 default_i_val=-1)
144 CALL section_add_keyword(section, keyword)
145 CALL keyword_release(keyword)
146
147 CALL keyword_create(keyword, __location__, name="WAVEFUNCTIONS", &
148 description="Use real/complex wavefunctions if possible.", &
149 usage="WAVEFUNCTIONS REAL", &
150 default_i_val=use_complex_wfn, &
151 enum_c_vals=s2a("REAL", "COMPLEX"), &
152 enum_desc=s2a("Use real wavefunctions (if possible by kpoints specified).", &
153 "Use complex wavefunctions (default)."), &
154 enum_i_vals=(/use_real_wfn, use_complex_wfn/))
155 CALL section_add_keyword(section, keyword)
156 CALL keyword_release(keyword)
157
158 END SUBROUTINE create_kpoints_section
159
160! **************************************************************************************************
161!> \brief ...
162!> \param section ...
163!> \param section_name ...
164!> \author JGH
165! **************************************************************************************************
166 SUBROUTINE create_kpoint_set_section(section, section_name)
167 TYPE(section_type), POINTER :: section
168 CHARACTER(LEN=*), OPTIONAL :: section_name
169
170 CHARACTER(len=default_path_length) :: my_section_name
171 TYPE(keyword_type), POINTER :: keyword
172
173 IF (PRESENT(section_name)) THEN
174 my_section_name = section_name
175 ELSE
176 my_section_name = "KPOINT_SET"
177 END IF
178
179 cpassert(.NOT. ASSOCIATED(section))
180 CALL section_create(section, __location__, name=my_section_name, &
181 description="Specifies a k-point line to be calculated.", &
182 n_keywords=0, n_subsections=0, repeats=.true.)
183 ! keywords
184 NULLIFY (keyword)
185 CALL keyword_create(keyword, __location__, name="SPECIAL_POINT", &
186 description="Name and coordinates of a special k-point", &
187 usage="SPECIAL_POINT GAMMA 0.0 0.0 0.0", n_var=-1, type_of_var=char_t, repeats=.true.)
188 CALL section_add_keyword(section, keyword)
189 CALL keyword_release(keyword)
190 !
191 CALL keyword_create(keyword, __location__, name="NPOINTS", &
192 description="Number of k-points along the line.", &
193 default_i_val=0)
194 CALL section_add_keyword(section, keyword)
195 CALL keyword_release(keyword)
196 !
197 CALL keyword_create(keyword, __location__, name="UNITS", &
198 description="Special k-points are defined either in units"// &
199 " of reciprocal lattice vectors or in Cartesian coordinates in uints of 2Pi/len."// &
200 " B_VECTOR: in multiples of the reciprocal lattice vectors (b)."// &
201 " CART_ANGSTROM: In units of 2*Pi/Angstrom."// &
202 " CART_BOHR: In units of 2*Pi/Bohr.", &
203 usage="UNITS <value>", type_of_var=char_t, default_c_val="B_VECTOR")
204 CALL section_add_keyword(section, keyword)
205 CALL keyword_release(keyword)
206
207 END SUBROUTINE create_kpoint_set_section
208
209END MODULE input_cp2k_kpoints
collects all references to literature in CP2K as new algorithms / method are included from literature...
integer, save, public monkhorst1976
integer, save, public macdonald1978
function that build the kpoints section of the input
subroutine, public create_kpoints_section(section)
Creates the Kpoints section SECTION: &kpoint... &end SCHEME [None, Gamma, Monkhorst-Pack,...
integer, parameter, public use_real_wfn
subroutine, public create_kpoint_set_section(section, section_name)
...
integer, parameter, public use_complex_wfn
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
a wrapper for basic fortran types.
integer, parameter, public real_t
integer, parameter, public char_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
integer, parameter, public default_path_length
Definition kinds.F:58
Utilities for string manipulations.
character(len=1), parameter, public newline
represent a keyword in the input
represent a section of the input file