(git:374b731)
Loading...
Searching...
No Matches
input_cp2k_atom.F
Go to the documentation of this file.
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! **************************************************************************************************
18 USE input_constants, ONLY: &
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
53CONTAINS
54
55! **************************************************************************************************
56!> \brief Creates the input section for the atom code
57!> \param section the section to create
58!> \author jgh
59! **************************************************************************************************
60 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 cpassert(.NOT. ASSOCIATED(section))
67 CALL section_create(section, __location__, name="ATOM", &
68 description="Section handling input for atomic calculations.", &
69 n_keywords=1, n_subsections=1, repeats=.false.)
70 NULLIFY (keyword, subsection)
71
72 CALL keyword_create(keyword, __location__, name="ATOMIC_NUMBER", &
73 description="Specify the atomic number", &
74 default_i_val=1)
75 CALL section_add_keyword(section, keyword)
76 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 default_c_val="H")
82 CALL section_add_keyword(section, keyword)
83 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"), &
92 enum_desc=s2a("Perform no run", &
93 "Perform energy optimization", &
94 "Perform basis optimization", &
95 "Perform pseudopotential optimization"))
96 CALL section_add_keyword(section, keyword)
97 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 "Use numerical method"))
110 CALL section_add_keyword(section, keyword)
111 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 "Use numerical method"))
124 CALL section_add_keyword(section, keyword)
125 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 n_var=-1, type_of_var=char_t)
131 CALL section_add_keyword(section, keyword)
132 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 n_var=-1, type_of_var=char_t)
139 CALL section_add_keyword(section, keyword)
140 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 default_i_val=3)
146 CALL section_add_keyword(section, keyword)
147 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 default_i_val=0, n_var=-1, type_of_var=integer_t)
153 CALL section_add_keyword(section, keyword)
154 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 default_l_val=.false.)
161 CALL section_add_keyword(section, keyword)
162 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 default_i_val=100)
168 CALL section_add_keyword(section, keyword)
169 CALL keyword_release(keyword)
170
171 CALL create_atom_print_section(subsection)
172 CALL section_add_subsection(section, subsection)
173 CALL section_release(subsection)
174
175 CALL create_atom_aebasis_section(subsection)
176 CALL section_add_subsection(section, subsection)
177 CALL section_release(subsection)
178
179 CALL create_atom_ppbasis_section(subsection)
180 CALL section_add_subsection(section, subsection)
181 CALL section_release(subsection)
182
183 CALL create_atom_method_section(subsection)
184 CALL section_add_subsection(section, subsection)
185 CALL section_release(subsection)
186
187 CALL create_optimization_section(subsection)
188 CALL section_add_subsection(section, subsection)
189 CALL section_release(subsection)
190
191 CALL create_potential_section(subsection)
192 CALL section_add_subsection(section, subsection)
193 CALL section_release(subsection)
194
195 CALL create_powell_section(subsection)
196 CALL section_add_subsection(section, subsection)
197 CALL section_release(subsection)
198
199 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 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 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 n_keywords=0, n_subsections=1, repeats=.false.)
216
217 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 print_level=silent_print_level, filename="__STD_OUT__")
223 CALL section_add_subsection(section, print_key)
224 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 print_level=medium_print_level, filename="__STD_OUT__")
230 CALL section_add_subsection(section, print_key)
231 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 print_level=high_print_level, filename="__STD_OUT__")
237 CALL section_add_subsection(section, print_key)
238 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 print_level=high_print_level, filename="__STD_OUT__")
244 CALL section_add_subsection(section, print_key)
245 CALL section_release(print_key)
246
247 ! Print key section
249 print_key, __location__, "FIT_DENSITY", &
250 description="Fit the total electronic density to a linear combination of Gaussian functions", &
251 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 default_i_val=40)
256 CALL section_add_keyword(print_key, keyword)
257 CALL keyword_release(keyword)
258 CALL section_add_subsection(section, print_key)
259 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 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 default_i_val=1)
270 CALL section_add_keyword(print_key, keyword)
271 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 default_i_val=4)
276 CALL section_add_keyword(print_key, keyword)
277 CALL keyword_release(keyword)
278 CALL section_add_subsection(section, print_key)
279 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 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 default_r_val=0.05_dp)
289 CALL section_add_keyword(print_key, keyword)
290 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 default_i_val=2)
295 CALL section_add_keyword(print_key, keyword)
296 CALL keyword_release(keyword)
297 CALL section_add_subsection(section, print_key)
298 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 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 default_r_val=0.05_dp)
309 CALL section_add_keyword(print_key, keyword)
310 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 default_i_val=3)
316 CALL section_add_keyword(print_key, keyword)
317 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 default_i_val=do_gapw_log)
328 CALL section_add_keyword(print_key, keyword)
329 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 default_i_val=400)
335 CALL section_add_keyword(print_key, keyword)
336 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 default_i_val=-1)
343 CALL section_add_keyword(print_key, keyword)
344 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 default_i_val=-1)
350 CALL section_add_keyword(print_key, keyword)
351 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 default_i_val=-1)
356 CALL section_add_keyword(print_key, keyword)
357 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 default_i_val=-1)
363 CALL section_add_keyword(print_key, keyword)
364 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 default_r_val=2.3_dp)
369 CALL section_add_keyword(print_key, keyword)
370 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 default_r_val=0.06_dp)
375 CALL section_add_keyword(print_key, keyword)
376 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 default_r_val=8.00_dp)
381 CALL section_add_keyword(print_key, keyword)
382 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 type_of_var=char_t, default_c_val="GRB", n_var=-1)
387 CALL section_add_keyword(print_key, keyword)
388 CALL keyword_release(keyword)
389 !
390 CALL section_add_subsection(section, print_key)
391 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 print_level=medium_print_level, filename="__STD_OUT__")
397 CALL section_add_subsection(section, print_key)
398 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 print_level=high_print_level, filename="__STD_OUT__")
404 CALL section_add_subsection(section, print_key)
405 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 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 usage="OVERLAP_CONDITION_NUMBER <logical>", type_of_var=logical_t, default_l_val=.false.)
414 CALL section_add_keyword(print_key, keyword)
415 CALL keyword_release(keyword)
416 CALL keyword_create(keyword, __location__, name="COMPLETENESS", &
417 description="Calculate a completeness estimate for the basis set.", &
418 usage="COMPLETENESS <logical>", type_of_var=logical_t, default_l_val=.false.)
419 CALL section_add_keyword(print_key, keyword)
420 CALL keyword_release(keyword)
421 CALL section_add_subsection(section, print_key)
422 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 print_level=medium_print_level, filename="__STD_OUT__")
428 CALL section_add_subsection(section, print_key)
429 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 print_level=medium_print_level, filename="__STD_OUT__")
435 CALL section_add_subsection(section, print_key)
436 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 print_level=high_print_level, filename="__STD_OUT__")
442 CALL section_add_subsection(section, print_key)
443 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 print_level=debug_print_level, filename="__STD_OUT__")
450 CALL section_add_subsection(section, print_key)
451 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 print_level=high_print_level, filename="__STD_OUT__")
457
458 NULLIFY (subsection)
459 CALL section_create(subsection, __location__, name="ADMM_BASIS", &
460 description="Section of basis set information for ADMM calculations.", &
461 n_keywords=0, n_subsections=0, repeats=.false.)
462 CALL atom_basis_section(subsection)
463 CALL section_add_subsection(print_key, subsection)
464 CALL section_release(subsection)
465 CALL section_add_subsection(section, print_key)
466 CALL section_release(print_key)
467
468 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 SUBROUTINE create_atom_aebasis_section(section)
476 TYPE(section_type), POINTER :: section
477
478 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 n_keywords=0, n_subsections=0, repeats=.false.)
482
483 CALL atom_basis_section(section)
484
485 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 SUBROUTINE create_atom_ppbasis_section(section)
493 TYPE(section_type), POINTER :: section
494
495 cpassert(.NOT. ASSOCIATED(section))
496 CALL section_create(section, __location__, name="PP_BASIS", &
497 description="Section of basis set information for pseudopotential calculations.", &
498 n_keywords=0, n_subsections=0, repeats=.false.)
499
500 CALL atom_basis_section(section)
501
502 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 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 cpassert(ASSOCIATED(section))
516 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 "/), &
528 enum_desc=s2a("Gaussian type orbitals", &
529 "Geometrical Gaussian type orbitals", &
530 "Contracted Gaussian type orbitals", &
531 "Slater-type orbitals", &
532 "Numerical basis type"))
533 CALL section_add_keyword(section, keyword)
534 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 default_i_val=-1)
540 CALL section_add_keyword(section, keyword)
541 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 default_i_val=-1)
547 CALL section_add_keyword(section, keyword)
548 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 default_i_val=0)
554 CALL section_add_keyword(section, keyword)
555 CALL keyword_release(keyword)
556
557 CALL keyword_create(keyword, __location__, name="S_EXPONENTS", &
558 description="Exponents for s functions", &
559 usage="S_EXPONENTS 1.0 2.0 ... ", n_var=-1, type_of_var=real_t)
560 CALL section_add_keyword(section, keyword)
561 CALL keyword_release(keyword)
562 CALL keyword_create(keyword, __location__, name="P_EXPONENTS", &
563 description="Exponents for p functions", &
564 usage="P_EXPONENTS 1.0 2.0 ... ", n_var=-1, type_of_var=real_t)
565 CALL section_add_keyword(section, keyword)
566 CALL keyword_release(keyword)
567 CALL keyword_create(keyword, __location__, name="D_EXPONENTS", &
568 description="Exponents for d functions", &
569 usage="D_EXPONENTS 1.0 2.0 ... ", n_var=-1, type_of_var=real_t)
570 CALL section_add_keyword(section, keyword)
571 CALL keyword_release(keyword)
572 CALL keyword_create(keyword, __location__, name="F_EXPONENTS", &
573 description="Exponents for f functions", &
574 usage="F_EXPONENTS 1.0 2.0 ... ", n_var=-1, type_of_var=real_t)
575 CALL section_add_keyword(section, keyword)
576 CALL keyword_release(keyword)
577
578 CALL keyword_create(keyword, __location__, name="S_QUANTUM_NUMBERS", &
579 description="Main quantum numbers for s functions", &
580 usage="S_QUANTUM_NUMBERS 1 2 ... ", n_var=-1, type_of_var=integer_t)
581 CALL section_add_keyword(section, keyword)
582 CALL keyword_release(keyword)
583 CALL keyword_create(keyword, __location__, name="P_QUANTUM_NUMBERS", &
584 description="Main quantum numbers for p functions", &
585 usage="P_QUANTUM_NUMBERS 2 3 ... ", n_var=-1, type_of_var=integer_t)
586 CALL section_add_keyword(section, keyword)
587 CALL keyword_release(keyword)
588 CALL keyword_create(keyword, __location__, name="D_QUANTUM_NUMBERS", &
589 description="Main quantum numbers for d functions", &
590 usage="D_QUANTUM_NUMBERS 3 4 ... ", n_var=-1, type_of_var=integer_t)
591 CALL section_add_keyword(section, keyword)
592 CALL keyword_release(keyword)
593 CALL keyword_create(keyword, __location__, name="F_QUANTUM_NUMBERS", &
594 description="Main quantum numbers for f functions", &
595 usage="F_QUANTUM_NUMBERS 4 5 ... ", n_var=-1, type_of_var=integer_t)
596 CALL section_add_keyword(section, keyword)
597 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 default_r_val=2.6_dp)
603 CALL section_add_keyword(section, keyword)
604 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 default_r_val=0.016_dp)
610 CALL section_add_keyword(section, keyword)
611 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 default_lc_val="BASIS_SET")
617 CALL section_add_keyword(section, keyword)
618 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 n_var=1)
625 CALL section_add_keyword(section, keyword)
626 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 default_i_val=do_gapw_log)
637 CALL section_add_keyword(section, keyword)
638 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 default_i_val=400)
644 CALL section_add_keyword(section, keyword)
645 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 default_r_val=1.e-12_dp)
651 CALL section_add_keyword(section, keyword)
652 CALL keyword_release(keyword)
653
654 NULLIFY (subsection)
655 CALL create_basis_section(subsection)
656 CALL section_add_subsection(section, subsection)
657 CALL section_release(subsection)
658
659 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 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 NULLIFY (subsection, keyword)
673 cpassert(.NOT. ASSOCIATED(section))
674 CALL section_create(section, __location__, name="METHOD", &
675 description="Section of information on method to use.", &
676 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 "/), &
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 "Restricted open-shell Hartree-Fock electronic structure method"))
698 CALL section_add_keyword(section, keyword)
699 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) "/), &
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 "Use Douglas-Kroll-Hess Hamiltonian of order 3"))
721 CALL section_add_keyword(section, keyword)
722 CALL keyword_release(keyword)
723
724 CALL create_xc_section(subsection)
725 CALL section_add_subsection(section, subsection)
726 CALL section_release(subsection)
727
728! ZMP creating zubsection for the zmp calculations
729 CALL create_zmp_section(subsection)
730 CALL section_add_subsection(section, subsection)
731 CALL section_release(subsection)
732
733 CALL create_external_vxc(subsection)
734 CALL section_add_subsection(section, subsection)
735 CALL section_release(subsection)
736
737 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 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 NULLIFY (subsection, keyword)
752 cpassert(.NOT. ASSOCIATED(section))
753 CALL section_create(section, __location__, name="ZMP", &
754 description="Section used to specify ZMP Potentials.", &
755 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 type_of_var=char_t, default_c_val="RHO_O.dat", n_var=-1)
761 CALL section_add_keyword(section, keyword)
762 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 usage="GRID_TOL <REAL>", default_r_val=1.e-12_dp)
767 CALL section_add_keyword(section, keyword)
768 CALL keyword_release(keyword)
769
770 CALL keyword_create(keyword, __location__, name="LAMBDA", &
771 description="Parameter used for the constraint in ZMP method", &
772 usage="LAMBDA <REAL>", default_r_val=10.0_dp)
773 CALL section_add_keyword(section, keyword)
774 CALL keyword_release(keyword)
775
776 CALL keyword_create(keyword, __location__, name="DM", &
777 description="read external density from density matrix", &
778 usage="DM <LOGICAL>", type_of_var=logical_t, default_l_val=.false.)
779 CALL section_add_keyword(section, keyword)
780 CALL keyword_release(keyword)
781
782 CALL create_zmp_restart_section(subsection)
783 CALL section_add_subsection(section, subsection)
784 CALL section_release(subsection)
785
786 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 SUBROUTINE create_zmp_restart_section(section)
795 TYPE(section_type), POINTER :: section
796
797 TYPE(keyword_type), POINTER :: keyword
798
799 NULLIFY (keyword)
800 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 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 type_of_var=char_t, default_c_val="RESTART.wfn", n_var=-1)
810 CALL section_add_keyword(section, keyword)
811 CALL keyword_release(keyword)
812
813 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 SUBROUTINE create_external_vxc(section)
822 TYPE(section_type), POINTER :: section
823
824 TYPE(keyword_type), POINTER :: keyword
825
826 NULLIFY (keyword)
827 cpassert(.NOT. ASSOCIATED(section))
828 CALL section_create(section, __location__, name="EXTERNAL_VXC", &
829 description="Section used to specify exernal VXC Potentials.", &
830 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 type_of_var=char_t, default_c_val="VXC.dat", n_var=-1)
836 CALL section_add_keyword(section, keyword)
837 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 usage="GRID_TOL <REAL>", default_r_val=1.e-12_dp)
842 CALL section_add_keyword(section, keyword)
843 CALL keyword_release(keyword)
844
845 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 SUBROUTINE create_optimization_section(section)
853 TYPE(section_type), POINTER :: section
854
855 TYPE(keyword_type), POINTER :: keyword
856
857 NULLIFY (keyword)
858 cpassert(.NOT. ASSOCIATED(section))
859 CALL section_create(section, __location__, name="OPTIMIZATION", &
860 description="Section of information on optimization thresholds and algorithms.", &
861 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 usage="MAX_ITER 50", default_i_val=200)
866 CALL section_add_keyword(section, keyword)
867 CALL keyword_release(keyword)
868
869 CALL keyword_create(keyword, __location__, name="EPS_SCF", &
870 description="Convergence criterion for SCF", &
871 usage="EPS_SCF 1.e-10", default_r_val=1.e-6_dp)
872 CALL section_add_keyword(section, keyword)
873 CALL keyword_release(keyword)
874
875 CALL keyword_create(keyword, __location__, name="DAMPING", &
876 description="Damping parameter for extrapolation method", &
877 usage="DAMPING 0.4", default_r_val=0.4_dp)
878 CALL section_add_keyword(section, keyword)
879 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 usage="EPS_DIIS 0.01", default_r_val=10000._dp)
884 CALL section_add_keyword(section, keyword)
885 CALL keyword_release(keyword)
886
887 CALL keyword_create(keyword, __location__, name="N_DIIS", &
888 description="Maximum number of DIIS vectors", &
889 usage="N_DIIS 6", default_i_val=5)
890 CALL section_add_keyword(section, keyword)
891 CALL keyword_release(keyword)
892
893 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 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 NULLIFY (keyword)
907 cpassert(.NOT. ASSOCIATED(section))
908 CALL section_create(section, __location__, name="POTENTIAL", &
909 description="Section of information on potential.", &
910 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 "Use a smooth barrier potential: a*F[R-c)/b]"))
923 CALL section_add_keyword(section, keyword)
924 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 repeats=.false., n_var=-1)
932 CALL section_add_keyword(section, keyword)
933 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 "/), &
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 "Use ECP semi-local pseudopotentials"))
950 CALL section_add_keyword(section, keyword)
951 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 default_lc_val="POTENTIAL")
957 CALL section_add_keyword(section, keyword)
958 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 usage="POTENTIAL_NAME <PSEUDO-POTENTIAL-NAME>", default_c_val=" ", n_var=1)
964 CALL section_add_keyword(section, keyword)
965 CALL keyword_release(keyword)
966
967 NULLIFY (subsection)
968 CALL create_gthpotential_section(subsection)
969 CALL section_add_subsection(section, subsection)
970 CALL section_release(subsection)
971
972 NULLIFY (subsection)
973 CALL create_ecp_section(subsection)
974 CALL section_add_subsection(section, subsection)
975 CALL section_release(subsection)
976
977 END SUBROUTINE create_potential_section
978
979! **************************************************************************************************
980!> \brief Creates the &GTH_POTENTIAL section
981!> \param section the section to create
982!> \author teo
983! **************************************************************************************************
984 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 n_keywords=1, n_subsections=0, repeats=.false.)
992 NULLIFY (keyword)
993 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
994 description="CP2K Pseudo Potential Standard Format (GTH, ALL or KG)", &
995 repeats=.true., type_of_var=lchar_t)
996 CALL section_add_keyword(section, keyword)
997 CALL keyword_release(keyword)
998 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 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 n_keywords=1, n_subsections=0, repeats=.false.)
1013 NULLIFY (keyword)
1014 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
1015 description="Effective Core Potentials definition", &
1016 repeats=.true., type_of_var=lchar_t)
1017 CALL section_add_keyword(section, keyword)
1018 CALL keyword_release(keyword)
1019 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 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 n_keywords=1, n_subsections=0, repeats=.false.)
1034 NULLIFY (keyword)
1035 CALL keyword_create(keyword, __location__, name="_DEFAULT_KEYWORD_", &
1036 description="CP2K Basis Set Standard Format", repeats=.true., &
1037 type_of_var=lchar_t)
1038 CALL section_add_keyword(section, keyword)
1039 CALL keyword_release(keyword)
1040 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 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 n_keywords=4, n_subsections=0, repeats=.false.)
1055
1056 NULLIFY (keyword)
1057 CALL keyword_create(keyword, __location__, name="ACCURACY", &
1058 description="Final accuracy requested in optimization (RHOEND)", &
1059 usage="ACCURACY 0.00001", &
1060 default_r_val=1.e-6_dp)
1061 CALL section_add_keyword(section, keyword)
1062 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 default_r_val=0.005_dp)
1068 CALL section_add_keyword(section, keyword)
1069 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 default_i_val=5000)
1075 CALL section_add_keyword(section, keyword)
1076 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 default_i_val=1)
1082 CALL section_add_keyword(section, keyword)
1083 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 default_r_val=0.75_dp)
1089 CALL section_add_keyword(section, keyword)
1090 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 default_r_val=1._dp)
1096 CALL section_add_keyword(section, keyword)
1097 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 default_r_val=1._dp)
1103 CALL section_add_keyword(section, keyword)
1104 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 default_r_val=1.0_dp)
1110 CALL section_add_keyword(section, keyword)
1111 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 default_r_val=1.0_dp)
1117 CALL section_add_keyword(section, keyword)
1118 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 default_r_val=1._dp)
1124 CALL section_add_keyword(section, keyword)
1125 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 n_var=-1, type_of_var=real_t, default_r_val=1.0_dp)
1131 CALL section_add_keyword(section, keyword)
1132 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 n_var=-1, type_of_var=real_t, default_r_val=1.0_dp)
1138 CALL section_add_keyword(section, keyword)
1139 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 default_r_val=1.0e-3_dp, unit_str="hartree")
1145 CALL section_add_keyword(section, keyword)
1146 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 default_r_val=1.0e-5_dp, unit_str="hartree")
1152 CALL section_add_keyword(section, keyword)
1153 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 default_r_val=1.0e-3_dp, unit_str="hartree")
1159 CALL section_add_keyword(section, keyword)
1160 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 default_r_val=1.0e-4_dp, unit_str="hartree")
1166 CALL section_add_keyword(section, keyword)
1167 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 default_r_val=0._dp)
1174 CALL section_add_keyword(section, keyword)
1175 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 default_r_val=0._dp)
1181 CALL section_add_keyword(section, keyword)
1182 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 default_r_val=1._dp)
1188 CALL section_add_keyword(section, keyword)
1189 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 default_r_val=1._dp, unit_str="hartree")
1195 CALL section_add_keyword(section, keyword)
1196 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 default_l_val=.false.)
1203 CALL section_add_keyword(section, keyword)
1204 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 default_l_val=.false.)
1211 CALL section_add_keyword(section, keyword)
1212 CALL keyword_release(keyword)
1213
1214 END SUBROUTINE create_powell_section
1215
1216! **************************************************************************************************
1217
1218END MODULE input_cp2k_atom
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public debug_print_level
integer, parameter, public medium_print_level
integer, parameter, public high_print_level
integer, parameter, public silent_print_level
subroutine, public cp_print_key_section_create(print_key_section, location, name, description, print_level, each_iter_names, each_iter_values, add_last, filename, common_iter_levels, citations, unit_str)
creates a print_key section
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public do_rhf_atom
integer, parameter, public do_gapw_gct
integer, parameter, public do_gapw_gcs
integer, parameter, public do_rks_atom
integer, parameter, public atom_pseudo_run
integer, parameter, public do_analytic
integer, parameter, public sgp_pseudo
integer, parameter, public do_dkh3_atom
integer, parameter, public atom_no_run
integer, parameter, public gth_pseudo
integer, parameter, public ecp_pseudo
integer, parameter, public do_nonrel_atom
integer, parameter, public do_dkh0_atom
integer, parameter, public no_conf
integer, parameter, public do_uhf_atom
integer, parameter, public upf_pseudo
integer, parameter, public contracted_gto
integer, parameter, public poly_conf
integer, parameter, public do_dkh2_atom
integer, parameter, public no_pseudo
integer, parameter, public do_uks_atom
integer, parameter, public barrier_conf
integer, parameter, public do_numeric
integer, parameter, public atom_basis_run
integer, parameter, public do_zoramp_atom
integer, parameter, public do_gapw_log
integer, parameter, public atom_energy_run
integer, parameter, public gaussian
integer, parameter, public do_dkh1_atom
integer, parameter, public do_rohf_atom
integer, parameter, public do_semi_analytic
integer, parameter, public geometrical_gto
integer, parameter, public numerical
integer, parameter, public do_sczoramp_atom
integer, parameter, public slater
builds the input structure for the ATOM module
subroutine, public create_atom_section(section)
Creates the input section for the atom code.
function that build the xc section of the input
subroutine, public create_xc_section(section)
creates the input section for the xc part
represents keywords in an input
subroutine, public keyword_release(keyword)
releases the given keyword (see doc/ReferenceCounting.html)
subroutine, public keyword_create(keyword, location, name, description, usage, type_of_var, n_var, repeats, variants, default_val, default_l_val, default_r_val, default_lc_val, default_c_val, default_i_val, default_l_vals, default_r_vals, default_c_vals, default_i_vals, lone_keyword_val, lone_keyword_l_val, lone_keyword_r_val, lone_keyword_c_val, lone_keyword_i_val, lone_keyword_l_vals, lone_keyword_r_vals, lone_keyword_c_vals, lone_keyword_i_vals, enum_c_vals, enum_i_vals, enum, enum_strict, enum_desc, unit_str, citations, deprecation_notice, removed)
creates a keyword object
objects that represent the structure of input sections and the data contained in an input section
subroutine, public section_create(section, location, name, description, n_keywords, n_subsections, repeats, citations)
creates a list of keywords
subroutine, public section_add_keyword(section, keyword)
adds a keyword to the given section
subroutine, public section_add_subsection(section, subsection)
adds a subsection to the given section
recursive subroutine, public section_release(section)
releases the given keyword list (see doc/ReferenceCounting.html)
a wrapper for basic fortran types.
integer, parameter, public real_t
integer, parameter, public lchar_t
integer, parameter, public logical_t
integer, parameter, public char_t
integer, parameter, public integer_t
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
Utilities for string manipulations.
represent a keyword in the input
represent a section of the input file