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