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