Line data Source code
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 :
15 : MODULE input_cp2k_pwdft
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
25 : USE input_keyword_types, ONLY: keyword_create, &
26 : keyword_release, &
27 : keyword_type
28 : USE input_section_types, ONLY: section_add_keyword, &
29 : section_add_subsection, &
30 : section_create, &
31 : section_release, &
32 : section_type
33 : USE input_val_types, ONLY: char_t, &
34 : integer_t, &
35 : lchar_t, &
36 : logical_t, &
37 : real_t
38 : USE cp_output_handling, ONLY: add_last_numeric, &
39 : cp_print_key_section_create, &
40 : debug_print_level, &
41 : high_print_level, &
42 : low_print_level, &
43 : medium_print_level, &
44 : silent_print_level
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 :
62 : CONTAINS
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 9284 : 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 9284 : 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 9284 : "supported by libxc and Van der Waals corrections (libvdwxc).")
89 :
90 9284 : 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 9284 : lone_keyword_l_val=.TRUE.)
99 9284 : CALL section_add_keyword(section, keyword)
100 9284 : CALL keyword_release(keyword)
101 :
102 9284 : NULLIFY (subsection)
103 9284 : CALL create_sirius_section(subsection, 'control')
104 9284 : CALL section_add_subsection(section, subsection)
105 9284 : CALL section_release(subsection)
106 :
107 9284 : CALL create_sirius_section(subsection, 'parameters')
108 9284 : CALL section_add_subsection(section, subsection)
109 9284 : CALL section_release(subsection)
110 :
111 9284 : CALL create_sirius_section(subsection, 'settings')
112 9284 : CALL section_add_subsection(section, subsection)
113 9284 : CALL section_release(subsection)
114 :
115 9284 : CALL create_sirius_section(subsection, 'mixer')
116 9284 : CALL section_add_subsection(section, subsection)
117 9284 : CALL section_release(subsection)
118 :
119 9284 : CALL create_sirius_section(subsection, 'iterative_solver')
120 9284 : CALL section_add_subsection(section, subsection)
121 9284 : 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 9284 : CALL create_print_section(subsection)
149 9284 : CALL section_add_subsection(section, subsection)
150 9284 : CALL section_release(subsection)
151 :
152 9284 : 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 46420 : 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 0 : CPASSERT(.NOT. ASSOCIATED(section))
167 46420 : 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 46420 : repeats=.FALSE.)
175 :
176 46420 : CALL fill_in_section(section, TRIM(ADJUSTL(section_name)))
177 46420 : END SUBROUTINE create_sirius_section
178 :
179 : ! **************************************************************************************************
180 : !> \brief ...
181 : !> \param section ...
182 : !> \param section_name ...
183 : ! **************************************************************************************************
184 46420 : 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:16)
190 : CHARACTER(len=4096) :: description, usage
191 : INTEGER :: ctype, enum_i_val(1:16), enum_length, i, &
192 : j, length, num_possible_values
193 46420 : INTEGER, ALLOCATABLE, DIMENSION(:), TARGET :: ivec
194 : INTEGER, TARGET :: dummy_i
195 : LOGICAL :: lvecl(1:16)
196 46420 : LOGICAL(4), ALLOCATABLE, DIMENSION(:), TARGET :: lvec
197 : LOGICAL(4), TARGET :: dummy_l
198 46420 : REAL(kind=dp), ALLOCATABLE, DIMENSION(:), TARGET :: rvec
199 : REAL(kind=dp), TARGET :: dummy_r
200 : TYPE(keyword_type), POINTER :: keyword
201 :
202 46420 : ALLOCATE (ivec(1:16))
203 46420 : ALLOCATE (rvec(1:16))
204 46420 : ALLOCATE (lvec(1:16))
205 :
206 : #ifdef __LIBVDWXC
207 46420 : IF (section_name == "parameters") THEN
208 9284 : NULLIFY (keyword)
209 : CALL keyword_create(keyword, __LOCATION__, name="VDW_FUNCTIONAL", &
210 : description="Select the Van der Walls functionals corrections type", &
211 : default_i_val=SIRIUS_NO_VDW, &
212 : enum_i_vals=[SIRIUS_NO_VDW, SIRIUS_FUNC_VDWDF, SIRIUS_FUNC_VDWDF2, SIRIUS_FUNC_VDWDFCX], &
213 : enum_c_vals=s2a("NONE", "FUNC_VDWDF", "FUNC_VDWDF2", "FUNC_VDWDFCX"), &
214 : enum_desc=s2a("No VdW correction", &
215 : "FUNC_VDWDF", &
216 : "FUNC_VDWDF2", &
217 9284 : "FUNC_VDWDFCX"))
218 9284 : CALL section_add_keyword(section, keyword)
219 9284 : CALL keyword_release(keyword)
220 : END IF
221 : #endif
222 :
223 46420 : CALL sirius_option_get_section_length(section_name, length)
224 :
225 993388 : DO i = 1, length
226 946968 : NULLIFY (keyword)
227 946968 : name = ''
228 946968 : description = ''
229 946968 : usage = ''
230 : CALL sirius_option_get_info(section_name, &
231 : i, &
232 : name, &
233 : 128, &
234 : ctype, &
235 : num_possible_values, &
236 : enum_length, &
237 : description, &
238 : 4096, &
239 : usage, &
240 946968 : 4096)
241 : ! description and usage are ignored here
242 : ! it is a minor inconvenience from the api.
243 :
244 946968 : name = TRIM(ADJUSTL(name))
245 : ! I exclude these three keywords because one of them is for debugging
246 : ! purpose the other are replaced by a dedicated call in cp2k
247 : !
248 : ! Moreover xc_functionals would need a special treatment.
249 :
250 1940356 : IF ((name /= 'xc_functionals') .AND. (name /= 'memory_usage') .AND. (name /= 'vk')) THEN
251 : ! we need to null char since SIRIUS interface is basically C
252 241384 : SELECT CASE (ctype)
253 : CASE (SIRIUS_INTEGER_TYPE)
254 241384 : CALL sirius_option_get(section_name, name, ctype, C_LOC(dummy_i))
255 : CALL keyword_create(keyword, __LOCATION__, &
256 : name=TRIM(name), &
257 : description=TRIM(ADJUSTL(description)), &
258 : ! usage=TRIM(ADJUSTL(usage)), &
259 : type_of_var=integer_t, &
260 : repeats=.FALSE., &
261 241384 : default_i_val=dummy_i)
262 241384 : CALL section_add_keyword(section, keyword)
263 241384 : CALL keyword_release(keyword)
264 : CASE (SIRIUS_NUMBER_TYPE)
265 269236 : CALL sirius_option_get(section_name, name, ctype, C_LOC(dummy_r))
266 : CALL keyword_create(keyword, __LOCATION__, &
267 : name=name, &
268 : description=TRIM(ADJUSTL(description)), &
269 : ! usage=TRIM(ADJUSTL(usage)), &
270 : type_of_var=real_t, &
271 : repeats=.FALSE., &
272 269236 : default_r_val=dummy_r)
273 269236 : CALL section_add_keyword(section, keyword)
274 269236 : CALL keyword_release(keyword)
275 : CASE (SIRIUS_LOGICAL_TYPE)
276 222816 : dummy_l = .FALSE.
277 222816 : CALL sirius_option_get(section_name, name, ctype, C_LOC(dummy_l))
278 222816 : IF (dummy_l) THEN
279 : CALL keyword_create(keyword, __LOCATION__, &
280 : name=name, &
281 : description=TRIM(ADJUSTL(description)), &
282 : ! usage=TRIM(ADJUSTL(usage)), &
283 : type_of_var=logical_t, &
284 : repeats=.FALSE., &
285 : default_l_val=.TRUE., &
286 74272 : lone_keyword_l_val=.TRUE.)
287 : ELSE
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=.FALSE., &
295 148544 : lone_keyword_l_val=.TRUE.)
296 : END IF
297 222816 : CALL section_add_keyword(section, keyword)
298 222816 : CALL keyword_release(keyword)
299 : CASE (SIRIUS_STRING_TYPE)
300 148544 : IF (enum_length >= 1) THEN
301 612744 : DO j = 1, enum_length
302 482768 : possible_values(j) = ''
303 482768 : CALL sirius_option_get(section_name, name, ctype, C_LOC(possible_values(j)), max_length=128, enum_idx=j)
304 482768 : enum_i_val(j) = j
305 612744 : possible_values(j) = TRIM(ADJUSTL(possible_values(j)))
306 : END DO
307 :
308 129976 : IF (enum_length > 1) THEN
309 : CALL keyword_create(keyword, __LOCATION__, &
310 : name=name, &
311 : description=TRIM(ADJUSTL(description)), &
312 : ! usage=TRIM(ADJUSTL(usage)), &
313 : repeats=.FALSE., &
314 : enum_i_vals=enum_i_val(1:enum_length), &
315 : enum_c_vals=possible_values(1:enum_length), &
316 129976 : default_i_val=1)
317 : ELSE
318 : CALL keyword_create(keyword, __LOCATION__, &
319 : name=name, &
320 : description=TRIM(ADJUSTL(description)), &
321 : ! usage=TRIM(ADJUSTL(usage)), &
322 : type_of_var=char_t, &
323 : default_c_val=possible_values(1), &
324 0 : repeats=.FALSE.)
325 : END IF
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='', &
333 18568 : repeats=.FALSE.)
334 : END IF
335 148544 : CALL section_add_keyword(section, keyword)
336 148544 : CALL keyword_release(keyword)
337 : CASE (SIRIUS_INTEGER_ARRAY_TYPE)
338 37136 : CALL sirius_option_get(section_name, name, ctype, C_LOC(ivec(1)), max_length=16)
339 :
340 37136 : IF (num_possible_values == 0) THEN
341 : CALL keyword_create(keyword, __LOCATION__, &
342 : name=name, &
343 : description=TRIM(ADJUSTL(description)), &
344 : type_of_var=integer_t, &
345 : n_var=-1, &
346 0 : repeats=.FALSE.)
347 : ELSE
348 : CALL keyword_create(keyword, __LOCATION__, &
349 : name=name, &
350 : description=TRIM(ADJUSTL(description)), &
351 : type_of_var=integer_t, &
352 : repeats=.FALSE., &
353 : n_var=num_possible_values, &
354 37136 : default_i_vals=ivec(1:num_possible_values))
355 : END IF
356 37136 : CALL section_add_keyword(section, keyword)
357 37136 : CALL keyword_release(keyword)
358 : CASE (SIRIUS_LOGICAL_ARRAY_TYPE)
359 0 : CALL sirius_option_get(section_name, name, ctype, C_LOC(lvec(1)), max_length=16)
360 0 : DO j = 1, num_possible_values
361 0 : lvecl(j) = lvec(j)
362 : END DO
363 0 : IF (num_possible_values > 0) THEN
364 : CALL keyword_create(keyword, __LOCATION__, &
365 : name=name, &
366 : description=TRIM(ADJUSTL(description)), &
367 : !usage=TRIM(ADJUSTL(usage)), &
368 : type_of_var=logical_t, &
369 : repeats=.FALSE., &
370 : n_var=num_possible_values, &
371 0 : default_l_vals=lvecl(1:num_possible_values))
372 : ELSE
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 0 : n_var=-1)
380 : END IF
381 0 : CALL section_add_keyword(section, keyword)
382 0 : CALL keyword_release(keyword)
383 : CASE (SIRIUS_NUMBER_ARRAY_TYPE)
384 9284 : CALL sirius_option_get(section_name, name, ctype, C_LOC(rvec(1)), max_length=16)
385 :
386 9284 : IF (num_possible_values == 0) THEN
387 : CALL keyword_create(keyword, __LOCATION__, &
388 : name=name, &
389 : description=TRIM(ADJUSTL(description)), &
390 : ! usage=TRIM(ADJUSTL(usage)), &
391 : type_of_var=real_t, &
392 : repeats=.FALSE., &
393 0 : n_var=-1)
394 : ELSE
395 : CALL keyword_create(keyword, __LOCATION__, &
396 : name=name, &
397 : description=TRIM(ADJUSTL(description)), &
398 : ! usage=TRIM(ADJUSTL(usage)), &
399 : type_of_var=real_t, &
400 : repeats=.FALSE., &
401 : n_var=num_possible_values, &
402 9284 : default_r_vals=rvec(1:num_possible_values))
403 : END IF
404 9284 : CALL section_add_keyword(section, keyword)
405 937684 : CALL keyword_release(keyword)
406 : CASE default
407 : END SELECT
408 : END IF
409 : END DO
410 92840 : END SUBROUTINE fill_in_section
411 :
412 : ! **************************************************************************************************
413 : !> \brief Create the print section for sirius
414 : !> \param section the section to create
415 : !> \author jgh
416 : ! **************************************************************************************************
417 9284 : SUBROUTINE create_print_section(section)
418 : TYPE(section_type), POINTER :: section
419 :
420 : TYPE(section_type), POINTER :: print_key
421 :
422 9284 : CPASSERT(.NOT. ASSOCIATED(section))
423 : CALL section_create(section, __LOCATION__, name="PRINT", &
424 : description="Section of possible print options in PW_DFT code.", &
425 9284 : n_keywords=0, n_subsections=1, repeats=.FALSE.)
426 :
427 9284 : NULLIFY (print_key)
428 9284 : CALL create_dos_section(print_key)
429 9284 : CALL section_add_subsection(section, print_key)
430 9284 : CALL section_release(print_key)
431 :
432 9284 : END SUBROUTINE create_print_section
433 :
434 : ! **************************************************************************************************
435 : !> \brief ...
436 : !> \param print_key ...
437 : ! **************************************************************************************************
438 9284 : SUBROUTINE create_dos_section(print_key)
439 :
440 : TYPE(section_type), POINTER :: print_key
441 :
442 : TYPE(keyword_type), POINTER :: keyword
443 :
444 9284 : NULLIFY (keyword)
445 :
446 : CALL cp_print_key_section_create(print_key, __LOCATION__, "DOS", &
447 : description="Print Density of States (DOS) (only available states from SCF)", &
448 9284 : print_level=debug_print_level, common_iter_levels=1, filename="")
449 :
450 : CALL keyword_create(keyword, __LOCATION__, name="APPEND", &
451 : description="Append the DOS obtained at different iterations to the output file. "// &
452 : "By default the file is overwritten", &
453 : usage="APPEND", default_l_val=.FALSE., &
454 9284 : lone_keyword_l_val=.TRUE.)
455 9284 : CALL section_add_keyword(print_key, keyword)
456 9284 : CALL keyword_release(keyword)
457 :
458 : CALL keyword_create(keyword, __LOCATION__, name="DELTA_E", &
459 : description="Histogramm energy spacing.", &
460 9284 : usage="DELTA_E 0.0005", type_of_var=real_t, default_r_val=0.001_dp)
461 9284 : CALL section_add_keyword(print_key, keyword)
462 9284 : CALL keyword_release(keyword)
463 :
464 9284 : END SUBROUTINE create_dos_section
465 :
466 : #else
467 : ! **************************************************************************************************
468 : !> \brief ...
469 : !> \param section ...
470 : ! **************************************************************************************************
471 : SUBROUTINE create_pwdft_section(section)
472 : TYPE(section_type), POINTER :: section
473 :
474 : CPASSERT(.NOT. ASSOCIATED(section))
475 :
476 : CALL section_create(section, __LOCATION__, name="PW_DFT", &
477 : description="This section contains all information to run an "// &
478 : "SIRIUS PW calculation.", &
479 : n_subsections=0, &
480 : repeats=.FALSE.)
481 :
482 : END SUBROUTINE create_pwdft_section
483 :
484 : #endif
485 :
486 : END MODULE input_cp2k_pwdft
|