Line data Source code
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 :
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, 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
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 9296 : 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 9296 : 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 9296 : "supported by libxc and Van der Waals corrections (libvdwxc).")
89 :
90 9296 : 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 9296 : lone_keyword_l_val=.TRUE.)
99 9296 : CALL section_add_keyword(section, keyword)
100 9296 : CALL keyword_release(keyword)
101 :
102 9296 : NULLIFY (subsection)
103 9296 : CALL create_sirius_section(subsection, 'control')
104 9296 : CALL section_add_subsection(section, subsection)
105 9296 : CALL section_release(subsection)
106 :
107 9296 : CALL create_sirius_section(subsection, 'parameters')
108 9296 : CALL section_add_subsection(section, subsection)
109 9296 : CALL section_release(subsection)
110 :
111 9296 : CALL create_sirius_section(subsection, 'settings')
112 9296 : CALL section_add_subsection(section, subsection)
113 9296 : CALL section_release(subsection)
114 :
115 9296 : CALL create_sirius_section(subsection, 'mixer')
116 9296 : CALL section_add_subsection(section, subsection)
117 9296 : CALL section_release(subsection)
118 :
119 9296 : CALL create_sirius_section(subsection, 'iterative_solver')
120 9296 : CALL section_add_subsection(section, subsection)
121 9296 : 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 9296 : CALL create_print_section(subsection)
149 9296 : CALL section_add_subsection(section, subsection)
150 9296 : CALL section_release(subsection)
151 :
152 9296 : 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 46480 : 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 46480 : 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 46480 : repeats=.FALSE.)
175 :
176 46480 : CALL fill_in_section(section, TRIM(ADJUSTL(section_name)))
177 46480 : END SUBROUTINE create_sirius_section
178 :
179 : ! **************************************************************************************************
180 : !> \brief ...
181 : !> \param section ...
182 : !> \param section_name ...
183 : ! **************************************************************************************************
184 46480 : 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 46480 : INTEGER, ALLOCATABLE, DIMENSION(:), TARGET :: enum_i_val, ivec
194 : INTEGER, TARGET :: dummy_i
195 : LOGICAL :: jump_dft_parameters, lvecl(1:16)
196 46480 : LOGICAL(4), ALLOCATABLE, DIMENSION(:), TARGET :: lvec
197 : LOGICAL(4), TARGET :: dummy_l
198 46480 : REAL(kind=dp), ALLOCATABLE, DIMENSION(:), TARGET :: rvec
199 : REAL(kind=dp), TARGET :: dummy_r
200 : TYPE(keyword_type), POINTER :: keyword
201 :
202 46480 : ALLOCATE (ivec(1:16))
203 46480 : ALLOCATE (rvec(1:16))
204 46480 : ALLOCATE (lvec(1:16))
205 46480 : ALLOCATE (enum_i_val(1:256))
206 46480 : jump_dft_parameters = .FALSE.
207 : #ifdef __LIBVDWXC
208 46480 : IF (section_name == "parameters") THEN
209 9296 : 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, &
213 : enum_i_vals=[SIRIUS_NO_VDW, SIRIUS_FUNC_VDWDF, SIRIUS_FUNC_VDWDF2, SIRIUS_FUNC_VDWDFCX], &
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 9296 : "FUNC_VDWDFCX"))
219 9296 : CALL section_add_keyword(section, keyword)
220 9296 : CALL keyword_release(keyword)
221 : END IF
222 : #endif
223 :
224 46480 : CALL sirius_option_get_section_length(section_name, length)
225 :
226 994672 : DO i = 1, length
227 948192 : NULLIFY (keyword)
228 948192 : name = ''
229 948192 : description = ''
230 948192 : 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 948192 : 4096)
242 :
243 : ! description and usage are ignored here
244 : ! it is a minor inconvenience from the api.
245 948192 : 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 1942864 : 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 241696 : SELECT CASE (ctype)
262 : CASE (SIRIUS_INTEGER_TYPE)
263 241696 : 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 241696 : default_i_val=dummy_i)
271 241696 : CALL section_add_keyword(section, keyword)
272 241696 : CALL keyword_release(keyword)
273 : CASE (SIRIUS_NUMBER_TYPE)
274 269584 : 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 269584 : default_r_val=dummy_r)
282 269584 : CALL section_add_keyword(section, keyword)
283 269584 : CALL keyword_release(keyword)
284 : CASE (SIRIUS_LOGICAL_TYPE)
285 223104 : dummy_l = .FALSE.
286 223104 : CALL sirius_option_get(section_name, name, ctype, C_LOC(dummy_l))
287 223104 : 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 74368 : 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 148736 : lone_keyword_l_val=.TRUE.)
305 : END IF
306 223104 : CALL section_add_keyword(section, keyword)
307 223104 : CALL keyword_release(keyword)
308 : CASE (SIRIUS_STRING_TYPE)
309 148736 : IF (enum_length >= 1) THEN
310 613536 : DO j = 1, enum_length
311 483392 : possible_values(j) = ''
312 483392 : CALL sirius_option_get(section_name, name, ctype, C_LOC(possible_values(j)), max_length=128, enum_idx=j)
313 483392 : enum_i_val(j) = j
314 613536 : possible_values(j) = TRIM(ADJUSTL(possible_values(j)))
315 : END DO
316 :
317 130144 : 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 130144 : 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 0 : 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 18592 : repeats=.FALSE.)
343 : END IF
344 148736 : CALL section_add_keyword(section, keyword)
345 148736 : CALL keyword_release(keyword)
346 : CASE (SIRIUS_INTEGER_ARRAY_TYPE)
347 37184 : CALL sirius_option_get(section_name, name, ctype, C_LOC(ivec(1)), max_length=16)
348 :
349 37184 : 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 0 : 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 37184 : default_i_vals=ivec(1:num_possible_values))
364 : END IF
365 37184 : CALL section_add_keyword(section, keyword)
366 37184 : CALL keyword_release(keyword)
367 : CASE (SIRIUS_LOGICAL_ARRAY_TYPE)
368 0 : CALL sirius_option_get(section_name, name, ctype, C_LOC(lvec(1)), max_length=16)
369 0 : DO j = 1, num_possible_values
370 0 : lvecl(j) = lvec(j)
371 : END DO
372 0 : 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 0 : 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 0 : n_var=-1)
389 : END IF
390 0 : CALL section_add_keyword(section, keyword)
391 0 : CALL keyword_release(keyword)
392 : CASE (SIRIUS_NUMBER_ARRAY_TYPE)
393 9296 : CALL sirius_option_get(section_name, name, ctype, C_LOC(rvec(1)), max_length=16)
394 :
395 9296 : 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 0 : 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 9296 : default_r_vals=rvec(1:num_possible_values))
412 : END IF
413 9296 : CALL section_add_keyword(section, keyword)
414 938896 : 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 46480 : DEALLOCATE (ivec)
425 46480 : DEALLOCATE (rvec)
426 46480 : DEALLOCATE (lvec)
427 46480 : DEALLOCATE (enum_i_val)
428 46480 : 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 9296 : SUBROUTINE create_print_section(section)
436 : TYPE(section_type), POINTER :: section
437 :
438 : TYPE(section_type), POINTER :: print_key
439 :
440 9296 : CPASSERT(.NOT. ASSOCIATED(section))
441 : CALL section_create(section, __LOCATION__, name="PRINT", &
442 : description="Section of possible print options in PW_DFT code.", &
443 9296 : n_keywords=0, n_subsections=1, repeats=.FALSE.)
444 :
445 9296 : NULLIFY (print_key)
446 9296 : CALL create_dos_section(print_key)
447 9296 : CALL section_add_subsection(section, print_key)
448 9296 : CALL section_release(print_key)
449 :
450 9296 : END SUBROUTINE create_print_section
451 :
452 : ! **************************************************************************************************
453 : !> \brief ...
454 : !> \param print_key ...
455 : ! **************************************************************************************************
456 9296 : SUBROUTINE create_dos_section(print_key)
457 :
458 : TYPE(section_type), POINTER :: print_key
459 :
460 : TYPE(keyword_type), POINTER :: keyword
461 :
462 9296 : 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 9296 : 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 9296 : lone_keyword_l_val=.TRUE.)
473 9296 : CALL section_add_keyword(print_key, keyword)
474 9296 : CALL keyword_release(keyword)
475 :
476 : CALL keyword_create(keyword, __LOCATION__, name="DELTA_E", &
477 : description="Histogramm energy spacing.", &
478 9296 : usage="DELTA_E 0.0005", type_of_var=real_t, default_r_val=0.001_dp)
479 9296 : CALL section_add_keyword(print_key, keyword)
480 9296 : CALL keyword_release(keyword)
481 :
482 9296 : 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 :
504 : END MODULE input_cp2k_pwdft
|