Line data Source code
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 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 8530 : 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 8530 : 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 8530 : "supported by libxc and Van der Waals corrections (libvdwxc).")
89 :
90 8530 : 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 8530 : lone_keyword_l_val=.TRUE.)
99 8530 : CALL section_add_keyword(section, keyword)
100 8530 : CALL keyword_release(keyword)
101 :
102 8530 : NULLIFY (subsection)
103 8530 : CALL create_sirius_section(subsection, 'control')
104 8530 : CALL section_add_subsection(section, subsection)
105 8530 : CALL section_release(subsection)
106 :
107 8530 : CALL create_sirius_section(subsection, 'parameters')
108 8530 : CALL section_add_subsection(section, subsection)
109 8530 : CALL section_release(subsection)
110 :
111 8530 : CALL create_sirius_section(subsection, 'settings')
112 8530 : CALL section_add_subsection(section, subsection)
113 8530 : CALL section_release(subsection)
114 :
115 8530 : CALL create_sirius_section(subsection, 'mixer')
116 8530 : CALL section_add_subsection(section, subsection)
117 8530 : CALL section_release(subsection)
118 :
119 8530 : CALL create_sirius_section(subsection, 'iterative_solver')
120 8530 : CALL section_add_subsection(section, subsection)
121 8530 : 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 8530 : CALL create_print_section(subsection)
132 8530 : CALL section_add_subsection(section, subsection)
133 8530 : CALL section_release(subsection)
134 :
135 8530 : 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 42650 : 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 0 : CPASSERT(.NOT. ASSOCIATED(section))
150 42650 : 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 42650 : repeats=.FALSE.)
158 :
159 42650 : CALL fill_in_section(section, TRIM(ADJUSTL(section_name)))
160 42650 : END SUBROUTINE create_sirius_section
161 :
162 : ! **************************************************************************************************
163 : !> \brief ...
164 : !> \param section ...
165 : !> \param section_name ...
166 : ! **************************************************************************************************
167 42650 : 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 42650 : INTEGER, ALLOCATABLE, DIMENSION(:), TARGET :: ivec
177 : INTEGER, TARGET :: dummy_i
178 : LOGICAL :: lvecl(1:16)
179 42650 : LOGICAL(4), ALLOCATABLE, DIMENSION(:), TARGET :: lvec
180 : LOGICAL(4), TARGET :: dummy_l
181 42650 : REAL(kind=dp), ALLOCATABLE, DIMENSION(:), TARGET :: rvec
182 : REAL(kind=dp), TARGET :: dummy_r
183 : TYPE(keyword_type), POINTER :: keyword
184 :
185 42650 : ALLOCATE (ivec(1:16))
186 42650 : ALLOCATE (rvec(1:16))
187 42650 : ALLOCATE (lvec(1:16))
188 :
189 : #ifdef __LIBVDWXC
190 42650 : IF (section_name == "parameters") THEN
191 8530 : 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, &
195 : enum_i_vals=(/SIRIUS_NO_VDW, SIRIUS_FUNC_VDWDF, SIRIUS_FUNC_VDWDF2, SIRIUS_FUNC_VDWDFCX/), &
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 8530 : "FUNC_VDWDFCX"))
201 8530 : CALL section_add_keyword(section, keyword)
202 8530 : CALL keyword_release(keyword)
203 : END IF
204 : #endif
205 :
206 42650 : CALL sirius_option_get_section_length(section_name, length)
207 :
208 904180 : DO i = 1, length
209 861530 : NULLIFY (keyword)
210 861530 : name = ''
211 861530 : description = ''
212 861530 : 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 861530 : 4096)
224 : ! description and usage are ignored here
225 : ! it is a minor inconvenience from the api.
226 :
227 861530 : 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 1765710 : 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 221780 : SELECT CASE (ctype)
236 : CASE (SIRIUS_INTEGER_TYPE)
237 221780 : 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 221780 : default_i_val=dummy_i)
245 221780 : CALL section_add_keyword(section, keyword)
246 221780 : CALL keyword_release(keyword)
247 : CASE (SIRIUS_NUMBER_TYPE)
248 238840 : 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 238840 : default_r_val=dummy_r)
256 238840 : CALL section_add_keyword(section, keyword)
257 238840 : CALL keyword_release(keyword)
258 : CASE (SIRIUS_LOGICAL_TYPE)
259 204720 : dummy_l = .FALSE.
260 204720 : CALL sirius_option_get(section_name, name, ctype, C_LOC(dummy_l))
261 204720 : 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 68240 : 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 136480 : lone_keyword_l_val=.TRUE.)
279 : END IF
280 204720 : CALL section_add_keyword(section, keyword)
281 204720 : CALL keyword_release(keyword)
282 : CASE (SIRIUS_STRING_TYPE)
283 136480 : IF (enum_length >= 1) THEN
284 562980 : DO j = 1, enum_length
285 443560 : possible_values(j) = ''
286 443560 : CALL sirius_option_get(section_name, name, ctype, C_LOC(possible_values(j)), max_length=128, enum_idx=j)
287 443560 : enum_i_val(j) = j
288 562980 : possible_values(j) = TRIM(ADJUSTL(possible_values(j)))
289 : END DO
290 :
291 119420 : 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 119420 : 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 0 : 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 17060 : repeats=.FALSE.)
317 : END IF
318 136480 : CALL section_add_keyword(section, keyword)
319 136480 : CALL keyword_release(keyword)
320 : CASE (SIRIUS_INTEGER_ARRAY_TYPE)
321 34120 : CALL sirius_option_get(section_name, name, ctype, C_LOC(ivec(1)), max_length=16)
322 :
323 34120 : 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 0 : 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 34120 : default_i_vals=ivec(1:num_possible_values))
338 : END IF
339 34120 : CALL section_add_keyword(section, keyword)
340 34120 : CALL keyword_release(keyword)
341 : CASE (SIRIUS_LOGICAL_ARRAY_TYPE)
342 0 : CALL sirius_option_get(section_name, name, ctype, C_LOC(lvec(1)), max_length=16)
343 0 : DO j = 1, num_possible_values
344 0 : lvecl(j) = lvec(j)
345 : END DO
346 0 : 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 0 : 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 0 : n_var=-1)
363 : END IF
364 0 : CALL section_add_keyword(section, keyword)
365 0 : CALL keyword_release(keyword)
366 : CASE (SIRIUS_NUMBER_ARRAY_TYPE)
367 8530 : CALL sirius_option_get(section_name, name, ctype, C_LOC(rvec(1)), max_length=16)
368 :
369 8530 : 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 0 : 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 8530 : default_r_vals=rvec(1:num_possible_values))
386 : END IF
387 8530 : CALL section_add_keyword(section, keyword)
388 853000 : CALL keyword_release(keyword)
389 : CASE default
390 : END SELECT
391 : END IF
392 : END DO
393 85300 : 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 8530 : SUBROUTINE create_print_section(section)
401 : TYPE(section_type), POINTER :: section
402 :
403 : TYPE(section_type), POINTER :: print_key
404 :
405 8530 : CPASSERT(.NOT. ASSOCIATED(section))
406 : CALL section_create(section, __LOCATION__, name="PRINT", &
407 : description="Section of possible print options in PW_DFT code.", &
408 8530 : n_keywords=0, n_subsections=1, repeats=.FALSE.)
409 :
410 8530 : NULLIFY (print_key)
411 8530 : CALL create_dos_section(print_key)
412 8530 : CALL section_add_subsection(section, print_key)
413 8530 : CALL section_release(print_key)
414 :
415 8530 : END SUBROUTINE create_print_section
416 :
417 : ! **************************************************************************************************
418 : !> \brief ...
419 : !> \param print_key ...
420 : ! **************************************************************************************************
421 8530 : SUBROUTINE create_dos_section(print_key)
422 :
423 : TYPE(section_type), POINTER :: print_key
424 :
425 : TYPE(keyword_type), POINTER :: keyword
426 :
427 8530 : 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 8530 : 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 8530 : lone_keyword_l_val=.TRUE.)
438 8530 : CALL section_add_keyword(print_key, keyword)
439 8530 : CALL keyword_release(keyword)
440 :
441 : CALL keyword_create(keyword, __LOCATION__, name="DELTA_E", &
442 : description="Histogramm energy spacing.", &
443 8530 : usage="DELTA_E 0.0005", type_of_var=real_t, default_r_val=0.001_dp)
444 8530 : CALL section_add_keyword(print_key, keyword)
445 8530 : CALL keyword_release(keyword)
446 :
447 8530 : 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 :
469 : END MODULE input_cp2k_pwdft
|