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 builds the input structure for the ATOM module
10 : !> \author jgh
11 : ! **************************************************************************************************
12 : MODULE input_cp2k_atom
13 : USE cp_output_handling, ONLY: cp_print_key_section_create,&
14 : debug_print_level,&
15 : high_print_level,&
16 : medium_print_level,&
17 : silent_print_level
18 : USE input_constants, ONLY: &
19 : atom_basis_run, atom_energy_run, atom_no_run, atom_pseudo_run, barrier_conf, &
20 : contracted_gto, do_analytic, do_dkh0_atom, do_dkh1_atom, do_dkh2_atom, do_dkh3_atom, &
21 : do_gapw_gcs, do_gapw_gct, do_gapw_log, do_nonrel_atom, do_numeric, do_rhf_atom, &
22 : do_rks_atom, do_rohf_atom, do_sczoramp_atom, do_semi_analytic, do_uhf_atom, do_uks_atom, &
23 : do_zoramp_atom, ecp_pseudo, gaussian, geometrical_gto, gth_pseudo, no_conf, no_pseudo, &
24 : numerical, poly_conf, sgp_pseudo, slater, upf_pseudo
25 : USE input_cp2k_xc, ONLY: create_xc_section
26 : USE input_keyword_types, ONLY: keyword_create,&
27 : keyword_release,&
28 : keyword_type
29 : USE input_section_types, ONLY: section_add_keyword,&
30 : section_add_subsection,&
31 : section_create,&
32 : section_release,&
33 : section_type
34 : USE input_val_types, ONLY: char_t,&
35 : integer_t,&
36 : lchar_t,&
37 : logical_t,&
38 : real_t
39 : USE kinds, ONLY: dp
40 : USE string_utilities, ONLY: s2a
41 : #include "./base/base_uses.f90"
42 :
43 : IMPLICIT NONE
44 : PRIVATE
45 :
46 : LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .TRUE.
47 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_atom'
48 :
49 : PUBLIC :: create_atom_section
50 :
51 : ! **************************************************************************************************
52 :
53 : CONTAINS
54 :
55 : ! **************************************************************************************************
56 : !> \brief Creates the input section for the atom code
57 : !> \param section the section to create
58 : !> \author jgh
59 : ! **************************************************************************************************
60 9296 : SUBROUTINE create_atom_section(section)
61 : TYPE(section_type), POINTER :: section
62 :
63 : TYPE(keyword_type), POINTER :: keyword
64 : TYPE(section_type), POINTER :: subsection
65 :
66 9296 : CPASSERT(.NOT. ASSOCIATED(section))
67 : CALL section_create(section, __LOCATION__, name="ATOM", &
68 : description="Section handling input for atomic calculations.", &
69 9296 : n_keywords=1, n_subsections=1, repeats=.FALSE.)
70 9296 : NULLIFY (keyword, subsection)
71 :
72 : CALL keyword_create(keyword, __LOCATION__, name="ATOMIC_NUMBER", &
73 : description="Specify the atomic number", &
74 9296 : default_i_val=1)
75 9296 : CALL section_add_keyword(section, keyword)
76 9296 : CALL keyword_release(keyword)
77 :
78 : CALL keyword_create(keyword, __LOCATION__, name="ELEMENT", &
79 : description="Specify the element to be calculated", &
80 : usage="ELEMENT char", n_var=1, type_of_var=char_t, &
81 9296 : default_c_val="H")
82 9296 : CALL section_add_keyword(section, keyword)
83 9296 : CALL keyword_release(keyword)
84 :
85 : CALL keyword_create(keyword, __LOCATION__, name="RUN_TYPE", &
86 : description="Type of run that you want to perform "// &
87 : "[ENERGY,BASIS_OPTIMIZATION,PSEUDOPOTENTIAL_OPTIMIZATION,,...] ", &
88 : usage="RUN_TYPE (NONE|ENERGY|BASIS_OPTIMIZATION|PSEUDOPOTENTIAL_OPTIMIZATION)", &
89 : default_i_val=atom_energy_run, &
90 : enum_c_vals=s2a("NONE", "ENERGY", "BASIS_OPTIMIZATION", "PSEUDOPOTENTIAL_OPTIMIZATION"), &
91 : enum_i_vals=[atom_no_run, atom_energy_run, atom_basis_run, atom_pseudo_run], &
92 : enum_desc=s2a("Perform no run", &
93 : "Perform energy optimization", &
94 : "Perform basis optimization", &
95 9296 : "Perform pseudopotential optimization"))
96 9296 : CALL section_add_keyword(section, keyword)
97 9296 : CALL keyword_release(keyword)
98 :
99 : CALL keyword_create(keyword, __LOCATION__, name="COULOMB_INTEGRALS", &
100 : description="Method to calculate Coulomb integrals", &
101 : usage="COULOMB_INTEGRALS (ANALYTIC|SEMI_ANALYTIC|NUMERIC)", &
102 : default_i_val=do_numeric, &
103 : enum_c_vals=["ANALYTIC ", &
104 : "SEMI_ANALYTIC ", &
105 : "NUMERIC "], &
106 : enum_i_vals=[do_analytic, do_semi_analytic, do_numeric], &
107 : enum_desc=s2a("Use analytical method", &
108 : "Use semi-analytical method", &
109 37184 : "Use numerical method"))
110 9296 : CALL section_add_keyword(section, keyword)
111 9296 : CALL keyword_release(keyword)
112 :
113 : CALL keyword_create(keyword, __LOCATION__, name="EXCHANGE_INTEGRALS", &
114 : description="Method to calculate Exchange integrals", &
115 : usage="EXCHANGE_INTEGRALS (ANALYTIC|SEMI_ANALYTIC|NUMERIC)", &
116 : default_i_val=do_numeric, &
117 : enum_c_vals=["ANALYTIC ", &
118 : "SEMI_ANALYTIC ", &
119 : "NUMERIC "], &
120 : enum_i_vals=[do_analytic, do_semi_analytic, do_numeric], &
121 : enum_desc=s2a("Use analytical method. Not available for longrange Hartree-Fock", &
122 : "Use semi-analytical method", &
123 37184 : "Use numerical method"))
124 9296 : CALL section_add_keyword(section, keyword)
125 9296 : CALL keyword_release(keyword)
126 :
127 : CALL keyword_create(keyword, __LOCATION__, name="CORE", &
128 : description="Specifies the core electrons for a pseudopotential", &
129 : usage="CORE 1s2 ... or CORE [Ne] or CORE none for 0 electron cores", repeats=.FALSE., &
130 9296 : n_var=-1, type_of_var=char_t)
131 9296 : CALL section_add_keyword(section, keyword)
132 9296 : CALL keyword_release(keyword)
133 :
134 : CALL keyword_create(keyword, __LOCATION__, name="ELECTRON_CONFIGURATION", &
135 : description="Specifies the electron configuration. "// &
136 : "Optional the multiplicity (m) and a core state [XX] can be declared", &
137 : usage="ELECTRON_CONFIGURATION (1) [Ne] 3s2 ... ", repeats=.TRUE., &
138 9296 : n_var=-1, type_of_var=char_t)
139 9296 : CALL section_add_keyword(section, keyword)
140 9296 : CALL keyword_release(keyword)
141 :
142 : CALL keyword_create(keyword, __LOCATION__, name="MAX_ANGULAR_MOMENTUM", &
143 : description="Specifies the largest angular momentum calculated [0-3]", &
144 : usage="MAX_ANGULAR_MOMENTUM 3", repeats=.FALSE., &
145 9296 : default_i_val=3)
146 9296 : CALL section_add_keyword(section, keyword)
147 9296 : CALL keyword_release(keyword)
148 :
149 : CALL keyword_create(keyword, __LOCATION__, name="CALCULATE_STATES", &
150 : description="Specifies the number of states calculated per l value", &
151 : usage="CALCULATE_STATES 5 5 5 3 ", repeats=.FALSE., &
152 9296 : default_i_val=0, n_var=-1, type_of_var=integer_t)
153 9296 : CALL section_add_keyword(section, keyword)
154 9296 : CALL keyword_release(keyword)
155 :
156 : CALL keyword_create(keyword, __LOCATION__, name="USE_GAUSS_HERMITE", &
157 : description="Whether a Gauss-Hermite grid is to be used for the numerical integration of "// &
158 : "longrange exchange integrals", &
159 : usage="USE_GAUSS_HERMITE TRUE", repeats=.FALSE., &
160 9296 : default_l_val=.FALSE.)
161 9296 : CALL section_add_keyword(section, keyword)
162 9296 : CALL keyword_release(keyword)
163 :
164 : CALL keyword_create(keyword, __LOCATION__, name="GRID_POINTS_GH", &
165 : description="Number of grid points for Gauss-Hermite grid", &
166 : usage="GRID_POINTS_GH 100", repeats=.FALSE., &
167 9296 : default_i_val=100)
168 9296 : CALL section_add_keyword(section, keyword)
169 9296 : CALL keyword_release(keyword)
170 :
171 9296 : CALL create_atom_reference_section(subsection)
172 9296 : CALL section_add_subsection(section, subsection)
173 9296 : CALL section_release(subsection)
174 :
175 9296 : CALL create_atom_print_section(subsection)
176 9296 : CALL section_add_subsection(section, subsection)
177 9296 : CALL section_release(subsection)
178 :
179 9296 : CALL create_atom_aebasis_section(subsection)
180 9296 : CALL section_add_subsection(section, subsection)
181 9296 : CALL section_release(subsection)
182 :
183 9296 : CALL create_atom_ppbasis_section(subsection)
184 9296 : CALL section_add_subsection(section, subsection)
185 9296 : CALL section_release(subsection)
186 :
187 9296 : CALL create_atom_method_section(subsection)
188 9296 : CALL section_add_subsection(section, subsection)
189 9296 : CALL section_release(subsection)
190 :
191 9296 : CALL create_optimization_section(subsection)
192 9296 : CALL section_add_subsection(section, subsection)
193 9296 : CALL section_release(subsection)
194 :
195 9296 : CALL create_potential_section(subsection)
196 9296 : CALL section_add_subsection(section, subsection)
197 9296 : CALL section_release(subsection)
198 :
199 9296 : CALL create_powell_section(subsection)
200 9296 : CALL section_add_subsection(section, subsection)
201 9296 : CALL section_release(subsection)
202 :
203 9296 : END SUBROUTINE create_atom_section
204 :
205 : ! **************************************************************************************************
206 : !> \brief Create the atom section for reference method
207 : !> \param section the section to create
208 : !> \author jgh
209 : ! **************************************************************************************************
210 9296 : SUBROUTINE create_atom_reference_section(section)
211 : TYPE(section_type), POINTER :: section
212 :
213 : TYPE(keyword_type), POINTER :: keyword
214 : TYPE(section_type), POINTER :: subsection
215 :
216 9296 : CPASSERT(.NOT. ASSOCIATED(section))
217 : CALL section_create(section, __LOCATION__, name="REFERENCE", &
218 : description="Section to specify a reference method for PP optimization.", &
219 9296 : n_keywords=1, n_subsections=1, repeats=.FALSE.)
220 :
221 9296 : NULLIFY (keyword)
222 :
223 : CALL keyword_create(keyword, __LOCATION__, name="METHOD", &
224 : description="METHOD to be used as reference: [AE|PP] ", &
225 : usage="METHOD PP", &
226 9296 : type_of_var=char_t, default_c_val="AE", n_var=-1)
227 9296 : CALL section_add_keyword(section, keyword)
228 9296 : CALL keyword_release(keyword)
229 :
230 : CALL keyword_create(keyword, __LOCATION__, name="CORE", &
231 : description="Specifies the core electrons for a pseudopotential", &
232 : usage="CORE 1s2 ... or CORE [Ne] or CORE none for 0 electron cores", repeats=.FALSE., &
233 9296 : n_var=-1, type_of_var=char_t)
234 9296 : CALL section_add_keyword(section, keyword)
235 9296 : CALL keyword_release(keyword)
236 :
237 9296 : NULLIFY (subsection)
238 9296 : CALL create_potential_section(subsection)
239 9296 : CALL section_add_subsection(section, subsection)
240 9296 : CALL section_release(subsection)
241 :
242 9296 : END SUBROUTINE create_atom_reference_section
243 :
244 : ! **************************************************************************************************
245 : !> \brief Create the print atom section
246 : !> \param section the section to create
247 : !> \author jgh
248 : ! **************************************************************************************************
249 9296 : SUBROUTINE create_atom_print_section(section)
250 : TYPE(section_type), POINTER :: section
251 :
252 : TYPE(keyword_type), POINTER :: keyword
253 : TYPE(section_type), POINTER :: print_key, subsection
254 :
255 9296 : CPASSERT(.NOT. ASSOCIATED(section))
256 : CALL section_create(section, __LOCATION__, name="print", &
257 : description="Section of possible print options specific of the ATOM code.", &
258 9296 : n_keywords=0, n_subsections=1, repeats=.FALSE.)
259 :
260 9296 : NULLIFY (print_key, keyword)
261 :
262 : ! Print key section
263 : CALL cp_print_key_section_create(print_key, __LOCATION__, "PROGRAM_BANNER", &
264 : description="Controls the printing of the banner of the ATOM program", &
265 9296 : print_level=silent_print_level, filename="__STD_OUT__")
266 9296 : CALL section_add_subsection(section, print_key)
267 9296 : CALL section_release(print_key)
268 :
269 : ! Print key section
270 : CALL cp_print_key_section_create(print_key, __LOCATION__, "METHOD_INFO", &
271 : description="Controls the printing of method information", &
272 9296 : print_level=medium_print_level, filename="__STD_OUT__")
273 9296 : CALL section_add_subsection(section, print_key)
274 9296 : CALL section_release(print_key)
275 :
276 : ! Print key section
277 : CALL cp_print_key_section_create(print_key, __LOCATION__, "BASIS_SET", &
278 : description="Controls the printing of the basis sets", &
279 9296 : print_level=high_print_level, filename="__STD_OUT__")
280 9296 : CALL section_add_subsection(section, print_key)
281 9296 : CALL section_release(print_key)
282 :
283 : ! Print key section
284 : CALL cp_print_key_section_create(print_key, __LOCATION__, "POTENTIAL", &
285 : description="Controls the printing of the potentials", &
286 9296 : print_level=high_print_level, filename="__STD_OUT__")
287 9296 : CALL section_add_subsection(section, print_key)
288 9296 : CALL section_release(print_key)
289 :
290 : ! Print key section
291 : CALL cp_print_key_section_create( &
292 : print_key, __LOCATION__, "FIT_DENSITY", &
293 : description="Fit the total electronic density to a linear combination of Gaussian functions", &
294 9296 : print_level=high_print_level, filename="__STD_OUT__")
295 : CALL keyword_create(keyword, __LOCATION__, name="NUM_GTO", &
296 : description="Number of Gaussian type functions for density fit", &
297 : usage="NUM_GTO integer ", type_of_var=integer_t, &
298 9296 : default_i_val=40)
299 9296 : CALL section_add_keyword(print_key, keyword)
300 9296 : CALL keyword_release(keyword)
301 9296 : CALL section_add_subsection(section, print_key)
302 9296 : CALL section_release(print_key)
303 :
304 : ! Print key section
305 : CALL cp_print_key_section_create(print_key, __LOCATION__, "FIT_KGPOT", &
306 : description="Fit an approximation to the non-additive"// &
307 : " kinetic energy potential used in KG", &
308 9296 : print_level=high_print_level, filename="__STD_OUT__")
309 : CALL keyword_create(keyword, __LOCATION__, name="NUM_GAUSSIAN", &
310 : description="Number of Gaussian terms for the fit", &
311 : usage="NUM_GAUSSIAN integer ", type_of_var=integer_t, &
312 9296 : default_i_val=1)
313 9296 : CALL section_add_keyword(print_key, keyword)
314 9296 : CALL keyword_release(keyword)
315 : CALL keyword_create(keyword, __LOCATION__, name="NUM_POLYNOM", &
316 : description="Number of terms in the polynomial expansion", &
317 : usage="NUM_POLYNOM integer ", type_of_var=integer_t, &
318 9296 : default_i_val=4)
319 9296 : CALL section_add_keyword(print_key, keyword)
320 9296 : CALL keyword_release(keyword)
321 9296 : CALL section_add_subsection(section, print_key)
322 9296 : CALL section_release(print_key)
323 :
324 : ! Print key section
325 : CALL cp_print_key_section_create(print_key, __LOCATION__, "RESPONSE_BASIS", &
326 : description="Calculate a response basis set contraction scheme", &
327 9296 : print_level=high_print_level, filename="__STD_OUT__")
328 : CALL keyword_create(keyword, __LOCATION__, name="DELTA_CHARGE", &
329 : description="Variation of charge used in finite difference calculation", &
330 : usage="DELTA_CHARGE real ", type_of_var=real_t, &
331 9296 : default_r_val=0.05_dp)
332 9296 : CALL section_add_keyword(print_key, keyword)
333 9296 : CALL keyword_release(keyword)
334 : CALL keyword_create(keyword, __LOCATION__, name="DERIVATIVES", &
335 : description="Number of wavefunction derivatives to calculate", &
336 : usage="DERIVATIVES integer ", type_of_var=integer_t, &
337 9296 : default_i_val=2)
338 9296 : CALL section_add_keyword(print_key, keyword)
339 9296 : CALL keyword_release(keyword)
340 9296 : CALL section_add_subsection(section, print_key)
341 9296 : CALL section_release(print_key)
342 :
343 : ! Print key section
344 : CALL cp_print_key_section_create(print_key, __LOCATION__, "GEOMETRICAL_RESPONSE_BASIS", &
345 : description="Calculate a response basis set based on a set of geometrical exponents", &
346 9296 : print_level=high_print_level, filename="__STD_OUT__")
347 : !
348 : CALL keyword_create(keyword, __LOCATION__, name="DELTA_CHARGE", &
349 : description="Variation of charge used in finite difference calculation", &
350 : usage="DELTA_CHARGE real ", type_of_var=real_t, &
351 9296 : default_r_val=0.05_dp)
352 9296 : CALL section_add_keyword(print_key, keyword)
353 9296 : CALL keyword_release(keyword)
354 : !
355 : CALL keyword_create(keyword, __LOCATION__, name="DERIVATIVES", &
356 : description="Number of wavefunction derivatives to calculate", &
357 : usage="DERIVATIVES integer ", type_of_var=integer_t, &
358 9296 : default_i_val=3)
359 9296 : CALL section_add_keyword(print_key, keyword)
360 9296 : CALL keyword_release(keyword)
361 : !
362 : CALL keyword_create(keyword, __LOCATION__, name="QUADRATURE", &
363 : description="Algorithm to construct the atomic radial grids", &
364 : usage="QUADRATURE (GC_SIMPLE|GC_TRANSFORMED|GC_LOG)", &
365 : enum_c_vals=s2a("GC_SIMPLE", "GC_TRANSFORMED", "GC_LOG"), &
366 : enum_i_vals=[do_gapw_gcs, do_gapw_gct, do_gapw_log], &
367 : enum_desc=s2a("Gauss-Chebyshev quadrature", &
368 : "Transformed Gauss-Chebyshev quadrature", &
369 : "Logarithmic transformed Gauss-Chebyshev quadrature"), &
370 9296 : default_i_val=do_gapw_log)
371 9296 : CALL section_add_keyword(print_key, keyword)
372 9296 : CALL keyword_release(keyword)
373 : !
374 : CALL keyword_create(keyword, __LOCATION__, name="GRID_POINTS", &
375 : description="Number of radial grid points", &
376 : usage="GRID_POINTS integer", &
377 9296 : default_i_val=400)
378 9296 : CALL section_add_keyword(print_key, keyword)
379 9296 : CALL keyword_release(keyword)
380 : !
381 : CALL keyword_create(keyword, __LOCATION__, name="NUM_GTO_CORE", &
382 : description="Number of Gaussian type functions for s, p, d, ... "// &
383 : "for the main body of the basis", &
384 : usage="NUM_GTO_CORE 6 ", n_var=1, type_of_var=integer_t, &
385 9296 : default_i_val=-1)
386 9296 : CALL section_add_keyword(print_key, keyword)
387 9296 : CALL keyword_release(keyword)
388 : CALL keyword_create(keyword, __LOCATION__, name="NUM_GTO_EXTENDED", &
389 : description="Number of Gaussian type functions for s, p, d, ... "// &
390 : "for the extension set", &
391 : usage="NUM_GTO_EXTENDED 4 ", n_var=1, type_of_var=integer_t, &
392 9296 : default_i_val=-1)
393 9296 : CALL section_add_keyword(print_key, keyword)
394 9296 : CALL keyword_release(keyword)
395 : CALL keyword_create(keyword, __LOCATION__, name="NUM_GTO_POLARIZATION", &
396 : description="Number of Gaussian type functions for the polarization set", &
397 : usage="NUM_GTO_POLARIZATION 4 ", n_var=1, type_of_var=integer_t, &
398 9296 : default_i_val=-1)
399 9296 : CALL section_add_keyword(print_key, keyword)
400 9296 : CALL keyword_release(keyword)
401 : CALL keyword_create(keyword, __LOCATION__, name="EXTENSION_BASIS", &
402 : description="Number of basis functions for s, p, d, ... "// &
403 : "for the extension set", &
404 : usage="EXTENSION_BASIS 4 3 2 1 ", n_var=-1, type_of_var=integer_t, &
405 9296 : default_i_val=-1)
406 9296 : CALL section_add_keyword(print_key, keyword)
407 9296 : CALL keyword_release(keyword)
408 : CALL keyword_create(keyword, __LOCATION__, name="GEOMETRICAL_FACTOR", &
409 : description="Geometrical basis: factor C in a*C^k (initial value for optimization)", &
410 : usage="GEOMETRICAL_FACTOR real", &
411 9296 : default_r_val=2.3_dp)
412 9296 : CALL section_add_keyword(print_key, keyword)
413 9296 : CALL keyword_release(keyword)
414 : CALL keyword_create(keyword, __LOCATION__, name="GEO_START_VALUE", &
415 : description="Geometrical basis: starting value a in a*C^k (initial value for optimization)", &
416 : usage="GEO_START_VALUE real", &
417 9296 : default_r_val=0.06_dp)
418 9296 : CALL section_add_keyword(print_key, keyword)
419 9296 : CALL keyword_release(keyword)
420 : CALL keyword_create(keyword, __LOCATION__, name="CONFINEMENT", &
421 : description="Onset value of barrier confinement potential [Bohr]", &
422 : usage="CONFINEMENT real", &
423 9296 : default_r_val=8.00_dp)
424 9296 : CALL section_add_keyword(print_key, keyword)
425 9296 : CALL keyword_release(keyword)
426 : CALL keyword_create(keyword, __LOCATION__, name="NAME_BODY", &
427 : description="Specifies the body of the basis set name ", &
428 : usage="NAME_BODY <char>", &
429 9296 : type_of_var=char_t, default_c_val="GRB", n_var=-1)
430 9296 : CALL section_add_keyword(print_key, keyword)
431 9296 : CALL keyword_release(keyword)
432 : !
433 9296 : CALL section_add_subsection(section, print_key)
434 9296 : CALL section_release(print_key)
435 :
436 : ! Print key section
437 : CALL cp_print_key_section_create(print_key, __LOCATION__, "SCF_INFO", &
438 : description="Controls the printing of SCF information", &
439 9296 : print_level=medium_print_level, filename="__STD_OUT__")
440 9296 : CALL section_add_subsection(section, print_key)
441 9296 : CALL section_release(print_key)
442 :
443 : ! Print key section
444 : CALL cp_print_key_section_create(print_key, __LOCATION__, "ORBITALS", &
445 : description="Controls the printing of the optimized orbitals information", &
446 9296 : print_level=high_print_level, filename="__STD_OUT__")
447 : CALL keyword_create(keyword, __LOCATION__, name="XMGRACE", &
448 : description="Output orbitals in Xmgrace format to files.", &
449 : usage="XMGRACE <logical>", &
450 : type_of_var=logical_t, &
451 : default_l_val=.FALSE., &
452 9296 : lone_keyword_l_val=.TRUE.)
453 9296 : CALL section_add_keyword(print_key, keyword)
454 9296 : CALL keyword_release(keyword)
455 9296 : CALL section_add_subsection(section, print_key)
456 9296 : CALL section_release(print_key)
457 :
458 : ! Print key section
459 : CALL cp_print_key_section_create(print_key, __LOCATION__, "ANALYZE_BASIS", &
460 : description="Calculates some basis set analysis data", &
461 9296 : print_level=high_print_level, filename="__STD_OUT__")
462 : CALL keyword_create(keyword, __LOCATION__, name="OVERLAP_CONDITION_NUMBER", &
463 : description="Condition number of the basis set overlap matrix calculated for a cubic crystal", &
464 9296 : usage="OVERLAP_CONDITION_NUMBER <logical>", type_of_var=logical_t, default_l_val=.FALSE.)
465 9296 : CALL section_add_keyword(print_key, keyword)
466 9296 : CALL keyword_release(keyword)
467 : CALL keyword_create(keyword, __LOCATION__, name="COMPLETENESS", &
468 : description="Calculate a completeness estimate for the basis set.", &
469 9296 : usage="COMPLETENESS <logical>", type_of_var=logical_t, default_l_val=.FALSE.)
470 9296 : CALL section_add_keyword(print_key, keyword)
471 9296 : CALL keyword_release(keyword)
472 9296 : CALL section_add_subsection(section, print_key)
473 9296 : CALL section_release(print_key)
474 :
475 : ! Print key section
476 : CALL cp_print_key_section_create(print_key, __LOCATION__, "FIT_PSEUDO", &
477 : description="Controls the printing of FIT PSEUDO task", &
478 9296 : print_level=medium_print_level, filename="__STD_OUT__")
479 9296 : CALL section_add_subsection(section, print_key)
480 9296 : CALL section_release(print_key)
481 :
482 : ! Print key section
483 : CALL cp_print_key_section_create(print_key, __LOCATION__, "FIT_BASIS", &
484 : description="Controls the printing of FIT BASIS task", &
485 9296 : print_level=medium_print_level, filename="__STD_OUT__")
486 9296 : CALL section_add_subsection(section, print_key)
487 9296 : CALL section_release(print_key)
488 :
489 : ! Print key section
490 : CALL cp_print_key_section_create(print_key, __LOCATION__, "UPF_FILE", &
491 : description="Write GTH pseudopotential in UPF format", &
492 9296 : print_level=high_print_level, filename="__STD_OUT__")
493 9296 : CALL section_add_subsection(section, print_key)
494 9296 : CALL section_release(print_key)
495 :
496 : ! Print key section
497 : CALL cp_print_key_section_create(print_key, __LOCATION__, "SEPARABLE_GAUSSIAN_PSEUDO", &
498 : description="Creates a representation of the pseudopotential in separable "// &
499 : "form using Gaussian functions.", &
500 9296 : print_level=debug_print_level, filename="__STD_OUT__")
501 9296 : CALL section_add_subsection(section, print_key)
502 9296 : CALL section_release(print_key)
503 :
504 : ! Print key section: ADMM Analysis
505 : CALL cp_print_key_section_create(print_key, __LOCATION__, "ADMM", &
506 : description="Analysis of ADMM approximation to exact exchange", &
507 9296 : print_level=high_print_level, filename="__STD_OUT__")
508 :
509 9296 : NULLIFY (subsection)
510 : CALL section_create(subsection, __LOCATION__, name="ADMM_BASIS", &
511 : description="Section of basis set information for ADMM calculations.", &
512 9296 : n_keywords=0, n_subsections=0, repeats=.FALSE.)
513 9296 : CALL atom_basis_section(subsection)
514 9296 : CALL section_add_subsection(print_key, subsection)
515 9296 : CALL section_release(subsection)
516 9296 : CALL section_add_subsection(section, print_key)
517 9296 : CALL section_release(print_key)
518 :
519 9296 : END SUBROUTINE create_atom_print_section
520 :
521 : ! **************************************************************************************************
522 : !> \brief Create the all-electron basis section
523 : !> \param section the section to create
524 : !> \author jgh
525 : ! **************************************************************************************************
526 9296 : SUBROUTINE create_atom_aebasis_section(section)
527 : TYPE(section_type), POINTER :: section
528 :
529 9296 : CPASSERT(.NOT. ASSOCIATED(section))
530 : CALL section_create(section, __LOCATION__, name="AE_BASIS", &
531 : description="Section of basis set information for all-electron calculations.", &
532 9296 : n_keywords=0, n_subsections=0, repeats=.FALSE.)
533 :
534 9296 : CALL atom_basis_section(section)
535 :
536 9296 : END SUBROUTINE create_atom_aebasis_section
537 :
538 : ! **************************************************************************************************
539 : !> \brief Create the pseudopotential basis section
540 : !> \param section the section to create
541 : !> \author jgh
542 : ! **************************************************************************************************
543 9296 : SUBROUTINE create_atom_ppbasis_section(section)
544 : TYPE(section_type), POINTER :: section
545 :
546 9296 : CPASSERT(.NOT. ASSOCIATED(section))
547 : CALL section_create(section, __LOCATION__, name="PP_BASIS", &
548 : description="Section of basis set information for pseudopotential calculations.", &
549 9296 : n_keywords=0, n_subsections=0, repeats=.FALSE.)
550 :
551 9296 : CALL atom_basis_section(section)
552 :
553 9296 : END SUBROUTINE create_atom_ppbasis_section
554 :
555 : ! **************************************************************************************************
556 : !> \brief Keywords in the atom basis section
557 : !> \param section the section to fill
558 : !> \author jgh
559 : ! **************************************************************************************************
560 27888 : SUBROUTINE atom_basis_section(section)
561 : TYPE(section_type), POINTER :: section
562 :
563 : TYPE(keyword_type), POINTER :: keyword
564 : TYPE(section_type), POINTER :: subsection
565 :
566 27888 : CPASSERT(ASSOCIATED(section))
567 27888 : NULLIFY (keyword)
568 :
569 : CALL keyword_create(keyword, __LOCATION__, name="BASIS_TYPE", &
570 : description="Basis set type", &
571 : usage="BASIS_TYPE (GAUSSIAN|GEOMETRICAL_GTO|CONTRACTED_GTO|SLATER|NUMERICAL)", &
572 : default_i_val=gaussian, &
573 : enum_c_vals=["GAUSSIAN ", &
574 : "GEOMETRICAL_GTO ", &
575 : "CONTRACTED_GTO ", &
576 : "SLATER ", &
577 : "NUMERICAL "], &
578 : enum_i_vals=[gaussian, geometrical_gto, contracted_gto, slater, numerical], &
579 : enum_desc=s2a("Gaussian type orbitals", &
580 : "Geometrical Gaussian type orbitals", &
581 : "Contracted Gaussian type orbitals", &
582 : "Slater-type orbitals", &
583 167328 : "Numerical basis type"))
584 27888 : CALL section_add_keyword(section, keyword)
585 27888 : CALL keyword_release(keyword)
586 :
587 : CALL keyword_create(keyword, __LOCATION__, name="NUM_GTO", &
588 : description="Number of Gaussian type functions for s, p, d, ...", &
589 : usage="NUM_GTO 5 5 5 ", n_var=-1, type_of_var=integer_t, &
590 27888 : default_i_val=-1)
591 27888 : CALL section_add_keyword(section, keyword)
592 27888 : CALL keyword_release(keyword)
593 :
594 : CALL keyword_create(keyword, __LOCATION__, name="NUM_SLATER", &
595 : description="Number of Slater type functions for s, p, d, ...", &
596 : usage="NUM_SLATER 5 5 5 ", n_var=-1, type_of_var=integer_t, &
597 27888 : default_i_val=-1)
598 27888 : CALL section_add_keyword(section, keyword)
599 27888 : CALL keyword_release(keyword)
600 :
601 : CALL keyword_create(keyword, __LOCATION__, name="START_INDEX", &
602 : description="Starting index for Geometrical Basis sets", &
603 : usage="START_INDEX 0 2 5 4 ", n_var=-1, type_of_var=integer_t, &
604 27888 : default_i_val=0)
605 27888 : CALL section_add_keyword(section, keyword)
606 27888 : CALL keyword_release(keyword)
607 :
608 : CALL keyword_create(keyword, __LOCATION__, name="S_EXPONENTS", &
609 : description="Exponents for s functions", &
610 27888 : usage="S_EXPONENTS 1.0 2.0 ... ", n_var=-1, type_of_var=real_t)
611 27888 : CALL section_add_keyword(section, keyword)
612 27888 : CALL keyword_release(keyword)
613 : CALL keyword_create(keyword, __LOCATION__, name="P_EXPONENTS", &
614 : description="Exponents for p functions", &
615 27888 : usage="P_EXPONENTS 1.0 2.0 ... ", n_var=-1, type_of_var=real_t)
616 27888 : CALL section_add_keyword(section, keyword)
617 27888 : CALL keyword_release(keyword)
618 : CALL keyword_create(keyword, __LOCATION__, name="D_EXPONENTS", &
619 : description="Exponents for d functions", &
620 27888 : usage="D_EXPONENTS 1.0 2.0 ... ", n_var=-1, type_of_var=real_t)
621 27888 : CALL section_add_keyword(section, keyword)
622 27888 : CALL keyword_release(keyword)
623 : CALL keyword_create(keyword, __LOCATION__, name="F_EXPONENTS", &
624 : description="Exponents for f functions", &
625 27888 : usage="F_EXPONENTS 1.0 2.0 ... ", n_var=-1, type_of_var=real_t)
626 27888 : CALL section_add_keyword(section, keyword)
627 27888 : CALL keyword_release(keyword)
628 :
629 : CALL keyword_create(keyword, __LOCATION__, name="S_QUANTUM_NUMBERS", &
630 : description="Main quantum numbers for s functions", &
631 27888 : usage="S_QUANTUM_NUMBERS 1 2 ... ", n_var=-1, type_of_var=integer_t)
632 27888 : CALL section_add_keyword(section, keyword)
633 27888 : CALL keyword_release(keyword)
634 : CALL keyword_create(keyword, __LOCATION__, name="P_QUANTUM_NUMBERS", &
635 : description="Main quantum numbers for p functions", &
636 27888 : usage="P_QUANTUM_NUMBERS 2 3 ... ", n_var=-1, type_of_var=integer_t)
637 27888 : CALL section_add_keyword(section, keyword)
638 27888 : CALL keyword_release(keyword)
639 : CALL keyword_create(keyword, __LOCATION__, name="D_QUANTUM_NUMBERS", &
640 : description="Main quantum numbers for d functions", &
641 27888 : usage="D_QUANTUM_NUMBERS 3 4 ... ", n_var=-1, type_of_var=integer_t)
642 27888 : CALL section_add_keyword(section, keyword)
643 27888 : CALL keyword_release(keyword)
644 : CALL keyword_create(keyword, __LOCATION__, name="F_QUANTUM_NUMBERS", &
645 : description="Main quantum numbers for f functions", &
646 27888 : usage="F_QUANTUM_NUMBERS 4 5 ... ", n_var=-1, type_of_var=integer_t)
647 27888 : CALL section_add_keyword(section, keyword)
648 27888 : CALL keyword_release(keyword)
649 :
650 : CALL keyword_create(keyword, __LOCATION__, name="GEOMETRICAL_FACTOR", &
651 : description="Geometrical basis: factor C in a*C^k", &
652 : usage="GEOMETRICAL_FACTOR real", &
653 27888 : default_r_val=2.6_dp)
654 27888 : CALL section_add_keyword(section, keyword)
655 27888 : CALL keyword_release(keyword)
656 :
657 : CALL keyword_create(keyword, __LOCATION__, name="GEO_START_VALUE", &
658 : description="Geometrical basis: starting value a in a*C^k", &
659 : usage="GEO_START_VALUE real", &
660 27888 : default_r_val=0.016_dp)
661 27888 : CALL section_add_keyword(section, keyword)
662 27888 : CALL keyword_release(keyword)
663 :
664 : CALL keyword_create(keyword, __LOCATION__, name="BASIS_SET_FILE_NAME", &
665 : description="Name of the basis set file, may include a path", &
666 : usage="BASIS_SET_FILE_NAME <FILENAME>", &
667 27888 : default_lc_val="BASIS_SET")
668 27888 : CALL section_add_keyword(section, keyword)
669 27888 : CALL keyword_release(keyword)
670 :
671 : CALL keyword_create(keyword, __LOCATION__, name="BASIS_SET", &
672 : variants=s2a("ORBITAL_BASIS_SET", "ORB_BASIS"), &
673 : description="The contracted Gaussian basis set", &
674 : usage="BASIS_SET DZVP", default_c_val=" ", &
675 27888 : n_var=1)
676 27888 : CALL section_add_keyword(section, keyword)
677 27888 : CALL keyword_release(keyword)
678 :
679 : CALL keyword_create(keyword, __LOCATION__, name="QUADRATURE", &
680 : description="Algorithm to construct the atomic radial grids", &
681 : usage="QUADRATURE (GC_SIMPLE|GC_TRANSFORMED|GC_LOG)", &
682 : enum_c_vals=s2a("GC_SIMPLE", "GC_TRANSFORMED", "GC_LOG"), &
683 : enum_i_vals=[do_gapw_gcs, do_gapw_gct, do_gapw_log], &
684 : enum_desc=s2a("Gauss-Chebyshev quadrature", &
685 : "Transformed Gauss-Chebyshev quadrature", &
686 : "Logarithmic transformed Gauss-Chebyshev quadrature"), &
687 27888 : default_i_val=do_gapw_log)
688 27888 : CALL section_add_keyword(section, keyword)
689 27888 : CALL keyword_release(keyword)
690 :
691 : CALL keyword_create(keyword, __LOCATION__, name="GRID_POINTS", &
692 : description="Number of radial grid points", &
693 : usage="GRID_POINTS integer", &
694 27888 : default_i_val=400)
695 27888 : CALL section_add_keyword(section, keyword)
696 27888 : CALL keyword_release(keyword)
697 :
698 : CALL keyword_create(keyword, __LOCATION__, name="EPS_EIGENVALUE", &
699 : description="Cutoff of overlap matrix eigenvalues included into basis", &
700 : usage="EPS_EIGENVALUE real", &
701 27888 : default_r_val=1.e-12_dp)
702 27888 : CALL section_add_keyword(section, keyword)
703 27888 : CALL keyword_release(keyword)
704 :
705 27888 : NULLIFY (subsection)
706 27888 : CALL create_basis_section(subsection)
707 27888 : CALL section_add_subsection(section, subsection)
708 27888 : CALL section_release(subsection)
709 :
710 27888 : END SUBROUTINE atom_basis_section
711 :
712 : ! **************************************************************************************************
713 : !> \brief Create the method section for Atom calculations
714 : !> \param section the section to create
715 : !> \author jgh
716 : ! **************************************************************************************************
717 9296 : SUBROUTINE create_atom_method_section(section)
718 : TYPE(section_type), POINTER :: section
719 :
720 : TYPE(keyword_type), POINTER :: keyword
721 : TYPE(section_type), POINTER :: subsection
722 :
723 9296 : NULLIFY (subsection, keyword)
724 9296 : CPASSERT(.NOT. ASSOCIATED(section))
725 : CALL section_create(section, __LOCATION__, name="METHOD", &
726 : description="Section of information on method to use.", &
727 9296 : n_keywords=0, n_subsections=2, repeats=.TRUE.)
728 :
729 : CALL keyword_create(keyword, __LOCATION__, name="METHOD_TYPE", &
730 : description="Type of electronic structure method to be used", &
731 : usage="METHOD_TYPE (KOHN-SHAM|RKS|UKS|HARTREE-FOCK|RHF|UHF|ROHF)", &
732 : default_i_val=do_rks_atom, &
733 : enum_c_vals=["KOHN-SHAM ", &
734 : "RKS ", &
735 : "UKS ", &
736 : "HARTREE-FOCK ", &
737 : "RHF ", &
738 : "UHF ", &
739 : "ROHF "], &
740 : enum_i_vals=[do_rks_atom, do_rks_atom, do_uks_atom, do_rhf_atom, &
741 : do_rhf_atom, do_uhf_atom, do_rohf_atom], &
742 : enum_desc=s2a("Kohn-Sham electronic structure method", &
743 : "Restricted Kohn-Sham electronic structure method", &
744 : "Unrestricted Kohn-Sham electronic structure method", &
745 : "Hartree-Fock electronic structure method", &
746 : "Restricted Hartree-Fock electronic structure method", &
747 : "Unrestricted Hartree-Fock electronic structure method", &
748 74368 : "Restricted open-shell Hartree-Fock electronic structure method"))
749 9296 : CALL section_add_keyword(section, keyword)
750 9296 : CALL keyword_release(keyword)
751 :
752 : CALL keyword_create(keyword, __LOCATION__, name="RELATIVISTIC", &
753 : description="Type of scalar relativistic method to be used", &
754 : usage="RELATIVISTIC (OFF|ZORA(MP)|scZORA(MP)|DKH(0)|DKH(1)|DKH(2)|DKH(3))", &
755 : default_i_val=do_nonrel_atom, &
756 : enum_c_vals=["OFF ", &
757 : "ZORA(MP) ", &
758 : "scZORA(MP) ", &
759 : "DKH(0) ", &
760 : "DKH(1) ", &
761 : "DKH(2) ", &
762 : "DKH(3) "], &
763 : enum_i_vals=[do_nonrel_atom, do_zoramp_atom, do_sczoramp_atom, do_dkh0_atom, &
764 : do_dkh1_atom, do_dkh2_atom, do_dkh3_atom], &
765 : enum_desc=s2a("Use no scalar relativistic method", &
766 : "Use ZORA method with atomic model potential", &
767 : "Use scaled ZORA method with atomic model potential", &
768 : "Use Douglas-Kroll-Hess Hamiltonian of order 0", &
769 : "Use Douglas-Kroll-Hess Hamiltonian of order 1", &
770 : "Use Douglas-Kroll-Hess Hamiltonian of order 2", &
771 74368 : "Use Douglas-Kroll-Hess Hamiltonian of order 3"))
772 9296 : CALL section_add_keyword(section, keyword)
773 9296 : CALL keyword_release(keyword)
774 :
775 9296 : CALL create_xc_section(subsection)
776 9296 : CALL section_add_subsection(section, subsection)
777 9296 : CALL section_release(subsection)
778 :
779 : ! ZMP creating zubsection for the zmp calculations
780 9296 : CALL create_zmp_section(subsection)
781 9296 : CALL section_add_subsection(section, subsection)
782 9296 : CALL section_release(subsection)
783 :
784 9296 : CALL create_external_vxc(subsection)
785 9296 : CALL section_add_subsection(section, subsection)
786 9296 : CALL section_release(subsection)
787 :
788 9296 : END SUBROUTINE create_atom_method_section
789 :
790 : ! **************************************************************************************************
791 : !> \brief Create the ZMP subsection for Atom calculations
792 : !>
793 : !> \param section ...
794 : !> \author D. Varsano [daniele.varsano@nano.cnr.it]
795 : ! **************************************************************************************************
796 9296 : SUBROUTINE create_zmp_section(section)
797 : TYPE(section_type), POINTER :: section
798 :
799 : TYPE(keyword_type), POINTER :: keyword
800 : TYPE(section_type), POINTER :: subsection
801 :
802 9296 : NULLIFY (subsection, keyword)
803 9296 : CPASSERT(.NOT. ASSOCIATED(section))
804 : CALL section_create(section, __LOCATION__, name="ZMP", &
805 : description="Section used to specify ZMP Potentials.", &
806 9296 : n_keywords=3, n_subsections=0, repeats=.FALSE.)
807 :
808 : CALL keyword_create(keyword, __LOCATION__, name="FILE_DENSITY", &
809 : description="Specifies the filename containing the target density ", &
810 : usage="FILE_DENSITY <FILENAME>", &
811 9296 : type_of_var=char_t, default_c_val="RHO_O.dat", n_var=-1)
812 9296 : CALL section_add_keyword(section, keyword)
813 9296 : CALL keyword_release(keyword)
814 :
815 : CALL keyword_create(keyword, __LOCATION__, name="GRID_TOL", &
816 : description="Tolerance in the equivalence of read-grid in ZMP method", &
817 9296 : usage="GRID_TOL <REAL>", default_r_val=1.E-12_dp)
818 9296 : CALL section_add_keyword(section, keyword)
819 9296 : CALL keyword_release(keyword)
820 :
821 : CALL keyword_create(keyword, __LOCATION__, name="LAMBDA", &
822 : description="Parameter used for the constraint in ZMP method", &
823 9296 : usage="LAMBDA <REAL>", default_r_val=10.0_dp)
824 9296 : CALL section_add_keyword(section, keyword)
825 9296 : CALL keyword_release(keyword)
826 :
827 : CALL keyword_create(keyword, __LOCATION__, name="DM", &
828 : description="read external density from density matrix", &
829 9296 : usage="DM <LOGICAL>", type_of_var=logical_t, default_l_val=.FALSE.)
830 9296 : CALL section_add_keyword(section, keyword)
831 9296 : CALL keyword_release(keyword)
832 :
833 9296 : CALL create_zmp_restart_section(subsection)
834 9296 : CALL section_add_subsection(section, subsection)
835 9296 : CALL section_release(subsection)
836 :
837 9296 : END SUBROUTINE create_zmp_section
838 :
839 : ! **************************************************************************************************
840 : !> \brief Create the ZMP restart subsection for Atom calculations
841 : !>
842 : !> \param section ...
843 : !> \author D. Varsano [daniele.varsano@nano.cnr.it]
844 : ! **************************************************************************************************
845 9296 : SUBROUTINE create_zmp_restart_section(section)
846 : TYPE(section_type), POINTER :: section
847 :
848 : TYPE(keyword_type), POINTER :: keyword
849 :
850 9296 : NULLIFY (keyword)
851 9296 : CPASSERT(.NOT. ASSOCIATED(section))
852 : CALL section_create(section, __LOCATION__, name="RESTART", &
853 : description="Section used to specify the restart option in the ZMP "// &
854 : "procedure, and the file that must be read.", &
855 9296 : n_keywords=1, n_subsections=0, repeats=.FALSE.)
856 :
857 : CALL keyword_create(keyword, __LOCATION__, name="FILE_RESTART", &
858 : description="Specifies the filename containing the restart file density ", &
859 : usage="FILE_RESTART <FILENAME>", &
860 9296 : type_of_var=char_t, default_c_val="RESTART.wfn", n_var=-1)
861 9296 : CALL section_add_keyword(section, keyword)
862 9296 : CALL keyword_release(keyword)
863 :
864 9296 : END SUBROUTINE create_zmp_restart_section
865 :
866 : ! **************************************************************************************************
867 : !> \brief Subroutine to create the external v_xc potential
868 : !>
869 : !> \param section ...
870 : !> \author D. Varsano [daniele.varsano@nano.cnr.it]
871 : ! **************************************************************************************************
872 9296 : SUBROUTINE create_external_vxc(section)
873 : TYPE(section_type), POINTER :: section
874 :
875 : TYPE(keyword_type), POINTER :: keyword
876 :
877 9296 : NULLIFY (keyword)
878 9296 : CPASSERT(.NOT. ASSOCIATED(section))
879 : CALL section_create(section, __LOCATION__, name="EXTERNAL_VXC", &
880 : description="Section used to specify exernal VXC Potentials.", &
881 9296 : n_keywords=1, n_subsections=0, repeats=.FALSE.)
882 :
883 : CALL keyword_create(keyword, __LOCATION__, name="FILE_VXC", &
884 : description="Specifies the filename containing the external vxc ", &
885 : usage="FILE_VXC <FILENAME>", &
886 9296 : type_of_var=char_t, default_c_val="VXC.dat", n_var=-1)
887 9296 : CALL section_add_keyword(section, keyword)
888 9296 : CALL keyword_release(keyword)
889 :
890 : CALL keyword_create(keyword, __LOCATION__, name="GRID_TOL", &
891 : description="Tolerance in the equivalence of read-grid in ZMP method", &
892 9296 : usage="GRID_TOL <REAL>", default_r_val=1.E-12_dp)
893 9296 : CALL section_add_keyword(section, keyword)
894 9296 : CALL keyword_release(keyword)
895 :
896 9296 : END SUBROUTINE create_external_vxc
897 :
898 : ! **************************************************************************************************
899 : !> \brief Create the optimization section for Atom calculations
900 : !> \param section the section to create
901 : !> \author jgh
902 : ! **************************************************************************************************
903 9296 : SUBROUTINE create_optimization_section(section)
904 : TYPE(section_type), POINTER :: section
905 :
906 : TYPE(keyword_type), POINTER :: keyword
907 :
908 9296 : NULLIFY (keyword)
909 9296 : CPASSERT(.NOT. ASSOCIATED(section))
910 : CALL section_create(section, __LOCATION__, name="OPTIMIZATION", &
911 : description="Section of information on optimization thresholds and algorithms.", &
912 9296 : n_keywords=0, n_subsections=1, repeats=.FALSE.)
913 :
914 : CALL keyword_create(keyword, __LOCATION__, name="MAX_ITER", &
915 : description="Maximum number of iterations for optimization", &
916 9296 : usage="MAX_ITER 50", default_i_val=200)
917 9296 : CALL section_add_keyword(section, keyword)
918 9296 : CALL keyword_release(keyword)
919 :
920 : CALL keyword_create(keyword, __LOCATION__, name="EPS_SCF", &
921 : description="Convergence criterion for SCF", &
922 9296 : usage="EPS_SCF 1.e-10", default_r_val=1.e-6_dp)
923 9296 : CALL section_add_keyword(section, keyword)
924 9296 : CALL keyword_release(keyword)
925 :
926 : CALL keyword_create(keyword, __LOCATION__, name="DAMPING", &
927 : description="Damping parameter for extrapolation method", &
928 9296 : usage="DAMPING 0.4", default_r_val=0.4_dp)
929 9296 : CALL section_add_keyword(section, keyword)
930 9296 : CALL keyword_release(keyword)
931 :
932 : CALL keyword_create(keyword, __LOCATION__, name="EPS_DIIS", &
933 : description="Starting DIIS method at convergence to EPS_DIIS", &
934 9296 : usage="EPS_DIIS 0.01", default_r_val=10000._dp)
935 9296 : CALL section_add_keyword(section, keyword)
936 9296 : CALL keyword_release(keyword)
937 :
938 : CALL keyword_create(keyword, __LOCATION__, name="N_DIIS", &
939 : description="Maximum number of DIIS vectors", &
940 9296 : usage="N_DIIS 6", default_i_val=5)
941 9296 : CALL section_add_keyword(section, keyword)
942 9296 : CALL keyword_release(keyword)
943 :
944 9296 : END SUBROUTINE create_optimization_section
945 :
946 : ! **************************************************************************************************
947 : !> \brief Create the potential section for Atom calculations
948 : !> \param section the section to create
949 : !> \author jgh
950 : ! **************************************************************************************************
951 18592 : SUBROUTINE create_potential_section(section)
952 : TYPE(section_type), POINTER :: section
953 :
954 : TYPE(keyword_type), POINTER :: keyword
955 : TYPE(section_type), POINTER :: subsection
956 :
957 18592 : NULLIFY (keyword)
958 18592 : CPASSERT(.NOT. ASSOCIATED(section))
959 : CALL section_create(section, __LOCATION__, name="POTENTIAL", &
960 : description="Section of information on potential.", &
961 18592 : n_keywords=0, n_subsections=1, repeats=.FALSE.)
962 :
963 : CALL keyword_create(keyword, __LOCATION__, name="CONFINEMENT_TYPE", &
964 : description="Define functional form of confinement potential.", &
965 : usage="CONFINEMENT_TYPE (NONE|POLYNOM|BARRIER)", &
966 : default_i_val=poly_conf, &
967 : enum_c_vals=["NONE ", &
968 : "POLYNOM ", &
969 : "BARRIER "], &
970 : enum_i_vals=[no_conf, poly_conf, barrier_conf], &
971 : enum_desc=s2a("Do not use confinement potential", &
972 : "Use polynomial confinement potential: a*(R/b)^c", &
973 74368 : "Use a smooth barrier potential: a*F[R-c)/b]"))
974 18592 : CALL section_add_keyword(section, keyword)
975 18592 : CALL keyword_release(keyword)
976 :
977 : CALL keyword_create(keyword, __LOCATION__, name="CONFINEMENT", &
978 : description="Definition of parameters for confinement potential (a,b,c)", &
979 : usage="CONFINEMENT prefactor range exponent (POLYNOM) "// &
980 : "CONFINEMENT prefactor range r_onset (BARRIER)", &
981 : default_r_vals=[0._dp, 0._dp, 0._dp], &
982 18592 : repeats=.FALSE., n_var=-1)
983 18592 : CALL section_add_keyword(section, keyword)
984 18592 : CALL keyword_release(keyword)
985 :
986 : CALL keyword_create(keyword, __LOCATION__, name="PSEUDO_TYPE", &
987 : description="Pseudopotential type", &
988 : usage="PSEUDO_TYPE (NONE|GTH|UPF|ECP)", &
989 : default_i_val=no_pseudo, &
990 : enum_c_vals=["NONE ", &
991 : "GTH ", &
992 : "UPF ", &
993 : "SGP ", &
994 : "ECP "], &
995 : enum_i_vals=[no_pseudo, gth_pseudo, upf_pseudo, sgp_pseudo, ecp_pseudo], &
996 : enum_desc=s2a("Do not use pseudopotentials", &
997 : "Use Goedecker-Teter-Hutter pseudopotentials", &
998 : "Use UPF norm-conserving pseudopotentials", &
999 : "Use SGP norm-conserving pseudopotentials", &
1000 111552 : "Use ECP semi-local pseudopotentials"))
1001 18592 : CALL section_add_keyword(section, keyword)
1002 18592 : CALL keyword_release(keyword)
1003 :
1004 : CALL keyword_create(keyword, __LOCATION__, name="POTENTIAL_FILE_NAME", &
1005 : description="Name of the pseudo potential file, may include a path", &
1006 : usage="POTENTIAL_FILE_NAME <FILENAME>", &
1007 18592 : default_lc_val="POTENTIAL")
1008 18592 : CALL section_add_keyword(section, keyword)
1009 18592 : CALL keyword_release(keyword)
1010 :
1011 : CALL keyword_create(keyword, __LOCATION__, name="POTENTIAL_NAME", &
1012 : variants=["POT_NAME"], &
1013 : description="The name of the pseudopotential for the defined kind.", &
1014 37184 : usage="POTENTIAL_NAME <PSEUDO-POTENTIAL-NAME>", default_c_val=" ", n_var=1)
1015 18592 : CALL section_add_keyword(section, keyword)
1016 18592 : CALL keyword_release(keyword)
1017 :
1018 18592 : NULLIFY (subsection)
1019 18592 : CALL create_gthpotential_section(subsection)
1020 18592 : CALL section_add_subsection(section, subsection)
1021 18592 : CALL section_release(subsection)
1022 :
1023 18592 : NULLIFY (subsection)
1024 18592 : CALL create_ecp_section(subsection)
1025 18592 : CALL section_add_subsection(section, subsection)
1026 18592 : CALL section_release(subsection)
1027 :
1028 18592 : END SUBROUTINE create_potential_section
1029 :
1030 : ! **************************************************************************************************
1031 : !> \brief Creates the >H_POTENTIAL section
1032 : !> \param section the section to create
1033 : !> \author teo
1034 : ! **************************************************************************************************
1035 18592 : SUBROUTINE create_gthpotential_section(section)
1036 : TYPE(section_type), POINTER :: section
1037 :
1038 : TYPE(keyword_type), POINTER :: keyword
1039 :
1040 : CALL section_create(section, __LOCATION__, name="GTH_POTENTIAL", &
1041 : description="Section used to specify Potentials.", &
1042 18592 : n_keywords=1, n_subsections=0, repeats=.FALSE.)
1043 18592 : NULLIFY (keyword)
1044 : CALL keyword_create(keyword, __LOCATION__, name="_DEFAULT_KEYWORD_", &
1045 : description="CP2K Pseudo Potential Standard Format (GTH, ALL or KG)", &
1046 18592 : repeats=.TRUE., type_of_var=lchar_t)
1047 18592 : CALL section_add_keyword(section, keyword)
1048 18592 : CALL keyword_release(keyword)
1049 18592 : END SUBROUTINE create_gthpotential_section
1050 :
1051 : ! **************************************************************************************************
1052 : !> \brief Creates the &ECP section
1053 : !> \param section the section to create
1054 : !> \author jgh
1055 : ! **************************************************************************************************
1056 18592 : SUBROUTINE create_ecp_section(section)
1057 : TYPE(section_type), POINTER :: section
1058 :
1059 : TYPE(keyword_type), POINTER :: keyword
1060 :
1061 : CALL section_create(section, __LOCATION__, name="ECP", &
1062 : description="Section used to specify ECP's.", &
1063 18592 : n_keywords=1, n_subsections=0, repeats=.FALSE.)
1064 18592 : NULLIFY (keyword)
1065 : CALL keyword_create(keyword, __LOCATION__, name="_DEFAULT_KEYWORD_", &
1066 : description="Effective Core Potentials definition", &
1067 18592 : repeats=.TRUE., type_of_var=lchar_t)
1068 18592 : CALL section_add_keyword(section, keyword)
1069 18592 : CALL keyword_release(keyword)
1070 18592 : END SUBROUTINE create_ecp_section
1071 :
1072 : ! **************************************************************************************************
1073 : !> \brief Creates the &BASIS section
1074 : !> \param section the section to create
1075 : !> \author teo
1076 : ! **************************************************************************************************
1077 27888 : SUBROUTINE create_basis_section(section)
1078 : TYPE(section_type), POINTER :: section
1079 :
1080 : TYPE(keyword_type), POINTER :: keyword
1081 :
1082 : CALL section_create(section, __LOCATION__, name="basis", &
1083 : description="Section used to specify a general basis set for QM calculations.", &
1084 27888 : n_keywords=1, n_subsections=0, repeats=.FALSE.)
1085 27888 : NULLIFY (keyword)
1086 : CALL keyword_create(keyword, __LOCATION__, name="_DEFAULT_KEYWORD_", &
1087 : description="CP2K Basis Set Standard Format", repeats=.TRUE., &
1088 27888 : type_of_var=lchar_t)
1089 27888 : CALL section_add_keyword(section, keyword)
1090 27888 : CALL keyword_release(keyword)
1091 27888 : END SUBROUTINE create_basis_section
1092 :
1093 : ! **************************************************************************************************
1094 : !> \brief Creates the &POWELL section
1095 : !> \param section the section to create
1096 : !> \author teo
1097 : ! **************************************************************************************************
1098 9296 : SUBROUTINE create_powell_section(section)
1099 : TYPE(section_type), POINTER :: section
1100 :
1101 : TYPE(keyword_type), POINTER :: keyword
1102 :
1103 : CALL section_create(section, __LOCATION__, name="powell", &
1104 : description="Section defines basic parameters for Powell optimization", &
1105 9296 : n_keywords=4, n_subsections=0, repeats=.FALSE.)
1106 :
1107 9296 : NULLIFY (keyword)
1108 : CALL keyword_create(keyword, __LOCATION__, name="ACCURACY", &
1109 : description="Final accuracy requested in optimization (RHOEND)", &
1110 : usage="ACCURACY 0.00001", &
1111 9296 : default_r_val=1.e-6_dp)
1112 9296 : CALL section_add_keyword(section, keyword)
1113 9296 : CALL keyword_release(keyword)
1114 :
1115 : CALL keyword_create(keyword, __LOCATION__, name="STEP_SIZE", &
1116 : description="Initial step size for search algorithm (RHOBEG)", &
1117 : usage="STEP_SIZE 0.005", &
1118 9296 : default_r_val=0.005_dp)
1119 9296 : CALL section_add_keyword(section, keyword)
1120 9296 : CALL keyword_release(keyword)
1121 :
1122 : CALL keyword_create(keyword, __LOCATION__, name="MAX_FUN", &
1123 : description="Maximum number of function evaluations", &
1124 : usage="MAX_FUN 1000", &
1125 9296 : default_i_val=5000)
1126 9296 : CALL section_add_keyword(section, keyword)
1127 9296 : CALL keyword_release(keyword)
1128 :
1129 : CALL keyword_create(keyword, __LOCATION__, name="MAX_INIT", &
1130 : description="Maximum number of re-initialization of Powell method", &
1131 : usage="MAX_INIT 5", &
1132 9296 : default_i_val=1)
1133 9296 : CALL section_add_keyword(section, keyword)
1134 9296 : CALL keyword_release(keyword)
1135 :
1136 : CALL keyword_create(keyword, __LOCATION__, name="STEP_SIZE_SCALING", &
1137 : description="Scaling of Step Size on re-initialization of Powell method", &
1138 : usage="STEP_SIZE_SCALING 0.80", &
1139 9296 : default_r_val=0.75_dp)
1140 9296 : CALL section_add_keyword(section, keyword)
1141 9296 : CALL keyword_release(keyword)
1142 :
1143 : CALL keyword_create(keyword, __LOCATION__, name="WEIGHT_POT_VIRTUAL", &
1144 : description="Weight for virtual states in pseudopotential optimization", &
1145 : usage="WEIGHT_POT_VIRTUAL 1.0", &
1146 9296 : default_r_val=1._dp)
1147 9296 : CALL section_add_keyword(section, keyword)
1148 9296 : CALL keyword_release(keyword)
1149 :
1150 : CALL keyword_create(keyword, __LOCATION__, name="WEIGHT_POT_SEMICORE", &
1151 : description="Weight for semi core states in pseudopotential optimization", &
1152 : usage="WEIGHT_POT_SEMICORE 1.0", &
1153 9296 : default_r_val=1._dp)
1154 9296 : CALL section_add_keyword(section, keyword)
1155 9296 : CALL keyword_release(keyword)
1156 :
1157 : CALL keyword_create(keyword, __LOCATION__, name="WEIGHT_POT_VALENCE", &
1158 : description="Weight for valence states in pseudopotential optimization", &
1159 : usage="WEIGHT_POT_VALENCE 1.0", &
1160 9296 : default_r_val=1.0_dp)
1161 9296 : CALL section_add_keyword(section, keyword)
1162 9296 : CALL keyword_release(keyword)
1163 :
1164 : CALL keyword_create(keyword, __LOCATION__, name="WEIGHT_POT_NODE", &
1165 : description="Weight for node mismatch in pseudopotential optimization", &
1166 : usage="WEIGHT_POT_NODE 1.0", &
1167 9296 : default_r_val=1.0_dp)
1168 9296 : CALL section_add_keyword(section, keyword)
1169 9296 : CALL keyword_release(keyword)
1170 :
1171 : CALL keyword_create(keyword, __LOCATION__, name="WEIGHT_DELTA_ENERGY", &
1172 : description="Weight for energy differences in pseudopotential optimization", &
1173 : usage="WEIGHT_DELTA_ENERGY 1.0", &
1174 9296 : default_r_val=1._dp)
1175 9296 : CALL section_add_keyword(section, keyword)
1176 9296 : CALL keyword_release(keyword)
1177 :
1178 : CALL keyword_create(keyword, __LOCATION__, name="WEIGHT_ELECTRON_CONFIGURATION", &
1179 : description="Weight for different electronic states in optimization", &
1180 : usage="WEIGHT_ELECTRON_CONFIGURATION 1.0 0.1 ...", &
1181 9296 : n_var=-1, type_of_var=real_t, default_r_val=1.0_dp)
1182 9296 : CALL section_add_keyword(section, keyword)
1183 9296 : CALL keyword_release(keyword)
1184 :
1185 : CALL keyword_create(keyword, __LOCATION__, name="WEIGHT_METHOD", &
1186 : description="Weight for different methods in optimization", &
1187 : usage="WEIGHT_METHOD 1.0 0.1 ...", &
1188 9296 : n_var=-1, type_of_var=real_t, default_r_val=1.0_dp)
1189 9296 : CALL section_add_keyword(section, keyword)
1190 9296 : CALL keyword_release(keyword)
1191 :
1192 : CALL keyword_create(keyword, __LOCATION__, name="TARGET_POT_VIRTUAL", &
1193 : description="Target accuracy for virtual state eigenvalues in pseudopotential optimization", &
1194 : usage="TARGET_POT_VIRTUAL 0.0001", &
1195 9296 : default_r_val=1.0e-3_dp, unit_str="hartree")
1196 9296 : CALL section_add_keyword(section, keyword)
1197 9296 : CALL keyword_release(keyword)
1198 :
1199 : CALL keyword_create(keyword, __LOCATION__, name="TARGET_POT_VALENCE", &
1200 : description="Target accuracy for valence state eigenvalues in pseudopotential optimization", &
1201 : usage="TARGET_POT_VALENCE 0.0001", &
1202 9296 : default_r_val=1.0e-5_dp, unit_str="hartree")
1203 9296 : CALL section_add_keyword(section, keyword)
1204 9296 : CALL keyword_release(keyword)
1205 :
1206 : CALL keyword_create(keyword, __LOCATION__, name="TARGET_POT_SEMICORE", &
1207 : description="Target accuracy for semicore state eigenvalues in pseudopotential optimization", &
1208 : usage="TARGET_POT_SEMICORE 0.01", &
1209 9296 : default_r_val=1.0e-3_dp, unit_str="hartree")
1210 9296 : CALL section_add_keyword(section, keyword)
1211 9296 : CALL keyword_release(keyword)
1212 :
1213 : CALL keyword_create(keyword, __LOCATION__, name="TARGET_DELTA_ENERGY", &
1214 : description="Target accuracy for energy differences in pseudopotential optimization", &
1215 : usage="TARGET_DELTA_ENERGY 0.01", &
1216 9296 : default_r_val=1.0e-4_dp, unit_str="hartree")
1217 9296 : CALL section_add_keyword(section, keyword)
1218 9296 : CALL keyword_release(keyword)
1219 :
1220 : CALL keyword_create(keyword, __LOCATION__, name="TARGET_PSIR0", &
1221 : description="Minimum value for the wavefunctions at r=0 (only occupied states)"// &
1222 : " Value=0 means keeping wfn(r=0)=0", &
1223 : usage="TARGET_PSIR0 0.50", &
1224 9296 : default_r_val=0._dp)
1225 9296 : CALL section_add_keyword(section, keyword)
1226 9296 : CALL keyword_release(keyword)
1227 :
1228 : CALL keyword_create(keyword, __LOCATION__, name="WEIGHT_PSIR0", &
1229 : description="Weight for the wavefunctions at r=0 (only occupied states)", &
1230 : usage="WEIGHT_PSIR0 0.01", &
1231 9296 : default_r_val=0._dp)
1232 9296 : CALL section_add_keyword(section, keyword)
1233 9296 : CALL keyword_release(keyword)
1234 :
1235 : CALL keyword_create(keyword, __LOCATION__, name="RCOV_MULTIPLICATION", &
1236 : description="Multiply Rcov integration limit for charge conservation", &
1237 : usage="RCOV_MULTIPLICATION 1.10", &
1238 9296 : default_r_val=1._dp)
1239 9296 : CALL section_add_keyword(section, keyword)
1240 9296 : CALL keyword_release(keyword)
1241 :
1242 : CALL keyword_create(keyword, __LOCATION__, name="SEMICORE_LEVEL", &
1243 : description="Energy at which to consider a full shell as semicore", &
1244 : usage="SEMICORE_LEVEL 1.0", &
1245 9296 : default_r_val=1._dp, unit_str="hartree")
1246 9296 : CALL section_add_keyword(section, keyword)
1247 9296 : CALL keyword_release(keyword)
1248 :
1249 : CALL keyword_create(keyword, __LOCATION__, name="NOOPT_NLCC", &
1250 : description="Don't optimize NLCC parameters.", &
1251 : usage="NOOPT_NLCC T", &
1252 : type_of_var=logical_t, &
1253 9296 : default_l_val=.FALSE.)
1254 9296 : CALL section_add_keyword(section, keyword)
1255 9296 : CALL keyword_release(keyword)
1256 :
1257 : CALL keyword_create(keyword, __LOCATION__, name="PREOPT_NLCC", &
1258 : description="Optimize NLCC parameters by fitting core charge density.", &
1259 : usage="PREOPT_NLCC T", &
1260 : type_of_var=logical_t, &
1261 9296 : default_l_val=.FALSE.)
1262 9296 : CALL section_add_keyword(section, keyword)
1263 9296 : CALL keyword_release(keyword)
1264 :
1265 9296 : END SUBROUTINE create_powell_section
1266 :
1267 : ! **************************************************************************************************
1268 :
1269 : END MODULE input_cp2k_atom
|