(git:374b731)
Loading...
Searching...
No Matches
almo_scf_env_methods.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 almo_scf_env methods
10!> \par History
11!> 2016.12 created [Rustam Z Khaliullin]
12!> \author Rustam Z Khaliullin
13! **************************************************************************************************
15
19 USE input_constants, ONLY: &
28 USE kinds, ONLY: dp
32#include "./base/base_uses.f90"
33
34 IMPLICIT NONE
35
36 PRIVATE
37
38 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'almo_scf_env_methods'
39
40 PUBLIC :: almo_scf_env_create
41
42CONTAINS
43
44! **************************************************************************************************
45!> \brief Creation and basic initialization of the almo environment
46!> \param qs_env ...
47!> \par History
48!> 2016.11 created [Rustam Z Khaliullin]
49!> \author Rustam Z Khaliullin
50! **************************************************************************************************
51 SUBROUTINE almo_scf_env_create(qs_env)
52 TYPE(qs_environment_type), POINTER :: qs_env
53
54 CHARACTER(len=*), PARAMETER :: routinen = 'almo_scf_env_create'
55
56 INTEGER :: handle, nallocate
57 TYPE(almo_scf_env_type), POINTER :: almo_scf_env
58 TYPE(dft_control_type), POINTER :: dft_control
59 TYPE(section_vals_type), POINTER :: input
60
61 CALL timeset(routinen, handle)
62
63 ALLOCATE (almo_scf_env)
64
65 ! get basic quantities from the qs_env
66 CALL get_qs_env(qs_env, input=input, dft_control=dft_control)
67
68 ! parse the almo_scf section and set appropriate quantities
69 CALL almo_scf_init_read_write_input(input, almo_scf_env)
70
71 ! set up the buffer for the history of matrices
72 almo_scf_env%nspins = dft_control%nspins
73 almo_scf_env%almo_history%nstore = almo_scf_env%almo_extrapolation_order
74 almo_scf_env%almo_history%istore = 0
75 ! do not allocate zero
76 nallocate = max(1, almo_scf_env%almo_extrapolation_order)
77 ALLOCATE (almo_scf_env%almo_history%matrix_p_up_down(almo_scf_env%nspins, nallocate))
78 ALLOCATE (almo_scf_env%almo_history%matrix_t(almo_scf_env%nspins))
79 almo_scf_env%xalmo_history%nstore = almo_scf_env%xalmo_extrapolation_order
80 almo_scf_env%xalmo_history%istore = 0
81 nallocate = max(1, almo_scf_env%xalmo_extrapolation_order)
82 ALLOCATE (almo_scf_env%xalmo_history%matrix_p_up_down(almo_scf_env%nspins, nallocate))
83 !ALLOCATE (almo_scf_env%xalmo_history%matrix_x(almo_scf_env%nspins, nallocate))
84 ALLOCATE (almo_scf_env%xalmo_history%matrix_t(almo_scf_env%nspins))
85
86 ! put almo_scf_env in qs_env
87 CALL set_qs_env(qs_env, almo_scf_env=almo_scf_env)
88
89 CALL timestop(handle)
90
91 END SUBROUTINE almo_scf_env_create
92
93! **************************************************************************************************
94!> \brief Parses the ALMO input section
95!> \param input ...
96!> \param almo_scf_env ...
97!> \par History
98!> 2011.05 created [Rustam Z Khaliullin]
99!> \author Rustam Z Khaliullin
100! **************************************************************************************************
101 SUBROUTINE almo_scf_init_read_write_input(input, almo_scf_env)
102 TYPE(section_vals_type), POINTER :: input
103 TYPE(almo_scf_env_type), INTENT(INOUT) :: almo_scf_env
104
105 CHARACTER(len=*), PARAMETER :: routinen = 'almo_scf_init_read_write_input'
106
107 INTEGER :: handle
108 TYPE(section_vals_type), POINTER :: almo_analysis_section, almo_opt_diis_section, &
109 almo_opt_pcg_section, almo_opt_trustr_section, almo_scf_section, matrix_iterate_section, &
110 nlmo_opt_pcg_section, penalty_section, xalmo_opt_newton_pcg_section, &
111 xalmo_opt_pcg_section, xalmo_opt_trustr_section
112
113 CALL timeset(routinen, handle)
114
115 almo_scf_section => section_vals_get_subs_vals(input, "DFT%ALMO_SCF")
116 almo_opt_diis_section => section_vals_get_subs_vals(almo_scf_section, &
117 "ALMO_OPTIMIZER_DIIS")
118 almo_opt_pcg_section => section_vals_get_subs_vals(almo_scf_section, &
119 "ALMO_OPTIMIZER_PCG")
120 almo_opt_trustr_section => section_vals_get_subs_vals(almo_scf_section, &
121 "ALMO_OPTIMIZER_TRUSTR")
122 xalmo_opt_pcg_section => section_vals_get_subs_vals(almo_scf_section, &
123 "XALMO_OPTIMIZER_PCG")
124 xalmo_opt_trustr_section => section_vals_get_subs_vals(almo_scf_section, &
125 "XALMO_OPTIMIZER_TRUSTR")
126 nlmo_opt_pcg_section => section_vals_get_subs_vals(almo_scf_section, &
127 "NLMO_OPTIMIZER_PCG")
128 almo_analysis_section => section_vals_get_subs_vals(almo_scf_section, "ANALYSIS")
129 xalmo_opt_newton_pcg_section => section_vals_get_subs_vals(xalmo_opt_pcg_section, &
130 "XALMO_NEWTON_PCG_SOLVER")
131 matrix_iterate_section => section_vals_get_subs_vals(almo_scf_section, &
132 "MATRIX_ITERATE")
133
134 ! read user input
135 ! common ALMO options
136 CALL section_vals_val_get(almo_scf_section, "EPS_FILTER", &
137 r_val=almo_scf_env%eps_filter)
138 CALL section_vals_val_get(almo_scf_section, "ALMO_SCF_GUESS", &
139 i_val=almo_scf_env%almo_scf_guess)
140 CALL section_vals_val_get(almo_scf_section, "ALMO_ALGORITHM", &
141 i_val=almo_scf_env%almo_update_algorithm)
142 CALL section_vals_val_get(almo_scf_section, "XALMO_ALGORITHM", &
143 i_val=almo_scf_env%xalmo_update_algorithm)
144 CALL section_vals_val_get(almo_scf_section, "XALMO_TRIAL_WF", &
145 i_val=almo_scf_env%xalmo_trial_wf)
146 CALL section_vals_val_get(almo_scf_section, "MO_OVERLAP_INV_ALG", &
147 i_val=almo_scf_env%sigma_inv_algorithm)
148 CALL section_vals_val_get(almo_scf_section, "DELOCALIZE_METHOD", &
149 i_val=almo_scf_env%deloc_method)
150 CALL section_vals_val_get(almo_scf_section, "XALMO_R_CUTOFF_FACTOR", &
151 r_val=almo_scf_env%quencher_r0_factor)
152 CALL section_vals_val_get(almo_scf_section, "ALMO_EXTRAPOLATION_ORDER", &
153 i_val=almo_scf_env%almo_extrapolation_order)
154 almo_scf_env%almo_extrapolation_order = max(0, almo_scf_env%almo_extrapolation_order)
155 CALL section_vals_val_get(almo_scf_section, "XALMO_EXTRAPOLATION_ORDER", &
156 i_val=almo_scf_env%xalmo_extrapolation_order)
157 almo_scf_env%xalmo_extrapolation_order = max(0, almo_scf_env%xalmo_extrapolation_order)
158 CALL section_vals_val_get(almo_scf_section, "RETURN_ORTHOGONALIZED_MOS", &
159 l_val=almo_scf_env%return_orthogonalized_mos)
160 CALL section_vals_val_get(almo_scf_section, "CONSTRUCT_NLMOS", &
161 l_val=almo_scf_env%construct_nlmos)
162
163 CALL section_vals_val_get(matrix_iterate_section, "EPS_LANCZOS", &
164 r_val=almo_scf_env%eps_lanczos)
165 CALL section_vals_val_get(matrix_iterate_section, "ORDER_LANCZOS", &
166 i_val=almo_scf_env%order_lanczos)
167 CALL section_vals_val_get(matrix_iterate_section, "MAX_ITER_LANCZOS", &
168 i_val=almo_scf_env%max_iter_lanczos)
169 CALL section_vals_val_get(matrix_iterate_section, "EPS_TARGET_FACTOR", &
170 r_val=almo_scf_env%matrix_iter_eps_error_factor)
171
172 ! optimizers
173 CALL section_vals_val_get(almo_opt_diis_section, "EPS_ERROR", &
174 r_val=almo_scf_env%opt_block_diag_diis%eps_error)
175 CALL section_vals_val_get(almo_opt_diis_section, "MAX_ITER", &
176 i_val=almo_scf_env%opt_block_diag_diis%max_iter)
177 CALL section_vals_val_get(almo_opt_diis_section, "EPS_ERROR_EARLY", &
178 r_val=almo_scf_env%opt_block_diag_diis%eps_error_early)
179 CALL section_vals_val_get(almo_opt_diis_section, "MAX_ITER_EARLY", &
180 i_val=almo_scf_env%opt_block_diag_diis%max_iter_early)
181 CALL section_vals_val_get(almo_opt_diis_section, "N_DIIS", &
182 i_val=almo_scf_env%opt_block_diag_diis%ndiis)
183
184 CALL section_vals_val_get(almo_opt_pcg_section, "EPS_ERROR", &
185 r_val=almo_scf_env%opt_block_diag_pcg%eps_error)
186 CALL section_vals_val_get(almo_opt_pcg_section, "MAX_ITER", &
187 i_val=almo_scf_env%opt_block_diag_pcg%max_iter)
188 CALL section_vals_val_get(almo_opt_pcg_section, "EPS_ERROR_EARLY", &
189 r_val=almo_scf_env%opt_block_diag_pcg%eps_error_early)
190 CALL section_vals_val_get(almo_opt_pcg_section, "MAX_ITER_EARLY", &
191 i_val=almo_scf_env%opt_block_diag_pcg%max_iter_early)
192 CALL section_vals_val_get(almo_opt_pcg_section, "MAX_ITER_OUTER_LOOP", &
193 i_val=almo_scf_env%opt_block_diag_pcg%max_iter_outer_loop)
194 CALL section_vals_val_get(almo_opt_pcg_section, "LIN_SEARCH_EPS_ERROR", &
195 r_val=almo_scf_env%opt_block_diag_pcg%lin_search_eps_error)
196 CALL section_vals_val_get(almo_opt_pcg_section, "LIN_SEARCH_STEP_SIZE_GUESS", &
197 r_val=almo_scf_env%opt_block_diag_pcg%lin_search_step_size_guess)
198 CALL section_vals_val_get(almo_opt_pcg_section, "PRECOND_FILTER_THRESHOLD", &
199 r_val=almo_scf_env%opt_block_diag_pcg%neglect_threshold)
200 CALL section_vals_val_get(almo_opt_pcg_section, "CONJUGATOR", &
201 i_val=almo_scf_env%opt_block_diag_pcg%conjugator)
202 CALL section_vals_val_get(almo_opt_pcg_section, "PRECONDITIONER", &
203 i_val=almo_scf_env%opt_block_diag_pcg%preconditioner)
204
205 CALL section_vals_val_get(almo_opt_trustr_section, "EPS_ERROR", &
206 r_val=almo_scf_env%opt_block_diag_trustr%eps_error)
207 CALL section_vals_val_get(almo_opt_trustr_section, "MAX_ITER", &
208 i_val=almo_scf_env%opt_block_diag_trustr%max_iter)
209 CALL section_vals_val_get(almo_opt_trustr_section, "ALGORITHM", &
210 i_val=almo_scf_env%opt_block_diag_trustr%trustr_algorithm)
211 CALL section_vals_val_get(almo_opt_trustr_section, "EPS_ERROR_EARLY", &
212 r_val=almo_scf_env%opt_block_diag_trustr%eps_error_early)
213 CALL section_vals_val_get(almo_opt_trustr_section, "MAX_ITER_EARLY", &
214 i_val=almo_scf_env%opt_block_diag_trustr%max_iter_early)
215 CALL section_vals_val_get(almo_opt_trustr_section, "MAX_ITER_OUTER_LOOP", &
216 i_val=almo_scf_env%opt_block_diag_trustr%max_iter_outer_loop)
217 CALL section_vals_val_get(almo_opt_trustr_section, "ETA", &
218 r_val=almo_scf_env%opt_block_diag_trustr%rho_do_not_update)
219 almo_scf_env%opt_block_diag_trustr%rho_do_not_update = &
220 min(max(almo_scf_env%opt_block_diag_trustr%rho_do_not_update, 0.0_dp), 0.25_dp)
221 CALL section_vals_val_get(almo_opt_trustr_section, "MODEL_GRAD_NORM_RATIO", &
222 r_val=almo_scf_env%opt_block_diag_trustr%model_grad_norm_ratio)
223 CALL section_vals_val_get(almo_opt_trustr_section, "INITIAL_TRUST_RADIUS", &
224 r_val=almo_scf_env%opt_block_diag_trustr%initial_trust_radius)
225 CALL section_vals_val_get(almo_opt_trustr_section, "MAX_TRUST_RADIUS", &
226 r_val=almo_scf_env%opt_block_diag_trustr%max_trust_radius)
227 CALL section_vals_val_get(almo_opt_trustr_section, "CONJUGATOR", &
228 i_val=almo_scf_env%opt_block_diag_trustr%conjugator)
229 CALL section_vals_val_get(almo_opt_trustr_section, "PRECONDITIONER", &
230 i_val=almo_scf_env%opt_block_diag_trustr%preconditioner)
231
232 CALL section_vals_val_get(xalmo_opt_trustr_section, "EPS_ERROR", &
233 r_val=almo_scf_env%opt_xalmo_trustr%eps_error)
234 CALL section_vals_val_get(xalmo_opt_trustr_section, "MAX_ITER", &
235 i_val=almo_scf_env%opt_xalmo_trustr%max_iter)
236 CALL section_vals_val_get(xalmo_opt_trustr_section, "ALGORITHM", &
237 i_val=almo_scf_env%opt_xalmo_trustr%trustr_algorithm)
238 CALL section_vals_val_get(xalmo_opt_trustr_section, "EPS_ERROR_EARLY", &
239 r_val=almo_scf_env%opt_xalmo_trustr%eps_error_early)
240 CALL section_vals_val_get(xalmo_opt_trustr_section, "MAX_ITER_EARLY", &
241 i_val=almo_scf_env%opt_xalmo_trustr%max_iter_early)
242 CALL section_vals_val_get(xalmo_opt_trustr_section, "MAX_ITER_OUTER_LOOP", &
243 i_val=almo_scf_env%opt_xalmo_trustr%max_iter_outer_loop)
244 CALL section_vals_val_get(xalmo_opt_trustr_section, "ETA", &
245 r_val=almo_scf_env%opt_xalmo_trustr%rho_do_not_update)
246 almo_scf_env%opt_xalmo_trustr%rho_do_not_update = &
247 min(max(almo_scf_env%opt_xalmo_trustr%rho_do_not_update, 0.0_dp), 0.25_dp)
248 CALL section_vals_val_get(xalmo_opt_trustr_section, "MODEL_GRAD_NORM_RATIO", &
249 r_val=almo_scf_env%opt_xalmo_trustr%model_grad_norm_ratio)
250 CALL section_vals_val_get(xalmo_opt_trustr_section, "INITIAL_TRUST_RADIUS", &
251 r_val=almo_scf_env%opt_xalmo_trustr%initial_trust_radius)
252 CALL section_vals_val_get(xalmo_opt_trustr_section, "MAX_TRUST_RADIUS", &
253 r_val=almo_scf_env%opt_xalmo_trustr%max_trust_radius)
254 CALL section_vals_val_get(xalmo_opt_trustr_section, "CONJUGATOR", &
255 i_val=almo_scf_env%opt_xalmo_trustr%conjugator)
256 CALL section_vals_val_get(xalmo_opt_trustr_section, "PRECONDITIONER", &
257 i_val=almo_scf_env%opt_xalmo_trustr%preconditioner)
258
259 CALL section_vals_val_get(xalmo_opt_pcg_section, "EPS_ERROR", &
260 r_val=almo_scf_env%opt_xalmo_pcg%eps_error)
261 CALL section_vals_val_get(xalmo_opt_pcg_section, "MAX_ITER", &
262 i_val=almo_scf_env%opt_xalmo_pcg%max_iter)
263 CALL section_vals_val_get(xalmo_opt_pcg_section, "EPS_ERROR_EARLY", &
264 r_val=almo_scf_env%opt_xalmo_pcg%eps_error_early)
265 CALL section_vals_val_get(xalmo_opt_pcg_section, "MAX_ITER_EARLY", &
266 i_val=almo_scf_env%opt_xalmo_pcg%max_iter_early)
267 CALL section_vals_val_get(xalmo_opt_pcg_section, "MAX_ITER_OUTER_LOOP", &
268 i_val=almo_scf_env%opt_xalmo_pcg%max_iter_outer_loop)
269 CALL section_vals_val_get(xalmo_opt_pcg_section, "LIN_SEARCH_EPS_ERROR", &
270 r_val=almo_scf_env%opt_xalmo_pcg%lin_search_eps_error)
271 CALL section_vals_val_get(xalmo_opt_pcg_section, "LIN_SEARCH_STEP_SIZE_GUESS", &
272 r_val=almo_scf_env%opt_xalmo_pcg%lin_search_step_size_guess)
273 CALL section_vals_val_get(xalmo_opt_pcg_section, "PRECOND_FILTER_THRESHOLD", &
274 r_val=almo_scf_env%opt_xalmo_pcg%neglect_threshold)
275 CALL section_vals_val_get(xalmo_opt_pcg_section, "CONJUGATOR", &
276 i_val=almo_scf_env%opt_xalmo_pcg%conjugator)
277 CALL section_vals_val_get(xalmo_opt_pcg_section, "PRECONDITIONER", &
278 i_val=almo_scf_env%opt_xalmo_pcg%preconditioner)
279
280 penalty_section => section_vals_get_subs_vals(nlmo_opt_pcg_section, "PENALTY")
281 CALL section_vals_val_get(nlmo_opt_pcg_section, "EPS_ERROR", &
282 r_val=almo_scf_env%opt_nlmo_pcg%eps_error)
283 CALL section_vals_val_get(nlmo_opt_pcg_section, "MAX_ITER", &
284 i_val=almo_scf_env%opt_nlmo_pcg%max_iter)
285 CALL section_vals_val_get(nlmo_opt_pcg_section, "EPS_ERROR_EARLY", &
286 r_val=almo_scf_env%opt_nlmo_pcg%eps_error_early)
287 CALL section_vals_val_get(nlmo_opt_pcg_section, "MAX_ITER_EARLY", &
288 i_val=almo_scf_env%opt_nlmo_pcg%max_iter_early)
289 CALL section_vals_val_get(nlmo_opt_pcg_section, "MAX_ITER_OUTER_LOOP", &
290 i_val=almo_scf_env%opt_nlmo_pcg%max_iter_outer_loop)
291 CALL section_vals_val_get(nlmo_opt_pcg_section, "LIN_SEARCH_EPS_ERROR", &
292 r_val=almo_scf_env%opt_nlmo_pcg%lin_search_eps_error)
293 CALL section_vals_val_get(nlmo_opt_pcg_section, "LIN_SEARCH_STEP_SIZE_GUESS", &
294 r_val=almo_scf_env%opt_nlmo_pcg%lin_search_step_size_guess)
295 CALL section_vals_val_get(nlmo_opt_pcg_section, "PRECOND_FILTER_THRESHOLD", &
296 r_val=almo_scf_env%opt_nlmo_pcg%neglect_threshold)
297 CALL section_vals_val_get(nlmo_opt_pcg_section, "CONJUGATOR", &
298 i_val=almo_scf_env%opt_nlmo_pcg%conjugator)
299 CALL section_vals_val_get(nlmo_opt_pcg_section, "PRECONDITIONER", &
300 i_val=almo_scf_env%opt_nlmo_pcg%preconditioner)
301 CALL section_vals_val_get(penalty_section, &
302 "OPERATOR", &
303 i_val=almo_scf_env%opt_nlmo_pcg%opt_penalty%operator_type)
304 CALL section_vals_val_get(penalty_section, &
305 "PENALTY_STRENGTH", &
306 r_val=almo_scf_env%opt_nlmo_pcg%opt_penalty%penalty_strength)
307 CALL section_vals_val_get(penalty_section, &
308 "PENALTY_STRENGTH_DECREASE_FACTOR", &
309 r_val=almo_scf_env%opt_nlmo_pcg%opt_penalty%penalty_strength_dec_factor)
310 CALL section_vals_val_get(penalty_section, &
311 "DETERMINANT_TOLERANCE", &
312 r_val=almo_scf_env%opt_nlmo_pcg%opt_penalty%determinant_tolerance)
313 CALL section_vals_val_get(penalty_section, &
314 "FINAL_DETERMINANT", &
315 r_val=almo_scf_env%opt_nlmo_pcg%opt_penalty%final_determinant)
316 CALL section_vals_val_get(penalty_section, &
317 "COMPACTIFICATION_FILTER_START", &
318 r_val=almo_scf_env%opt_nlmo_pcg%opt_penalty%compactification_filter_start)
319 CALL section_vals_val_get(penalty_section, &
320 "VIRTUAL_NLMOS", &
321 l_val=almo_scf_env%opt_nlmo_pcg%opt_penalty%virtual_nlmos)
322
323 CALL section_vals_val_get(xalmo_opt_newton_pcg_section, "EPS_ERROR", &
324 r_val=almo_scf_env%opt_xalmo_newton_pcg_solver%eps_error)
325 CALL section_vals_val_get(xalmo_opt_newton_pcg_section, "MAX_ITER", &
326 i_val=almo_scf_env%opt_xalmo_newton_pcg_solver%max_iter)
327 CALL section_vals_val_get(xalmo_opt_newton_pcg_section, "MAX_ITER_OUTER_LOOP", &
328 i_val=almo_scf_env%opt_xalmo_newton_pcg_solver%max_iter_outer_loop)
329 CALL section_vals_val_get(xalmo_opt_newton_pcg_section, "PRECONDITIONER", &
330 i_val=almo_scf_env%opt_xalmo_newton_pcg_solver%preconditioner)
331
332 CALL section_vals_val_get(almo_analysis_section, "_SECTION_PARAMETERS_", &
333 l_val=almo_scf_env%almo_analysis%do_analysis)
334 CALL section_vals_val_get(almo_analysis_section, "FROZEN_MO_ENERGY_TERM", &
335 i_val=almo_scf_env%almo_analysis%frozen_mo_energy_term)
336
337 !CALL section_vals_val_get(almo_scf_section,"DOMAIN_LAYOUT_AOS",&
338 ! i_val=almo_scf_env%domain_layout_aos)
339 !CALL section_vals_val_get(almo_scf_section,"DOMAIN_LAYOUT_MOS",&
340 ! i_val=almo_scf_env%domain_layout_mos)
341 !CALL section_vals_val_get(almo_scf_section,"MATRIX_CLUSTERING_AOS",&
342 ! i_val=almo_scf_env%mat_distr_aos)
343 !CALL section_vals_val_get(almo_scf_section,"MATRIX_CLUSTERING_MOS",&
344 ! i_val=almo_scf_env%mat_distr_mos)
345 !CALL section_vals_val_get(almo_scf_section,"CONSTRAINT_TYPE",&
346 ! i_val=almo_scf_env%constraint_type)
347 !CALL section_vals_val_get(almo_scf_section,"MU",&
348 ! r_val=almo_scf_env%mu)
349 !CALL section_vals_val_get(almo_scf_section,"FIXED_MU",&
350 ! l_val=almo_scf_env%fixed_mu)
351 !CALL section_vals_val_get(almo_scf_section,"EPS_USE_PREV_AS_GUESS",&
352 ! r_val=almo_scf_env%eps_prev_guess)
353 !CALL section_vals_val_get(almo_scf_section,"MIXING_FRACTION",&
354 ! r_val=almo_scf_env%mixing_fraction)
355 !CALL section_vals_val_get(almo_scf_section,"DELOC_CAYLEY_TENSOR_TYPE",&
356 ! i_val=almo_scf_env%deloc_cayley_tensor_type)
357 !CALL section_vals_val_get(almo_scf_section,"DELOC_CAYLEY_CONJUGATOR",&
358 ! i_val=almo_scf_env%deloc_cayley_conjugator)
359 !CALL section_vals_val_get(almo_scf_section,"DELOC_CAYLEY_MAX_ITER",&
360 ! i_val=almo_scf_env%deloc_cayley_max_iter)
361 !CALL section_vals_val_get(almo_scf_section,"DELOC_USE_OCC_ORBS",&
362 ! l_val=almo_scf_env%deloc_use_occ_orbs)
363 !CALL section_vals_val_get(almo_scf_section,"DELOC_CAYLEY_USE_VIRT_ORBS",&
364 ! l_val=almo_scf_env%deloc_cayley_use_virt_orbs)
365 !CALL section_vals_val_get(almo_scf_section,"DELOC_CAYLEY_LINEAR",&
366 ! l_val=almo_scf_env%deloc_cayley_linear)
367 !CALL section_vals_val_get(almo_scf_section,"DELOC_CAYLEY_EPS_CONVERGENCE",&
368 ! r_val=almo_scf_env%deloc_cayley_eps_convergence)
369 !CALL section_vals_val_get(almo_scf_section,"DELOC_CAYLEY_OCC_PRECOND",&
370 ! l_val=almo_scf_env%deloc_cayley_occ_precond)
371 !CALL section_vals_val_get(almo_scf_section,"DELOC_CAYLEY_VIR_PRECOND",&
372 ! l_val=almo_scf_env%deloc_cayley_vir_precond)
373 !CALL section_vals_val_get(almo_scf_section,"ALMO_UPDATE_ALGORITHM_BD",&
374 ! i_val=almo_scf_env%almo_update_algorithm)
375 !CALL section_vals_val_get(almo_scf_section,"DELOC_TRUNCATE_VIRTUALS",&
376 ! i_val=almo_scf_env%deloc_truncate_virt)
377 !CALL section_vals_val_get(almo_scf_section,"DELOC_VIRT_PER_DOMAIN",&
378 ! i_val=almo_scf_env%deloc_virt_per_domain)
379 !
380 !CALL section_vals_val_get(almo_scf_section,"OPT_K_EPS_CONVERGENCE",&
381 ! r_val=almo_scf_env%opt_k_eps_convergence)
382 !CALL section_vals_val_get(almo_scf_section,"OPT_K_MAX_ITER",&
383 ! i_val=almo_scf_env%opt_k_max_iter)
384 !CALL section_vals_val_get(almo_scf_section,"OPT_K_OUTER_MAX_ITER",&
385 ! i_val=almo_scf_env%opt_k_outer_max_iter)
386 !CALL section_vals_val_get(almo_scf_section,"OPT_K_TRIAL_STEP_SIZE",&
387 ! r_val=almo_scf_env%opt_k_trial_step_size)
388 !CALL section_vals_val_get(almo_scf_section,"OPT_K_CONJUGATOR",&
389 ! i_val=almo_scf_env%opt_k_conjugator)
390 !CALL section_vals_val_get(almo_scf_section,"OPT_K_TRIAL_STEP_SIZE_MULTIPLIER",&
391 ! r_val=almo_scf_env%opt_k_trial_step_size_multiplier)
392 !CALL section_vals_val_get(almo_scf_section,"OPT_K_CONJ_ITER_START",&
393 ! i_val=almo_scf_env%opt_k_conj_iter_start)
394 !CALL section_vals_val_get(almo_scf_section,"OPT_K_PREC_ITER_START",&
395 ! i_val=almo_scf_env%opt_k_prec_iter_start)
396 !CALL section_vals_val_get(almo_scf_section,"OPT_K_CONJ_ITER_FREQ_RESET",&
397 ! i_val=almo_scf_env%opt_k_conj_iter_freq)
398 !CALL section_vals_val_get(almo_scf_section,"OPT_K_PREC_ITER_FREQ_UPDATE",&
399 ! i_val=almo_scf_env%opt_k_prec_iter_freq)
400 !
401 !CALL section_vals_val_get(almo_scf_section,"QUENCHER_RADIUS_TYPE",&
402 ! i_val=almo_scf_env%quencher_radius_type)
403 !CALL section_vals_val_get(almo_scf_section,"QUENCHER_R0_FACTOR",&
404 ! r_val=almo_scf_env%quencher_r0_factor)
405 !CALL section_vals_val_get(almo_scf_section,"QUENCHER_R1_FACTOR",&
406 ! r_val=almo_scf_env%quencher_r1_factor)
407 !!CALL section_vals_val_get(almo_scf_section,"QUENCHER_R0_SHIFT",&
408 !! r_val=almo_scf_env%quencher_r0_shift)
409 !!
410 !!CALL section_vals_val_get(almo_scf_section,"QUENCHER_R1_SHIFT",&
411 !! r_val=almo_scf_env%quencher_r1_shift)
412 !!
413 !!almo_scf_env%quencher_r0_shift = cp_unit_to_cp2k(&
414 !! almo_scf_env%quencher_r0_shift,"angstrom")
415 !!almo_scf_env%quencher_r1_shift = cp_unit_to_cp2k(&
416 !! almo_scf_env%quencher_r1_shift,"angstrom")
417 !
418 !CALL section_vals_val_get(almo_scf_section,"QUENCHER_AO_OVERLAP_0",&
419 ! r_val=almo_scf_env%quencher_s0)
420 !CALL section_vals_val_get(almo_scf_section,"QUENCHER_AO_OVERLAP_1",&
421 ! r_val=almo_scf_env%quencher_s1)
422
423 !CALL section_vals_val_get(almo_scf_section,"ENVELOPE_AMPLITUDE",&
424 ! r_val=almo_scf_env%envelope_amplitude)
425
426 !! how to read lists
427 !CALL section_vals_val_get(almo_scf_section,"INT_LIST01", &
428 ! n_rep_val=n_rep)
429 !counter_i = 0
430 !DO k = 1,n_rep
431 ! CALL section_vals_val_get(almo_scf_section,"INT_LIST01",&
432 ! i_rep_val=k,i_vals=tmplist)
433 ! DO jj = 1,SIZE(tmplist)
434 ! counter_i=counter_i+1
435 ! almo_scf_env%charge_of_domain(counter_i)=tmplist(jj)
436 ! ENDDO
437 !ENDDO
438
439 almo_scf_env%domain_layout_aos = almo_domain_layout_molecular
440 almo_scf_env%domain_layout_mos = almo_domain_layout_molecular
441 almo_scf_env%mat_distr_aos = almo_mat_distr_molecular
442 almo_scf_env%mat_distr_mos = almo_mat_distr_molecular
443
444 almo_scf_env%constraint_type = almo_constraint_distance
445 almo_scf_env%mu = -0.1_dp
446 almo_scf_env%fixed_mu = .false.
447 almo_scf_env%mixing_fraction = 0.45_dp
448 almo_scf_env%eps_prev_guess = almo_scf_env%eps_filter/1000.0_dp
449
450 almo_scf_env%deloc_cayley_tensor_type = tensor_orthogonal
451 almo_scf_env%deloc_cayley_conjugator = cg_hager_zhang
452 almo_scf_env%deloc_cayley_max_iter = 100
453 almo_scf_env%deloc_use_occ_orbs = .true.
454 almo_scf_env%deloc_cayley_use_virt_orbs = .false.
455 almo_scf_env%deloc_cayley_linear = .false.
456 almo_scf_env%deloc_cayley_eps_convergence = 1.0e-6_dp
457 almo_scf_env%deloc_cayley_occ_precond = .true.
458 almo_scf_env%deloc_cayley_vir_precond = .true.
459 almo_scf_env%deloc_truncate_virt = virt_full
460 almo_scf_env%deloc_virt_per_domain = -1
461
462 almo_scf_env%opt_k_eps_convergence = 1.0e-5_dp
463 almo_scf_env%opt_k_max_iter = 100
464 almo_scf_env%opt_k_outer_max_iter = 1
465 almo_scf_env%opt_k_trial_step_size = 0.05_dp
466 almo_scf_env%opt_k_conjugator = cg_hager_zhang
467 almo_scf_env%opt_k_trial_step_size_multiplier = 1.05_dp
468 almo_scf_env%opt_k_conj_iter_start = 0
469 almo_scf_env%opt_k_prec_iter_start = 0
470 almo_scf_env%opt_k_conj_iter_freq = 10000000
471 almo_scf_env%opt_k_prec_iter_freq = 10000000
472
473 almo_scf_env%quencher_radius_type = do_bondparm_vdw
474 almo_scf_env%quencher_r1_factor = almo_scf_env%quencher_r0_factor
475 !almo_scf_env%quencher_r0_shift=0.0_dp
476 !almo_scf_env%quencher_r1_shift=0.0_dp
477 !almo_scf_env%quencher_r0_shift = cp_unit_to_cp2k(&
478 ! almo_scf_env%quencher_r0_shift,"angstrom")
479 !almo_scf_env%quencher_r1_shift = cp_unit_to_cp2k(&
480 ! almo_scf_env%quencher_r1_shift,"angstrom")
481
482 almo_scf_env%quencher_s0 = 1.0e-4_dp
483 almo_scf_env%quencher_s1 = 1.0e-6_dp
484
485 almo_scf_env%envelope_amplitude = 1.0_dp
486
487 almo_scf_env%logical01 = .false. ! md in eDOF space
488 almo_scf_env%logical02 = .true. ! not used
489 almo_scf_env%logical03 = .true. ! not used
490 almo_scf_env%logical04 = .true. ! use preconditioner
491 almo_scf_env%logical05 = .false. ! optimize theta
492
493 almo_scf_env%real01 = almo_scf_env%eps_filter/10.0_dp ! skip gradients
494 almo_scf_env%real02 = 0.0_dp ! not used
495 almo_scf_env%real03 = 0.0_dp ! not used
496 almo_scf_env%real04 = 0.5_dp ! mixing s-f precond
497
498 almo_scf_env%integer01 = 10 ! start eDOF-md
499 almo_scf_env%integer02 = 4 ! preconditioner type
500 almo_scf_env%integer03 = 0 ! not used
501 almo_scf_env%integer04 = 0 ! fixed number of line searches (no grad)
502 almo_scf_env%integer05 = 0 ! not used
503
504 ! check for conflicts between options
505 IF (almo_scf_env%xalmo_trial_wf .EQ. xalmo_trial_r0_out .AND. &
506 almo_scf_env%xalmo_update_algorithm .EQ. almo_scf_trustr) THEN
507 cpabort("Trust region algorithm cannot optimize projected XALMOs")
508 END IF
509
510 CALL section_vals_val_get(almo_scf_section, "XALMO_ALGORITHM", &
511 i_val=almo_scf_env%xalmo_update_algorithm)
512 CALL section_vals_val_get(almo_scf_section, "XALMO_TRIAL_WF", &
513 i_val=almo_scf_env%xalmo_trial_wf)
514 IF (almo_scf_env%deloc_method .EQ. almo_deloc_xalmo_1diag .AND. &
515 almo_scf_env%xalmo_update_algorithm .NE. almo_scf_diag) THEN
516 cpabort("1-step delocalization correction requires a different algorithm")
517 END IF
518
519 IF (almo_scf_env%xalmo_trial_wf .EQ. xalmo_trial_r0_out .AND. &
520 almo_scf_env%almo_update_algorithm .EQ. almo_scf_skip .AND. &
521 almo_scf_env%almo_scf_guess .NE. molecular_guess) THEN
522 cpabort("R0 projector requires optimized ALMOs")
523 END IF
524
525 IF (almo_scf_env%deloc_method .EQ. almo_deloc_none .AND. &
526 almo_scf_env%almo_update_algorithm .EQ. almo_scf_skip) THEN
527 cpabort("No optimization requested")
528 END IF
529
530 IF (almo_scf_env%deloc_truncate_virt .EQ. virt_number .AND. &
531 almo_scf_env%deloc_virt_per_domain .LE. 0) THEN
532 cpabort("specify a positive number of virtual orbitals")
533 END IF
534
535 IF (almo_scf_env%deloc_truncate_virt .EQ. virt_minimal) THEN
536 cpabort("VIRT TRUNCATION TO MINIMAL BASIS IS NIY")
537 END IF
538
539 IF (almo_scf_env%domain_layout_mos .NE. almo_domain_layout_molecular) THEN
540 cpabort("use MOLECULAR domains")
541 END IF
542
543 IF (almo_scf_env%domain_layout_aos .NE. almo_domain_layout_molecular) THEN
544 cpabort("use MOLECULAR domains")
545 END IF
546
547 IF (almo_scf_env%mat_distr_mos .NE. almo_mat_distr_molecular) THEN
548 cpabort("use MOLECULAR distr for MOs")
549 END IF
550
551 IF (almo_scf_env%mat_distr_aos == almo_mat_distr_molecular .AND. &
552 almo_scf_env%domain_layout_aos == almo_domain_layout_atomic) THEN
553 cpabort("AO blocks cannot be larger than domains")
554 END IF
555
556 IF (almo_scf_env%mat_distr_mos == almo_mat_distr_molecular .AND. &
557 almo_scf_env%domain_layout_mos == almo_domain_layout_atomic) THEN
558 cpabort("MO blocks cannot be larger than domains")
559 END IF
560
561 IF (almo_scf_env%quencher_r1_factor .GT. almo_max_cutoff_multiplier) THEN
562 CALL cp_abort(__location__, &
563 "XALMO_R_CUTOFF_FACTOR is larger than almo_max_cutoff_multiplier. "// &
564 "Increase the hard-coded almo_max_cutoff_multiplier")
565 END IF
566
567 ! check analysis settings
568 IF (almo_scf_env%almo_analysis%do_analysis) THEN
569
570 IF (almo_scf_env%almo_analysis%frozen_mo_energy_term == almo_frz_crystal &
571 .AND. almo_scf_env%almo_scf_guess .NE. molecular_guess) THEN
572 cpabort("To compute frozen-MO energy term set ALMO_SCF_GUESS MOLECULAR")
573 END IF
574
575 END IF ! end analysis settings
576
577 CALL timestop(handle)
578
579 END SUBROUTINE almo_scf_init_read_write_input
580
581END MODULE almo_scf_env_methods
582
almo_scf_env methods
subroutine, public almo_scf_env_create(qs_env)
Creation and basic initialization of the almo environment.
Types for all ALMO-based methods.
real(kind=dp), parameter, public almo_max_cutoff_multiplier
Defines control structures, which contain the parameters and the settings for the DFT-based calculati...
collects all constants needed in input so that they can be used without circular dependencies
integer, parameter, public xalmo_trial_r0_out
integer, parameter, public molecular_guess
integer, parameter, public almo_constraint_distance
integer, parameter, public virt_number
integer, parameter, public almo_domain_layout_atomic
integer, parameter, public almo_mat_distr_molecular
integer, parameter, public almo_domain_layout_molecular
integer, parameter, public do_bondparm_vdw
integer, parameter, public almo_scf_diag
integer, parameter, public almo_frz_crystal
integer, parameter, public almo_scf_skip
integer, parameter, public almo_scf_trustr
integer, parameter, public virt_minimal
integer, parameter, public virt_full
integer, parameter, public tensor_orthogonal
integer, parameter, public almo_deloc_xalmo_1diag
integer, parameter, public almo_deloc_none
integer, parameter, public cg_hager_zhang
objects that represent the structure of input sections and the data contained in an input section
recursive type(section_vals_type) function, pointer, public section_vals_get_subs_vals(section_vals, subsection_name, i_rep_section, can_return_null)
returns the values of the requested subsection
subroutine, public section_vals_val_get(section_vals, keyword_name, i_rep_section, i_rep_val, n_rep_val, val, l_val, i_val, r_val, c_val, l_vals, i_vals, r_vals, c_vals, explicit)
returns the requested value
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
subroutine, public set_qs_env(qs_env, super_cell, mos, qmmm, qmmm_periodic, ewald_env, ewald_pw, mpools, rho_external, external_vxc, mask, scf_control, rel_control, qs_charges, ks_env, ks_qmmm_env, wf_history, scf_env, active_space, input, oce, rho_atom_set, rho0_atom_set, rho0_mpole, run_rtp, rtp, rhoz_set, rhoz_tot, ecoul_1c, has_unit_metric, requires_mo_derivs, mo_derivs, mo_loc_history, efield, linres_control, xas_env, cp_ddapc_env, cp_ddapc_ewald, outer_scf_history, outer_scf_ihistory, x_data, et_coupling, dftb_potential, se_taper, se_store_int_env, se_nddo_mpole, se_nonbond_env, admm_env, ls_scf_env, do_transport, transport_env, lri_env, lri_density, exstate_env, ec_env, dispersion_env, gcp_env, mp2_env, bs_env, kg_env, force, kpoints, wanniercentres, almo_scf_env, gradient_history, variable_history, embed_pot, spin_embed_pot, polar_env, mos_last_converged, rhs)
Set the QUICKSTEP environment.
subroutine, public get_qs_env(qs_env, atomic_kind_set, qs_kind_set, cell, super_cell, cell_ref, use_ref_cell, kpoints, dft_control, mos, sab_orb, sab_all, qmmm, qmmm_periodic, sac_ae, sac_ppl, sac_lri, sap_ppnl, sab_vdw, sab_scp, sap_oce, sab_lrc, sab_se, sab_xtbe, sab_tbe, sab_core, sab_xb, sab_xtb_nonbond, sab_almo, sab_kp, sab_kp_nosym, particle_set, energy, force, matrix_h, matrix_h_im, matrix_ks, matrix_ks_im, matrix_vxc, run_rtp, rtp, matrix_h_kp, matrix_h_im_kp, matrix_ks_kp, matrix_ks_im_kp, matrix_vxc_kp, kinetic_kp, matrix_s_kp, matrix_w_kp, matrix_s_ri_aux_kp, matrix_s, matrix_s_ri_aux, matrix_w, matrix_p_mp2, matrix_p_mp2_admm, rho, rho_xc, pw_env, ewald_env, ewald_pw, active_space, mpools, input, para_env, blacs_env, scf_control, rel_control, kinetic, qs_charges, vppl, rho_core, rho_nlcc, rho_nlcc_g, ks_env, ks_qmmm_env, wf_history, scf_env, local_particles, local_molecules, distribution_2d, dbcsr_dist, molecule_kind_set, molecule_set, subsys, cp_subsys, oce, local_rho_set, rho_atom_set, task_list, task_list_soft, rho0_atom_set, rho0_mpole, rhoz_set, ecoul_1c, rho0_s_rs, rho0_s_gs, do_kpoints, has_unit_metric, requires_mo_derivs, mo_derivs, mo_loc_history, nkind, natom, nelectron_total, nelectron_spin, efield, neighbor_list_id, linres_control, xas_env, virial, cp_ddapc_env, cp_ddapc_ewald, outer_scf_history, outer_scf_ihistory, x_data, et_coupling, dftb_potential, results, se_taper, se_store_int_env, se_nddo_mpole, se_nonbond_env, admm_env, lri_env, lri_density, exstate_env, ec_env, dispersion_env, gcp_env, vee, rho_external, external_vxc, mask, mp2_env, bs_env, kg_env, wanniercentres, atprop, ls_scf_env, do_transport, transport_env, v_hartree_rspace, s_mstruct_changed, rho_changed, potential_changed, forces_up_to_date, mscfg_env, almo_scf_env, gradient_history, variable_history, embed_pot, spin_embed_pot, polar_env, mos_last_converged, rhs)
Get the QUICKSTEP environment.