(git:a0e5186)
Loading...
Searching...
No Matches
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-2026 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, sirius_object_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#if defined(__SIRIUS_NLCG)
127 CALL create_sirius_section(subsection, 'nlcg')
128 CALL section_add_subsection(section, subsection)
129 CALL section_release(subsection)
130#endif
131
132#if defined(__SIRIUS_VCSQNM)
133 CALL create_sirius_section(subsection, 'vcsqnm')
134 CALL section_add_subsection(section, subsection)
135 CALL section_release(subsection)
136#endif
137
138#if defined(__SIRIUS_DFTD4)
139 CALL create_sirius_section(subsection, "dftd4")
140 CALL section_add_subsection(section, subsection)
141 CALL section_release(subsection)
142
143 CALL create_sirius_section(subsection, "dftd3")
144 CALL section_add_subsection(section, subsection)
145 CALL section_release(subsection)
146#endif
147
148 CALL create_print_section(subsection)
149 CALL section_add_subsection(section, subsection)
150 CALL section_release(subsection)
151
152 END SUBROUTINE create_pwdft_section
153
154! **************************************************************************************************
155!> \brief input section for PWDFT control
156!> \param section will contain the CONTROL section
157!> \param section_name ...
158!> \author JHU
159! **************************************************************************************************
160 SUBROUTINE create_sirius_section(section, section_name)
161 TYPE(section_type), POINTER :: section
162 CHARACTER(len=*), INTENT(in) :: section_name
163
164 INTEGER :: length
165
166 cpassert(.NOT. ASSOCIATED(section))
167 CALL sirius_option_get_section_length(trim(adjustl(section_name)), length)
168
169 CALL section_create(section, __location__, &
170 name=trim(adjustl(section_name)), &
171 description=trim(section_name)//" section", &
172 n_subsections=0, &
173 n_keywords=length, &
174 repeats=.false.)
175
176 CALL fill_in_section(section, trim(adjustl(section_name)))
177 END SUBROUTINE create_sirius_section
178
179! **************************************************************************************************
180!> \brief ...
181!> \param section ...
182!> \param section_name ...
183! **************************************************************************************************
184 SUBROUTINE fill_in_section(section, section_name)
185 TYPE(section_type), POINTER :: section
186 CHARACTER(len=*), INTENT(in) :: section_name
187
188 CHARACTER(len=128) :: name
189 CHARACTER(len=128), TARGET :: possible_values(1:256)
190 CHARACTER(len=4096) :: description, usage
191 INTEGER :: ctype, enum_length, i, j, length, &
192 num_possible_values
193 INTEGER, ALLOCATABLE, DIMENSION(:), TARGET :: enum_i_val, ivec
194 INTEGER, TARGET :: dummy_i
195 LOGICAL :: jump_dft_parameters, lvecl(1:16)
196 LOGICAL(4), ALLOCATABLE, DIMENSION(:), TARGET :: lvec
197 LOGICAL(4), TARGET :: dummy_l
198 REAL(kind=dp), ALLOCATABLE, DIMENSION(:), TARGET :: rvec
199 REAL(kind=dp), TARGET :: dummy_r
200 TYPE(keyword_type), POINTER :: keyword
201
202 ALLOCATE (ivec(1:16))
203 ALLOCATE (rvec(1:16))
204 ALLOCATE (lvec(1:16))
205 ALLOCATE (enum_i_val(1:256))
206 jump_dft_parameters = .false.
207#ifdef __LIBVDWXC
208 IF (section_name == "parameters") THEN
209 NULLIFY (keyword)
210 CALL keyword_create(keyword, __location__, name="VDW_FUNCTIONAL", &
211 description="Select the Van der Walls functionals corrections type", &
212 default_i_val=sirius_no_vdw, &
214 enum_c_vals=s2a("NONE", "FUNC_VDWDF", "FUNC_VDWDF2", "FUNC_VDWDFCX"), &
215 enum_desc=s2a("No VdW correction", &
216 "FUNC_VDWDF", &
217 "FUNC_VDWDF2", &
218 "FUNC_VDWDFCX"))
219 CALL section_add_keyword(section, keyword)
220 CALL keyword_release(keyword)
221 END IF
222#endif
223
224 CALL sirius_option_get_section_length(section_name, length)
225
226 DO i = 1, length
227 NULLIFY (keyword)
228 name = ''
229 description = ''
230 usage = ''
231 CALL sirius_option_get_info(section_name, &
232 i, &
233 name, &
234 128, &
235 ctype, &
236 num_possible_values, &
237 enum_length, &
238 description, &
239 4096, &
240 usage, &
241 4096)
242
243 ! description and usage are ignored here
244 ! it is a minor inconvenience from the api.
245 name = trim(adjustl(name))
246
247#if defined(__SIRIUS_DFTD4)
248 ! need to implement the object case within a section
249 IF (((section_name == 'dftd3') .OR. (section_name == 'dftd4')) .AND. (name == 'parameters')) THEN
250 cycle
251 END IF
252#endif
253
254 ! I exclude these three keywords because one of them is for debugging
255 ! purpose the other are replaced by a dedicated call in cp2k
256 !
257 ! Moreover xc_functionals would need a special treatment.
258
259 IF ((name /= 'xc_functionals') .AND. (name /= 'memory_usage') .AND. (name /= 'vk')) THEN
260 ! we need to null char since SIRIUS interface is basically C
261 SELECT CASE (ctype)
262 CASE (sirius_integer_type)
263 CALL sirius_option_get(section_name, name, ctype, c_loc(dummy_i))
264 CALL keyword_create(keyword, __location__, &
265 name=trim(name), &
266 description=trim(adjustl(description)), &
267 ! usage=TRIM(ADJUSTL(usage)), &
268 type_of_var=integer_t, &
269 repeats=.false., &
270 default_i_val=dummy_i)
271 CALL section_add_keyword(section, keyword)
272 CALL keyword_release(keyword)
273 CASE (sirius_number_type)
274 CALL sirius_option_get(section_name, name, ctype, c_loc(dummy_r))
275 CALL keyword_create(keyword, __location__, &
276 name=name, &
277 description=trim(adjustl(description)), &
278 ! usage=TRIM(ADJUSTL(usage)), &
279 type_of_var=real_t, &
280 repeats=.false., &
281 default_r_val=dummy_r)
282 CALL section_add_keyword(section, keyword)
283 CALL keyword_release(keyword)
284 CASE (sirius_logical_type)
285 dummy_l = .false.
286 CALL sirius_option_get(section_name, name, ctype, c_loc(dummy_l))
287 IF (dummy_l) THEN
288 CALL keyword_create(keyword, __location__, &
289 name=name, &
290 description=trim(adjustl(description)), &
291 ! usage=TRIM(ADJUSTL(usage)), &
292 type_of_var=logical_t, &
293 repeats=.false., &
294 default_l_val=.true., &
295 lone_keyword_l_val=.true.)
296 ELSE
297 CALL keyword_create(keyword, __location__, &
298 name=name, &
299 description=trim(adjustl(description)), &
300 ! usage=TRIM(ADJUSTL(usage)), &
301 type_of_var=logical_t, &
302 repeats=.false., &
303 default_l_val=.false., &
304 lone_keyword_l_val=.true.)
305 END IF
306 CALL section_add_keyword(section, keyword)
307 CALL keyword_release(keyword)
308 CASE (sirius_string_type)
309 IF (enum_length >= 1) THEN
310 DO j = 1, enum_length
311 possible_values(j) = ''
312 CALL sirius_option_get(section_name, name, ctype, c_loc(possible_values(j)), max_length=128, enum_idx=j)
313 enum_i_val(j) = j
314 possible_values(j) = trim(adjustl(possible_values(j)))
315 END DO
316
317 IF (enum_length > 1) THEN
318 CALL keyword_create(keyword, __location__, &
319 name=name, &
320 description=trim(adjustl(description)), &
321 ! usage=TRIM(ADJUSTL(usage)), &
322 repeats=.false., &
323 enum_i_vals=enum_i_val(1:enum_length), &
324 enum_c_vals=possible_values(1:enum_length), &
325 default_i_val=1)
326 ELSE
327 CALL keyword_create(keyword, __location__, &
328 name=name, &
329 description=trim(adjustl(description)), &
330 ! usage=TRIM(ADJUSTL(usage)), &
331 type_of_var=char_t, &
332 default_c_val=possible_values(1), &
333 repeats=.false.)
334 END IF
335 ELSE
336 CALL keyword_create(keyword, __location__, &
337 name=name, &
338 description=trim(adjustl(description)), &
339 ! usage=TRIM(ADJUSTL(usage)), &
340 type_of_var=char_t, &
341 default_c_val='', &
342 repeats=.false.)
343 END IF
344 CALL section_add_keyword(section, keyword)
345 CALL keyword_release(keyword)
346 CASE (sirius_integer_array_type)
347 CALL sirius_option_get(section_name, name, ctype, c_loc(ivec(1)), max_length=16)
348
349 IF (num_possible_values == 0) THEN
350 CALL keyword_create(keyword, __location__, &
351 name=name, &
352 description=trim(adjustl(description)), &
353 type_of_var=integer_t, &
354 n_var=-1, &
355 repeats=.false.)
356 ELSE
357 CALL keyword_create(keyword, __location__, &
358 name=name, &
359 description=trim(adjustl(description)), &
360 type_of_var=integer_t, &
361 repeats=.false., &
362 n_var=num_possible_values, &
363 default_i_vals=ivec(1:num_possible_values))
364 END IF
365 CALL section_add_keyword(section, keyword)
366 CALL keyword_release(keyword)
367 CASE (sirius_logical_array_type)
368 CALL sirius_option_get(section_name, name, ctype, c_loc(lvec(1)), max_length=16)
369 DO j = 1, num_possible_values
370 lvecl(j) = lvec(j)
371 END DO
372 IF (num_possible_values > 0) THEN
373 CALL keyword_create(keyword, __location__, &
374 name=name, &
375 description=trim(adjustl(description)), &
376 !usage=TRIM(ADJUSTL(usage)), &
377 type_of_var=logical_t, &
378 repeats=.false., &
379 n_var=num_possible_values, &
380 default_l_vals=lvecl(1:num_possible_values))
381 ELSE
382 CALL keyword_create(keyword, __location__, &
383 name=name, &
384 description=trim(adjustl(description)), &
385 !usage=TRIM(ADJUSTL(usage)), &
386 type_of_var=logical_t, &
387 repeats=.false., &
388 n_var=-1)
389 END IF
390 CALL section_add_keyword(section, keyword)
391 CALL keyword_release(keyword)
392 CASE (sirius_number_array_type)
393 CALL sirius_option_get(section_name, name, ctype, c_loc(rvec(1)), max_length=16)
394
395 IF (num_possible_values == 0) THEN
396 CALL keyword_create(keyword, __location__, &
397 name=name, &
398 description=trim(adjustl(description)), &
399 ! usage=TRIM(ADJUSTL(usage)), &
400 type_of_var=real_t, &
401 repeats=.false., &
402 n_var=-1)
403 ELSE
404 CALL keyword_create(keyword, __location__, &
405 name=name, &
406 description=trim(adjustl(description)), &
407 ! usage=TRIM(ADJUSTL(usage)), &
408 type_of_var=real_t, &
409 repeats=.false., &
410 n_var=num_possible_values, &
411 default_r_vals=rvec(1:num_possible_values))
412 END IF
413 CALL section_add_keyword(section, keyword)
414 CALL keyword_release(keyword)
415 !CASE (SIRIUS_OBJECT_TYPE)
416 ! create a subsection for the dftd3/dftd4 parameters
417 !CALL create_sirius_section(sub_section, sub_section_name)
418 !CALL section_add_subsection(section, sub_section)
419 !CALL section_release(sub_section)
420 CASE default
421 END SELECT
422 END IF
423 END DO
424 DEALLOCATE (ivec)
425 DEALLOCATE (rvec)
426 DEALLOCATE (lvec)
427 DEALLOCATE (enum_i_val)
428 END SUBROUTINE fill_in_section
429
430! **************************************************************************************************
431!> \brief Create the print section for sirius
432!> \param section the section to create
433!> \author jgh
434! **************************************************************************************************
435 SUBROUTINE create_print_section(section)
436 TYPE(section_type), POINTER :: section
437
438 TYPE(section_type), POINTER :: print_key
439
440 cpassert(.NOT. ASSOCIATED(section))
441 CALL section_create(section, __location__, name="PRINT", &
442 description="Section of possible print options in PW_DFT code.", &
443 n_keywords=0, n_subsections=1, repeats=.false.)
444
445 NULLIFY (print_key)
446 CALL create_dos_section(print_key)
447 CALL section_add_subsection(section, print_key)
448 CALL section_release(print_key)
449
450 END SUBROUTINE create_print_section
451
452! **************************************************************************************************
453!> \brief ...
454!> \param print_key ...
455! **************************************************************************************************
456 SUBROUTINE create_dos_section(print_key)
457
458 TYPE(section_type), POINTER :: print_key
459
460 TYPE(keyword_type), POINTER :: keyword
461
462 NULLIFY (keyword)
463
464 CALL cp_print_key_section_create(print_key, __location__, "DOS", &
465 description="Print Density of States (DOS) (only available states from SCF)", &
466 print_level=debug_print_level, common_iter_levels=1, filename="")
467
468 CALL keyword_create(keyword, __location__, name="APPEND", &
469 description="Append the DOS obtained at different iterations to the output file. "// &
470 "By default the file is overwritten", &
471 usage="APPEND", default_l_val=.false., &
472 lone_keyword_l_val=.true.)
473 CALL section_add_keyword(print_key, keyword)
474 CALL keyword_release(keyword)
475
476 CALL keyword_create(keyword, __location__, name="DELTA_E", &
477 description="Histogramm energy spacing.", &
478 usage="DELTA_E 0.0005", type_of_var=real_t, default_r_val=0.001_dp)
479 CALL section_add_keyword(print_key, keyword)
480 CALL keyword_release(keyword)
481
482 END SUBROUTINE create_dos_section
483
484#else
485! **************************************************************************************************
486!> \brief ...
487!> \param section ...
488! **************************************************************************************************
489 SUBROUTINE create_pwdft_section(section)
490 TYPE(section_type), POINTER :: section
491
492 cpassert(.NOT. ASSOCIATED(section))
493
494 CALL section_create(section, __location__, name="PW_DFT", &
495 description="This section contains all information to run an "// &
496 "SIRIUS PW calculation.", &
497 n_subsections=0, &
498 repeats=.false.)
499
500 END SUBROUTINE create_pwdft_section
501
502#endif
503
504END 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