17 USE iso_c_binding,
ONLY: c_loc
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
47#include "./base/base_uses.f90"
52 LOGICAL,
PRIVATE,
PARAMETER :: debug_this_module = .true.
53 CHARACTER(len=*),
PARAMETER,
PRIVATE :: moduleN =
'input_cp2k_pwdft'
80 cpassert(.NOT.
ASSOCIATED(section))
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).")
92 name=
'ignore_convergence_failure', &
93 description=
"when set to true, calculation will continue irrespectively "// &
94 "of the convergence status of SIRIUS", &
97 default_l_val=.false., &
98 lone_keyword_l_val=.true.)
103 CALL create_sirius_section(subsection,
'control')
107 CALL create_sirius_section(subsection,
'parameters')
111 CALL create_sirius_section(subsection,
'settings')
115 CALL create_sirius_section(subsection,
'mixer')
119 CALL create_sirius_section(subsection,
'iterative_solver')
131 CALL create_print_section(subsection)
143 SUBROUTINE create_sirius_section(section, section_name)
145 CHARACTER(len=*),
INTENT(in) :: section_name
149 cpassert(.NOT.
ASSOCIATED(section))
150 CALL sirius_option_get_section_length(trim(adjustl(section_name)), length)
153 name=trim(adjustl(section_name)), &
154 description=trim(section_name)//
" section", &
159 CALL fill_in_section(section, trim(adjustl(section_name)))
160 END SUBROUTINE create_sirius_section
167 SUBROUTINE fill_in_section(section, section_name)
169 CHARACTER(len=*),
INTENT(in) :: section_name
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
185 ALLOCATE (ivec(1:16))
186 ALLOCATE (rvec(1:16))
187 ALLOCATE (lvec(1:16))
190 IF (section_name ==
"parameters")
THEN
192 CALL keyword_create(keyword, __location__, name=
"VDW_FUNCTIONAL", &
193 description=
"Select the Van der Walls functionals corrections type", &
196 enum_c_vals=
s2a(
"NONE",
"FUNC_VDWDF",
"FUNC_VDWDF2",
"FUNC_VDWDFCX"), &
197 enum_desc=
s2a(
"No VdW correction", &
206 CALL sirius_option_get_section_length(section_name, length)
213 CALL sirius_option_get_info(section_name, &
218 num_possible_values, &
227 name = trim(adjustl(name))
233 IF ((name /=
'xc_functionals') .AND. (name /=
'memory_usage') .AND. (name /=
'vk'))
THEN
236 CASE (sirius_integer_type)
237 CALL sirius_option_get(section_name, name, ctype, c_loc(dummy_i))
240 description=trim(adjustl(description)), &
244 default_i_val=dummy_i)
247 CASE (sirius_number_type)
248 CALL sirius_option_get(section_name, name, ctype, c_loc(dummy_r))
251 description=trim(adjustl(description)), &
255 default_r_val=dummy_r)
258 CASE (sirius_logical_type)
260 CALL sirius_option_get(section_name, name, ctype, c_loc(dummy_l))
264 description=trim(adjustl(description)), &
268 default_l_val=.true., &
269 lone_keyword_l_val=.true.)
273 description=trim(adjustl(description)), &
277 default_l_val=.false., &
278 lone_keyword_l_val=.true.)
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)
288 possible_values(j) = trim(adjustl(possible_values(j)))
291 IF (enum_length > 1)
THEN
294 description=trim(adjustl(description)), &
297 enum_i_vals=enum_i_val(1:enum_length), &
298 enum_c_vals=possible_values(1:enum_length), &
303 description=trim(adjustl(description)), &
306 default_c_val=possible_values(1), &
312 description=trim(adjustl(description)), &
320 CASE (sirius_integer_array_type)
321 CALL sirius_option_get(section_name, name, ctype, c_loc(ivec(1)), max_length=16)
323 IF (num_possible_values .EQ. 0)
THEN
326 description=trim(adjustl(description)), &
333 description=trim(adjustl(description)), &
336 n_var=num_possible_values, &
337 default_i_vals=ivec(1:num_possible_values))
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
346 IF (num_possible_values > 0)
THEN
349 description=trim(adjustl(description)), &
353 n_var=num_possible_values, &
354 default_l_vals=lvecl(1:num_possible_values))
358 description=trim(adjustl(description)), &
366 CASE (sirius_number_array_type)
367 CALL sirius_option_get(section_name, name, ctype, c_loc(rvec(1)), max_length=16)
369 IF (num_possible_values .EQ. 0)
THEN
372 description=trim(adjustl(description)), &
380 description=trim(adjustl(description)), &
384 n_var=num_possible_values, &
385 default_r_vals=rvec(1:num_possible_values))
393 END SUBROUTINE fill_in_section
400 SUBROUTINE create_print_section(section)
405 cpassert(.NOT.
ASSOCIATED(section))
407 description=
"Section of possible print options in PW_DFT code.", &
408 n_keywords=0, n_subsections=1, repeats=.false.)
411 CALL create_dos_section(print_key)
415 END SUBROUTINE create_print_section
421 SUBROUTINE create_dos_section(print_key)
430 description=
"Print Density of States (DOS) (only available states from SCF)", &
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.)
442 description=
"Histogramm energy spacing.", &
443 usage=
"DELTA_E 0.0005", type_of_var=
real_t, default_r_val=0.001_dp)
447 END SUBROUTINE create_dos_section
457 cpassert(.NOT.
ASSOCIATED(section))
460 description=
"This section contains all information to run an "// &
461 "SIRIUS PW calculation.", &
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
Defines the basic variable types.
integer, parameter, public dp
Utilities for string manipulations.