(git:97501a3)
Loading...
Searching...
No Matches
input_cp2k_as.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2025 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief function that build the active space section of the input
10!> \par History
11!> 10.2005 moved out of input_cp2k [fawzi]
12!> 07.2024 moved out of input_cp2k_dft [JGH]
13!> \author fawzi
14! **************************************************************************************************
22 USE input_constants, ONLY: &
36 USE input_val_types, ONLY: char_t,&
37 integer_t,&
38 lchar_t,&
39 logical_t,&
40 real_t
41 USE kinds, ONLY: dp
42 USE string_utilities, ONLY: s2a
43#include "./base/base_uses.f90"
44
45 IMPLICIT NONE
46 PRIVATE
47
48 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'input_cp2k_as'
49
51
52CONTAINS
53
54! **************************************************************************************************
55!> \brief Create CP2K input section for the calculation of an active space Hamiltonian
56!> \param section ...
57!> \par History:
58!> - Creation 06.04.2016
59!> \author JHU
60! **************************************************************************************************
61 SUBROUTINE create_active_space_section(section)
62
63 TYPE(section_type), POINTER :: section
64
65 TYPE(keyword_type), POINTER :: keyword
66 TYPE(section_type), POINTER :: print_key, subsection
67
68 cpassert(.NOT. ASSOCIATED(section))
69
70 CALL section_create(section, __location__, name="ACTIVE_SPACE", &
71 description="Define parameters and method to calculate an electronic active space", &
72 n_keywords=1, n_subsections=0, repeats=.false.)
73
74 NULLIFY (keyword, subsection, print_key)
75
76 CALL keyword_create(keyword, __location__, &
77 name="_SECTION_PARAMETERS_", &
78 description="Controls the activation of the ACTIVE_SPACE section", &
79 usage="&ACTIVE_SPACE ON", &
80 default_l_val=.false., &
81 lone_keyword_l_val=.true.)
82 CALL section_add_keyword(section, keyword)
83 CALL keyword_release(keyword)
84
85 CALL keyword_create(keyword, __location__, name="ACTIVE_ELECTRONS", &
86 description="The number of active electrons in the CAS space", &
87 usage="ACTIVE_ELECTRONS 4", n_var=1, default_i_val=-1, type_of_var=integer_t)
88 CALL section_add_keyword(section, keyword)
89 CALL keyword_release(keyword)
90
91 CALL keyword_create(keyword, __location__, name="ACTIVE_ORBITALS", &
92 description="The number of active orbitals defining the CAS space.", &
93 usage="ACTIVE_ORBITALS 2", n_var=1, default_i_val=-1, type_of_var=integer_t)
94 CALL section_add_keyword(section, keyword)
95 CALL keyword_release(keyword)
96
97 CALL keyword_create(keyword, __location__, name="ACTIVE_ORBITAL_INDICES", &
98 description="The indices of the active orbitals. Requires ORBITAL_SELECTION MANUAL!", &
99 usage="ACTIVE_ORBITAL_INDICES 2 3 {...}", n_var=-1, default_i_vals=(/-1/), &
100 type_of_var=integer_t)
101 CALL section_add_keyword(section, keyword)
102 CALL keyword_release(keyword)
103
104 CALL cp_print_key_section_create(print_key, __location__, "FCIDUMP", &
105 description="Controls the writing of a file in FCIDUMP format.", &
106 print_level=high_print_level, filename="")
107 CALL section_add_subsection(section, print_key)
108 CALL section_release(print_key)
109
110 CALL keyword_create(keyword, __location__, name="ORBITAL_SELECTION", &
111 description="Method used to select active space orbitals.", &
112 usage="ORBITAL_SELECTION CANONICAL", &
113 default_i_val=casci_canonical, &
114 enum_c_vals=s2a("CANONICAL", "WANNIER_PROJECTION", "MAO", "MANUAL"), &
116 enum_desc=s2a("Select orbitals using energy ordering of canoncial orbitals", &
117 "Select orbitals from projected Wannier functions", &
118 "Select orbitals from modified atomic orbitals", &
119 "Select orbitals manually via ACTIVE_ORBITAL_INDICES"))
120
121 CALL section_add_keyword(section, keyword)
122 CALL keyword_release(keyword)
123
124 CALL keyword_create(keyword, __location__, name="SUBSPACE_ATOM", &
125 description="Number of atom that defines the subspace to be projected on.", &
126 usage="SUBSPACE_ATOM x", default_i_val=-1, &
127 type_of_var=integer_t)
128 CALL section_add_keyword(section, keyword)
129 CALL keyword_release(keyword)
130
131 CALL keyword_create(keyword, __location__, name="SUBSPACE_SHELL", &
132 description="Shell definition for subsapce.", &
133 usage="SUBSPACE_SHELL 3d4s", default_c_val="X", &
134 type_of_var=char_t)
135 CALL section_add_keyword(section, keyword)
136 CALL keyword_release(keyword)
137
138 CALL keyword_create(keyword, __location__, name="SCF_EMBEDDING", &
139 description="Whether to turn on the self-consistent embedding scheme", &
140 default_l_val=.false., lone_keyword_l_val=.false.)
141 CALL section_add_keyword(section, keyword)
142 CALL keyword_release(keyword)
143
144 CALL keyword_create(keyword, __location__, name="QCSCHEMA", &
145 description="Name of the QCSchema file, may include a path", &
146 usage="QCSCHEMA <FILENAME>", &
147 type_of_var=lchar_t, repeats=.false., &
148 default_lc_val="")
149 CALL section_add_keyword(section, keyword)
150 CALL keyword_release(keyword)
151
152 CALL keyword_create(keyword, __location__, name="AS_SOLVER", &
153 description="The external active space solver for the embedding approach", &
154 usage="AS_SOLVER QISKIT", &
155 default_i_val=no_solver, &
156 enum_c_vals=s2a("NONE", "QISKIT"), &
157 enum_i_vals=(/no_solver, qiskit_solver/), &
158 enum_desc=s2a("NO solver, used to produce FCIDUMP/QCSchema files", &
159 "QISKIT active space solver"))
160 CALL section_add_keyword(section, keyword)
161 CALL keyword_release(keyword)
162
163 CALL keyword_create(keyword, __location__, name="EPS_ITER", &
164 description="Energy convergence threshold of the DFT embedding scheme.", &
165 usage="EPS_ITER 1.0E-6 ", type_of_var=real_t, &
166 default_r_val=1.0e-6_dp)
167 CALL section_add_keyword(section, keyword)
168 CALL keyword_release(keyword)
169
170 CALL keyword_create(keyword, __location__, name="ALPHA", &
171 description="Fraction of new density to be mixed with previous one in SCF embedding.", &
172 usage="ALPHA 0.25", type_of_var=real_t, &
173 default_r_val=0.4_dp)
174 CALL section_add_keyword(section, keyword)
175 CALL keyword_release(keyword)
176
177 CALL keyword_create(keyword, __location__, name="MAX_ITER", &
178 description="Max number of iterations for the DFT embedding scheme.", &
179 usage="MAX_ITER 50", type_of_var=integer_t, &
180 default_i_val=50)
181 CALL section_add_keyword(section, keyword)
182 CALL keyword_release(keyword)
183
184 CALL create_print_orb_section(subsection)
185 CALL section_add_subsection(section, subsection)
186 CALL section_release(subsection)
187
188 CALL create_eri_section(subsection)
189 CALL section_add_subsection(section, subsection)
190 CALL section_release(subsection)
191
192 CALL create_eri_gpw(subsection)
193 CALL section_add_subsection(section, subsection)
194 CALL section_release(subsection)
195
196 CALL create_localize_section(subsection)
197 CALL section_add_subsection(section, subsection)
198 CALL section_release(subsection)
199
200 CALL create_socket_section(subsection)
201 CALL section_add_subsection(section, subsection)
202 CALL section_release(subsection)
203
204 END SUBROUTINE create_active_space_section
205
206! **************************************************************************************************
207!> \brief ...
208!> \param section ...
209! **************************************************************************************************
210 SUBROUTINE create_socket_section(section)
211 TYPE(section_type), POINTER :: section
212
213 TYPE(keyword_type), POINTER :: keyword
214
215 cpassert(.NOT. ASSOCIATED(section))
216 CALL section_create(section, __location__, name="SOCKET", &
217 description="Parameters to set up the socket communicating to the external active space solver.", &
218 n_keywords=3, n_subsections=0, repeats=.false.)
219
220 NULLIFY (keyword)
221 CALL keyword_create(keyword, __location__, name="INET", &
222 description="Use an INET socket rather than a UNIX socket.", &
223 usage="INET <LOGICAL>", &
224 default_l_val=.false., lone_keyword_l_val=.true.)
225 CALL section_add_keyword(section, keyword)
226 CALL keyword_release(keyword)
227
228 CALL keyword_create(keyword, __location__, name="PORT", &
229 description="Port number for the socket client.", &
230 usage="port <INTEGER>", &
231 default_i_val=12345)
232 CALL section_add_keyword(section, keyword)
233 CALL keyword_release(keyword)
234
235 CALL keyword_create(keyword, __location__, name="HOST", &
236 description="Host name for the socket client.", &
237 usage="host <HOSTNAME>", &
238 default_c_val="embedding_socket")
239 CALL section_add_keyword(section, keyword)
240 CALL keyword_release(keyword)
241
242 END SUBROUTINE create_socket_section
243
244! **************************************************************************************************
245!> \brief ...
246!> \param section ...
247! **************************************************************************************************
248 SUBROUTINE create_print_orb_section(section)
249 TYPE(section_type), POINTER :: section
250
251 TYPE(keyword_type), POINTER :: keyword
252
253 cpassert(.NOT. ASSOCIATED(section))
254 CALL section_create(section, __location__, name="PRINT_ORBITAL_CUBES", &
255 description="Controls printing of active orbital cube files.", &
256 n_keywords=5, n_subsections=0, repeats=.false.)
257
258 NULLIFY (keyword)
259 CALL keyword_create(keyword, __location__, name="FILENAME", &
260 description="Body of Filename for the cube files.", &
261 usage="FILENAME {name}", default_c_val="ActiveOrbital", &
262 type_of_var=char_t)
263 CALL section_add_keyword(section, keyword)
264 CALL keyword_release(keyword)
265
266 CALL keyword_create(keyword, __location__, name="ALIST", &
267 description="List of alpha orbitals to be printed. -1 defaults to all values", &
268 usage="ALIST {1 2 3 ...}", n_var=-1, default_i_vals=(/-1/), &
269 lone_keyword_i_val=-1, type_of_var=integer_t)
270 CALL section_add_keyword(section, keyword)
271 CALL keyword_release(keyword)
272
273 CALL keyword_create(keyword, __location__, name="BLIST", &
274 description="List of beta orbitals to be printed. -1 defaults to all values", &
275 usage="BLIST {1 2 3 ...}", n_var=-1, default_i_vals=(/-1/), &
276 lone_keyword_i_val=-1, type_of_var=integer_t)
277 CALL section_add_keyword(section, keyword)
278 CALL keyword_release(keyword)
279
280 CALL keyword_create(keyword, __location__, name="STRIDE", &
281 description="The stride (X,Y,Z) used to write the cube file"// &
282 " (larger values result in smaller cube files)."// &
283 " You can provide 3 numbers (for X,Y,Z) or 1 number valid for all components", &
284 usage="STRIDE {2 2 2}", n_var=-1, default_i_vals=(/2, 2, 2/), &
285 type_of_var=integer_t)
286 CALL section_add_keyword(section, keyword)
287 CALL keyword_release(keyword)
288
289 CALL keyword_create(keyword, __location__, name="STOP_AFTER_CUBES", &
290 description="Whether to stop the computation after printing the cubes.", &
291 default_l_val=.false., lone_keyword_l_val=.false.)
292 CALL section_add_keyword(section, keyword)
293 CALL keyword_release(keyword)
294
295 END SUBROUTINE create_print_orb_section
296
297! **************************************************************************************************
298!> \brief ...
299!> \param section ...
300! **************************************************************************************************
301 SUBROUTINE create_eri_section(section)
302 TYPE(section_type), POINTER :: section
303
304 TYPE(keyword_type), POINTER :: keyword
305
306 cpassert(.NOT. ASSOCIATED(section))
307 CALL section_create(section, __location__, name="ERI", &
308 description="Parameters for the electron repulsion integrals.", &
309 n_keywords=5, n_subsections=0, repeats=.false.)
310
311 NULLIFY (keyword)
312 CALL keyword_create(keyword, __location__, name="METHOD", &
313 description="Method used in ERI calculation.", &
314 usage="METHOD FULL_GPW", &
315 enum_c_vals=s2a("FULL_GPW", "GPW_HALF_TRANSFORM"), &
316 enum_i_vals=(/eri_method_full_gpw, eri_method_gpw_ht/), &
317 enum_desc=s2a("Use the GPW approach with MOs", &
318 "Use the GPW approach for half-transformed MO ERIs"), &
319 default_i_val=eri_method_full_gpw)
320 CALL section_add_keyword(section, keyword)
321 CALL keyword_release(keyword)
322
323 CALL keyword_create(keyword, __location__, name="OPERATOR", &
324 description="Operator used in ERI calculation.", &
325 usage="OPERATOR LONGRANGE", &
326 enum_c_vals=s2a("COULOMB", "YUKAWA", "LONGRANGE", &
327 "SHORTRANGE", "GAUSSIAN", "TRUNCATED", "LR_TRUNC"), &
331 enum_desc=s2a("Coulomb operator: 1/r", &
332 "Yukawa operator: exp(-omega*R)/R", &
333 "Longrange operator: erf(omega*R)/R", &
334 "Shortrange operator: erfc(omega*R)/R", &
335 "Gaussian operator: exp(-omega*R2)/R", &
336 "Truncated Coulomb operator: if (R < R_c) 1/R else 0)", &
337 "Truncated longrange operator: if (R < R_c) erf(omega*R)/R else 0"), &
338 default_i_val=eri_operator_coulomb)
339 CALL section_add_keyword(section, keyword)
340 CALL keyword_release(keyword)
341
342 CALL keyword_create(keyword, __location__, name="PERIODICITY", &
343 description="Periodicity used for operators in ERI calclulation.", &
344 usage="PERIODICITY 1 1 1", n_var=-1, default_i_vals=(/0, 0, 0/), &
345 type_of_var=integer_t)
346 CALL section_add_keyword(section, keyword)
347 CALL keyword_release(keyword)
348
349 CALL keyword_create(keyword, __location__, name="OMEGA", &
350 description="Range-separation parameter for ERI operator.", &
351 usage="OMEGA 0.25", type_of_var=real_t, &
352 default_r_val=0.4_dp)
353 CALL section_add_keyword(section, keyword)
354 CALL keyword_release(keyword)
355
356 CALL keyword_create(keyword, __location__, name="CUTOFF_RADIUS", &
357 description="Cutoff radius (in Angstroms) for the truncated 1/r and "// &
358 "longrange potentials. "// &
359 "Only valid when doing truncated calculations.", &
360 usage="CUTOFF_RADIUS 10.0", type_of_var=real_t, &
361 unit_str="angstrom", default_r_val=0.0_dp)
362 CALL section_add_keyword(section, keyword)
363 CALL keyword_release(keyword)
364
365 CALL keyword_create( &
366 keyword, __location__, name="EPS_INTEGRAL", &
367 description="Accuracy of ERIs that will be stored.", &
368 usage="EPS_INTEGRAL 1.0E-10 ", type_of_var=real_t, &
369 default_r_val=1.0e-12_dp)
370 CALL section_add_keyword(section, keyword)
371 CALL keyword_release(keyword)
372
373 END SUBROUTINE create_eri_section
374
375! **************************************************************************************************
376!> \brief ...
377!> \param section ...
378! **************************************************************************************************
379 SUBROUTINE create_eri_gpw(section)
380 TYPE(section_type), POINTER :: section
381
382 TYPE(keyword_type), POINTER :: keyword
383
384 cpassert(.NOT. ASSOCIATED(section))
385 CALL section_create(section, __location__, name="ERI_GPW", &
386 description="Parameters for the GPW approach to electron repulsion integrals.", &
387 n_keywords=5, n_subsections=0, repeats=.false.)
388
389 NULLIFY (keyword)
390 CALL keyword_create(keyword, __location__, name="EPS_GRID", &
391 description="Determines a threshold for the GPW based integration", &
392 usage="EPS_GRID 1.0E-9 ", type_of_var=real_t, &
393 default_r_val=1.0e-8_dp)
394 CALL section_add_keyword(section, keyword)
395 CALL keyword_release(keyword)
396
397 CALL keyword_create(keyword, __location__, name="EPS_FILTER", &
398 description="Determines a threshold for the sparse matrix multiplications if METHOD "// &
399 "GPW_HALF_TRANSFORM is used", &
400 usage="EPS_FILTER 1.0E-9 ", type_of_var=real_t, &
401 default_r_val=1.0e-9_dp)
402 CALL section_add_keyword(section, keyword)
403 CALL keyword_release(keyword)
404
405 CALL keyword_create(keyword, __location__, name="CUTOFF", &
406 description="The cutoff of the finest grid level in the GPW integration.", &
407 usage="CUTOFF 300", type_of_var=real_t, &
408 default_r_val=300.0_dp)
409 CALL section_add_keyword(section, keyword)
410 CALL keyword_release(keyword)
411
412 CALL keyword_create(keyword, __location__, name="REL_CUTOFF", &
413 variants=(/"RELATIVE_CUTOFF"/), &
414 description="Determines the grid at which a Gaussian is mapped.", &
415 usage="REL_CUTOFF 50", type_of_var=real_t, &
416 default_r_val=50.0_dp)
417 CALL section_add_keyword(section, keyword)
418 CALL keyword_release(keyword)
419
420 CALL keyword_create(keyword, __location__, name="STORE_WFN", &
421 variants=(/"STORE_WAVEFUNCTION"/), &
422 description="Store wavefunction in real space representation for integration.", &
423 usage="STORE_WFN T", type_of_var=logical_t, &
424 default_l_val=.true., lone_keyword_l_val=.true.)
425 CALL section_add_keyword(section, keyword)
426 CALL keyword_release(keyword)
427
428 CALL keyword_create(keyword, __location__, name="GROUP_SIZE", &
429 description="Sets the size of a subgroup for ERI calculation, "// &
430 "each of which with a full set of work grids, arrays or orbitals "// &
431 "depending on the method of grids (work grids, arrays, orbitals). "// &
432 "Small numbers reduce communication but increase the memory demands. "// &
433 "A negative number indicates all processes (default).", &
434 usage="GROUP_SIZE 2", type_of_var=integer_t, &
435 default_i_val=-1)
436 CALL section_add_keyword(section, keyword)
437 CALL keyword_release(keyword)
438
439 CALL keyword_create(keyword, __location__, name="PRINT_LEVEL", &
440 variants=(/"IOLEVEL"/), &
441 description="How much output is written by the individual groups.", &
442 usage="PRINT_LEVEL HIGH", &
443 default_i_val=silent_print_level, enum_c_vals= &
444 s2a("SILENT", "LOW", "MEDIUM", "HIGH", "DEBUG"), &
445 enum_desc=s2a("Almost no output", &
446 "Little output", "Quite some output", "Lots of output", &
447 "Everything is written out, useful for debugging purposes only"), &
450 CALL section_add_keyword(section, keyword)
451 CALL keyword_release(keyword)
452
453 END SUBROUTINE create_eri_gpw
454
455END MODULE input_cp2k_as
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
integer, parameter, public debug_print_level
integer, parameter, public low_print_level
integer, parameter, public medium_print_level
integer, parameter, public high_print_level
integer, parameter, public 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 eri_operator_erf
integer, parameter, public qiskit_solver
integer, parameter, public no_solver
integer, parameter, public wannier_projection
integer, parameter, public mao_projection
integer, parameter, public eri_method_full_gpw
integer, parameter, public casci_canonical
integer, parameter, public manual_selection
integer, parameter, public eri_operator_gaussian
integer, parameter, public eri_method_gpw_ht
integer, parameter, public eri_operator_erfc
integer, parameter, public gaussian
integer, parameter, public eri_operator_trunc
integer, parameter, public eri_operator_coulomb
integer, parameter, public eri_operator_yukawa
integer, parameter, public eri_operator_lr_trunc
function that build the active space section of the input
subroutine, public create_active_space_section(section)
Create CP2K input section for the calculation of an active space Hamiltonian.
subroutine, public create_localize_section(section)
parameters fo the localization of wavefunctions
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, deprecation_notice)
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