Loading [MathJax]/extensions/tex2jax.js
 (git:aabdcc8)
All Data Structures Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros
input_cp2k_pwdft.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 Creates the PW section of the input
10! > \par History
11! > 07.2018 created
12! > \author JHU
13! **************************************************************************************************
14
16#if defined(__SIRIUS)
17 USE iso_c_binding, ONLY: c_loc
18 USE sirius, ONLY: &
19 sirius_option_get, &
20 sirius_option_get_section_length, sirius_option_get_info, &
21 sirius_integer_type, sirius_number_type, sirius_string_type, &
22 sirius_logical_type, sirius_array_type, sirius_integer_array_type, sirius_logical_array_type, &
23 sirius_number_array_type, sirius_string_array_type, string_f2c
24#endif
33 USE input_val_types, ONLY: char_t, &
34 integer_t, &
35 lchar_t, &
36 logical_t, &
37 real_t
45 USE kinds, ONLY: dp
46 USE string_utilities, ONLY: s2a
47#include "./base/base_uses.f90"
48
49 IMPLICIT NONE
50 PRIVATE
51
52 LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .true.
53 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_pwdft'
54
55 PUBLIC :: create_pwdft_section
56
57 INTEGER, PARAMETER, PUBLIC :: sirius_no_vdw = -1
58 INTEGER, PARAMETER, PUBLIC :: sirius_func_vdwdf = 1
59 INTEGER, PARAMETER, PUBLIC :: sirius_func_vdwdf2 = 2
60 INTEGER, PARAMETER, PUBLIC :: sirius_func_vdwdfcx = 3
61
62CONTAINS
63
64#if defined(__SIRIUS)
65! **************************************************************************************************
66!> \brief Create the input section for PW calculations using SIRIUS
67!> \param section the section to create
68!> \par History
69!> 07.2018 created
70!> \author JHU
71! **************************************************************************************************
72 SUBROUTINE create_pwdft_section(section)
73 TYPE(section_type), POINTER :: section
74
75 TYPE(keyword_type), POINTER :: keyword
76 TYPE(section_type), POINTER :: subsection
77
78! ------------------------------------------------------------------------
79
80 cpassert(.NOT. ASSOCIATED(section))
81 CALL section_create(section, __location__, name="PW_DFT", &
82 description="DFT calculation using plane waves basis can be set in this section. "// &
83 "The backend called SIRIUS, computes the basic properties of the system, "// &
84 "such as ground state, forces and stresses tensors which can be used by "// &
85 "cp2k afterwards. The engine has all these features build-in, support of "// &
86 "pseudo-potentials and full-potentials, spin-orbit coupling, collinear and "// &
87 "non collinear magnetism, Hubbard correction, all exchange functionals "// &
88 "supported by libxc and Van der Waals corrections (libvdwxc).")
89
90 NULLIFY (keyword)
91 CALL keyword_create(keyword, __location__, &
92 name='ignore_convergence_failure', &
93 description="when set to true, calculation will continue irrespectively "// &
94 "of the convergence status of SIRIUS", &
95 type_of_var=logical_t, &
96 repeats=.false., &
97 default_l_val=.false., &
98 lone_keyword_l_val=.true.)
99 CALL section_add_keyword(section, keyword)
100 CALL keyword_release(keyword)
101
102 NULLIFY (subsection)
103 CALL create_sirius_section(subsection, 'control')
104 CALL section_add_subsection(section, subsection)
105 CALL section_release(subsection)
106
107 CALL create_sirius_section(subsection, 'parameters')
108 CALL section_add_subsection(section, subsection)
109 CALL section_release(subsection)
110
111 CALL create_sirius_section(subsection, 'settings')
112 CALL section_add_subsection(section, subsection)
113 CALL section_release(subsection)
114
115 CALL create_sirius_section(subsection, 'mixer')
116 CALL section_add_subsection(section, subsection)
117 CALL section_release(subsection)
118
119 CALL create_sirius_section(subsection, 'iterative_solver')
120 CALL section_add_subsection(section, subsection)
121 CALL section_release(subsection)
122
123 !
124 ! uncomment these lines when nlcg is officialy supported in cp2k
125 !
126
127 ! CALL create_sirius_section(subsection, 'nlcg')
128 ! CALL section_add_subsection(section, subsection)
129 ! CALL section_release(subsection)
130
131 CALL create_print_section(subsection)
132 CALL section_add_subsection(section, subsection)
133 CALL section_release(subsection)
134
135 END SUBROUTINE create_pwdft_section
136
137! **************************************************************************************************
138!> \brief input section for PWDFT control
139!> \param section will contain the CONTROL section
140!> \param section_name ...
141!> \author JHU
142! **************************************************************************************************
143 SUBROUTINE create_sirius_section(section, section_name)
144 TYPE(section_type), POINTER :: section
145 CHARACTER(len=*), INTENT(in) :: section_name
146
147 INTEGER :: length
148
149 cpassert(.NOT. ASSOCIATED(section))
150 CALL sirius_option_get_section_length(trim(adjustl(section_name)), length)
151
152 CALL section_create(section, __location__, &
153 name=trim(adjustl(section_name)), &
154 description=trim(section_name)//" section", &
155 n_subsections=0, &
156 n_keywords=length, &
157 repeats=.false.)
158
159 CALL fill_in_section(section, trim(adjustl(section_name)))
160 END SUBROUTINE create_sirius_section
161
162! **************************************************************************************************
163!> \brief ...
164!> \param section ...
165!> \param section_name ...
166! **************************************************************************************************
167 SUBROUTINE fill_in_section(section, section_name)
168 TYPE(section_type), POINTER :: section
169 CHARACTER(len=*), INTENT(in) :: section_name
170
171 CHARACTER(len=128) :: name
172 CHARACTER(len=128), TARGET :: possible_values(1:16)
173 CHARACTER(len=4096) :: description, usage
174 INTEGER :: ctype, enum_i_val(1:16), enum_length, i, &
175 j, length, num_possible_values
176 INTEGER, ALLOCATABLE, DIMENSION(:), TARGET :: ivec
177 INTEGER, TARGET :: dummy_i
178 LOGICAL :: lvecl(1:16)
179 LOGICAL(4), ALLOCATABLE, DIMENSION(:), TARGET :: lvec
180 LOGICAL(4), TARGET :: dummy_l
181 REAL(kind=dp), ALLOCATABLE, DIMENSION(:), TARGET :: rvec
182 REAL(kind=dp), TARGET :: dummy_r
183 TYPE(keyword_type), POINTER :: keyword
184
185 ALLOCATE (ivec(1:16))
186 ALLOCATE (rvec(1:16))
187 ALLOCATE (lvec(1:16))
188
189#ifdef __LIBVDWXC
190 IF (section_name == "parameters") THEN
191 NULLIFY (keyword)
192 CALL keyword_create(keyword, __location__, name="VDW_FUNCTIONAL", &
193 description="Select the Van der Walls functionals corrections type", &
194 default_i_val=sirius_no_vdw, &
196 enum_c_vals=s2a("NONE", "FUNC_VDWDF", "FUNC_VDWDF2", "FUNC_VDWDFCX"), &
197 enum_desc=s2a("No VdW correction", &
198 "FUNC_VDWDF", &
199 "FUNC_VDWDF2", &
200 "FUNC_VDWDFCX"))
201 CALL section_add_keyword(section, keyword)
202 CALL keyword_release(keyword)
203 END IF
204#endif
205
206 CALL sirius_option_get_section_length(section_name, length)
207
208 DO i = 1, length
209 NULLIFY (keyword)
210 name = ''
211 description = ''
212 usage = ''
213 CALL sirius_option_get_info(section_name, &
214 i, &
215 name, &
216 128, &
217 ctype, &
218 num_possible_values, &
219 enum_length, &
220 description, &
221 4096, &
222 usage, &
223 4096)
224 ! description and usage are ignored here
225 ! it is a minor inconvenience from the api.
226
227 name = trim(adjustl(name))
228 ! I exclude these three keywords because one of them is for debugging
229 ! purpose the other are replaced by a dedicated call in cp2k
230 !
231 ! Moreover xc_functionals would need a special treatment.
232
233 IF ((name /= 'xc_functionals') .AND. (name /= 'memory_usage') .AND. (name /= 'vk')) THEN
234 ! we need to null char since SIRIUS interface is basically C
235 SELECT CASE (ctype)
236 CASE (sirius_integer_type)
237 CALL sirius_option_get(section_name, name, ctype, c_loc(dummy_i))
238 CALL keyword_create(keyword, __location__, &
239 name=trim(name), &
240 description=trim(adjustl(description)), &
241 ! usage=TRIM(ADJUSTL(usage)), &
242 type_of_var=integer_t, &
243 repeats=.false., &
244 default_i_val=dummy_i)
245 CALL section_add_keyword(section, keyword)
246 CALL keyword_release(keyword)
247 CASE (sirius_number_type)
248 CALL sirius_option_get(section_name, name, ctype, c_loc(dummy_r))
249 CALL keyword_create(keyword, __location__, &
250 name=name, &
251 description=trim(adjustl(description)), &
252 ! usage=TRIM(ADJUSTL(usage)), &
253 type_of_var=real_t, &
254 repeats=.false., &
255 default_r_val=dummy_r)
256 CALL section_add_keyword(section, keyword)
257 CALL keyword_release(keyword)
258 CASE (sirius_logical_type)
259 dummy_l = .false.
260 CALL sirius_option_get(section_name, name, ctype, c_loc(dummy_l))
261 IF (dummy_l) THEN
262 CALL keyword_create(keyword, __location__, &
263 name=name, &
264 description=trim(adjustl(description)), &
265 ! usage=TRIM(ADJUSTL(usage)), &
266 type_of_var=logical_t, &
267 repeats=.false., &
268 default_l_val=.true., &
269 lone_keyword_l_val=.true.)
270 ELSE
271 CALL keyword_create(keyword, __location__, &
272 name=name, &
273 description=trim(adjustl(description)), &
274 ! usage=TRIM(ADJUSTL(usage)), &
275 type_of_var=logical_t, &
276 repeats=.false., &
277 default_l_val=.false., &
278 lone_keyword_l_val=.true.)
279 END IF
280 CALL section_add_keyword(section, keyword)
281 CALL keyword_release(keyword)
282 CASE (sirius_string_type)
283 IF (enum_length >= 1) THEN
284 DO j = 1, enum_length
285 possible_values(j) = ''
286 CALL sirius_option_get(section_name, name, ctype, c_loc(possible_values(j)), max_length=128, enum_idx=j)
287 enum_i_val(j) = j
288 possible_values(j) = trim(adjustl(possible_values(j)))
289 END DO
290
291 IF (enum_length > 1) THEN
292 CALL keyword_create(keyword, __location__, &
293 name=name, &
294 description=trim(adjustl(description)), &
295 ! usage=TRIM(ADJUSTL(usage)), &
296 repeats=.false., &
297 enum_i_vals=enum_i_val(1:enum_length), &
298 enum_c_vals=possible_values(1:enum_length), &
299 default_i_val=1)
300 ELSE
301 CALL keyword_create(keyword, __location__, &
302 name=name, &
303 description=trim(adjustl(description)), &
304 ! usage=TRIM(ADJUSTL(usage)), &
305 type_of_var=char_t, &
306 default_c_val=possible_values(1), &
307 repeats=.false.)
308 END IF
309 ELSE
310 CALL keyword_create(keyword, __location__, &
311 name=name, &
312 description=trim(adjustl(description)), &
313 ! usage=TRIM(ADJUSTL(usage)), &
314 type_of_var=char_t, &
315 default_c_val='', &
316 repeats=.false.)
317 END IF
318 CALL section_add_keyword(section, keyword)
319 CALL keyword_release(keyword)
320 CASE (sirius_integer_array_type)
321 CALL sirius_option_get(section_name, name, ctype, c_loc(ivec(1)), max_length=16)
322
323 IF (num_possible_values .EQ. 0) THEN
324 CALL keyword_create(keyword, __location__, &
325 name=name, &
326 description=trim(adjustl(description)), &
327 type_of_var=integer_t, &
328 n_var=-1, &
329 repeats=.false.)
330 ELSE
331 CALL keyword_create(keyword, __location__, &
332 name=name, &
333 description=trim(adjustl(description)), &
334 type_of_var=integer_t, &
335 repeats=.false., &
336 n_var=num_possible_values, &
337 default_i_vals=ivec(1:num_possible_values))
338 END IF
339 CALL section_add_keyword(section, keyword)
340 CALL keyword_release(keyword)
341 CASE (sirius_logical_array_type)
342 CALL sirius_option_get(section_name, name, ctype, c_loc(lvec(1)), max_length=16)
343 DO j = 1, num_possible_values
344 lvecl(j) = lvec(j)
345 END DO
346 IF (num_possible_values > 0) THEN
347 CALL keyword_create(keyword, __location__, &
348 name=name, &
349 description=trim(adjustl(description)), &
350 !usage=TRIM(ADJUSTL(usage)), &
351 type_of_var=logical_t, &
352 repeats=.false., &
353 n_var=num_possible_values, &
354 default_l_vals=lvecl(1:num_possible_values))
355 ELSE
356 CALL keyword_create(keyword, __location__, &
357 name=name, &
358 description=trim(adjustl(description)), &
359 !usage=TRIM(ADJUSTL(usage)), &
360 type_of_var=logical_t, &
361 repeats=.false., &
362 n_var=-1)
363 END IF
364 CALL section_add_keyword(section, keyword)
365 CALL keyword_release(keyword)
366 CASE (sirius_number_array_type)
367 CALL sirius_option_get(section_name, name, ctype, c_loc(rvec(1)), max_length=16)
368
369 IF (num_possible_values .EQ. 0) THEN
370 CALL keyword_create(keyword, __location__, &
371 name=name, &
372 description=trim(adjustl(description)), &
373 ! usage=TRIM(ADJUSTL(usage)), &
374 type_of_var=real_t, &
375 repeats=.false., &
376 n_var=-1)
377 ELSE
378 CALL keyword_create(keyword, __location__, &
379 name=name, &
380 description=trim(adjustl(description)), &
381 ! usage=TRIM(ADJUSTL(usage)), &
382 type_of_var=real_t, &
383 repeats=.false., &
384 n_var=num_possible_values, &
385 default_r_vals=rvec(1:num_possible_values))
386 END IF
387 CALL section_add_keyword(section, keyword)
388 CALL keyword_release(keyword)
389 CASE default
390 END SELECT
391 END IF
392 END DO
393 END SUBROUTINE fill_in_section
394
395! **************************************************************************************************
396!> \brief Create the print section for sirius
397!> \param section the section to create
398!> \author jgh
399! **************************************************************************************************
400 SUBROUTINE create_print_section(section)
401 TYPE(section_type), POINTER :: section
402
403 TYPE(section_type), POINTER :: print_key
404
405 cpassert(.NOT. ASSOCIATED(section))
406 CALL section_create(section, __location__, name="PRINT", &
407 description="Section of possible print options in PW_DFT code.", &
408 n_keywords=0, n_subsections=1, repeats=.false.)
409
410 NULLIFY (print_key)
411 CALL create_dos_section(print_key)
412 CALL section_add_subsection(section, print_key)
413 CALL section_release(print_key)
414
415 END SUBROUTINE create_print_section
416
417! **************************************************************************************************
418!> \brief ...
419!> \param print_key ...
420! **************************************************************************************************
421 SUBROUTINE create_dos_section(print_key)
422
423 TYPE(section_type), POINTER :: print_key
424
425 TYPE(keyword_type), POINTER :: keyword
426
427 NULLIFY (keyword)
428
429 CALL cp_print_key_section_create(print_key, __location__, "DOS", &
430 description="Print Density of States (DOS) (only available states from SCF)", &
431 print_level=debug_print_level, common_iter_levels=1, filename="")
432
433 CALL keyword_create(keyword, __location__, name="APPEND", &
434 description="Append the DOS obtained at different iterations to the output file. "// &
435 "By default the file is overwritten", &
436 usage="APPEND", default_l_val=.false., &
437 lone_keyword_l_val=.true.)
438 CALL section_add_keyword(print_key, keyword)
439 CALL keyword_release(keyword)
440
441 CALL keyword_create(keyword, __location__, name="DELTA_E", &
442 description="Histogramm energy spacing.", &
443 usage="DELTA_E 0.0005", type_of_var=real_t, default_r_val=0.001_dp)
444 CALL section_add_keyword(print_key, keyword)
445 CALL keyword_release(keyword)
446
447 END SUBROUTINE create_dos_section
448
449#else
450! **************************************************************************************************
451!> \brief ...
452!> \param section ...
453! **************************************************************************************************
454 SUBROUTINE create_pwdft_section(section)
455 TYPE(section_type), POINTER :: section
456
457 cpassert(.NOT. ASSOCIATED(section))
458
459 CALL section_create(section, __location__, name="PW_DFT", &
460 description="This section contains all information to run an "// &
461 "SIRIUS PW calculation.", &
462 n_subsections=0, &
463 repeats=.false.)
464
465 END SUBROUTINE create_pwdft_section
466
467#endif
468
469END MODULE input_cp2k_pwdft
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
subroutine, public create_pwdft_section(section)
...
integer, parameter, public sirius_func_vdwdfcx
integer, parameter, public sirius_func_vdwdf2
integer, parameter, public sirius_no_vdw
integer, parameter, public sirius_func_vdwdf
represents keywords in an input
subroutine, public keyword_release(keyword)
releases the given keyword (see doc/ReferenceCounting.html)
subroutine, public keyword_create(keyword, location, name, description, usage, type_of_var, n_var, repeats, variants, default_val, default_l_val, default_r_val, default_lc_val, default_c_val, default_i_val, default_l_vals, default_r_vals, default_c_vals, default_i_vals, lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
creates a keyword object
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_create(section, location, name, description, n_keywords, n_subsections, repeats, citations, deprecation_notice)
creates a list of keywords
subroutine, public section_add_keyword(section, keyword)
adds a keyword to the given section
subroutine, public section_add_subsection(section, subsection)
adds a subsection to the given section
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
a wrapper for basic fortran types.
integer, parameter, public real_t
integer, parameter, public lchar_t
integer, parameter, public logical_t
integer, parameter, public char_t
integer, parameter, public integer_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Utilities for string manipulations.
represent a keyword in the input
represent a section of the input file