Line data Source code
1 : !--------------------------------------------------------------------------------------------------!
2 : ! CP2K: A general program to perform molecular dynamics simulations !
3 : ! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4 : ! !
5 : ! SPDX-License-Identifier: GPL-2.0-or-later !
6 : !--------------------------------------------------------------------------------------------------!
7 :
8 : ! **************************************************************************************************
9 : !> \brief module that contains the definitions of the scf types
10 : !> \par History
11 : !> 02.2003 created [fawzi]
12 : !> \author fawzi
13 : ! **************************************************************************************************
14 : MODULE qs_density_mixing_types
15 : USE ao_util, ONLY: exp_radius
16 : USE input_constants, ONLY: broy_mix,&
17 : direct_p_mix,&
18 : gaussian,&
19 : kerker_mix,&
20 : multisec_mix,&
21 : no_mix,&
22 : pulay_mix
23 : USE input_keyword_types, ONLY: keyword_create,&
24 : keyword_release,&
25 : keyword_type
26 : USE input_section_types, ONLY: section_add_keyword,&
27 : section_create,&
28 : section_type,&
29 : section_vals_type,&
30 : section_vals_val_get
31 : USE input_val_types, ONLY: real_t
32 : USE kinds, ONLY: default_string_length,&
33 : dp
34 : USE qs_rho_atom_types, ONLY: rho_atom_coeff
35 : USE string_utilities, ONLY: s2a
36 : #include "./base/base_uses.f90"
37 :
38 : IMPLICIT NONE
39 : PRIVATE
40 :
41 : LOGICAL, PRIVATE, PARAMETER :: debug_this_module = .TRUE.
42 :
43 : CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'qs_density_mixing_types'
44 :
45 : INTEGER, PARAMETER, PUBLIC :: no_mixing_nr = 0, direct_mixing_nr = 1, &
46 : gspace_mixing_nr = 2, pulay_mixing_nr = 3, &
47 : broyden_mixing_nr = 4, &
48 : multisecant_mixing_nr = 6
49 : PUBLIC :: cp_1d_z_p_type, mixing_storage_create, mixing_storage_type, mixing_storage_release, create_mixing_section
50 :
51 : TYPE cp_1d_z_p_type
52 : COMPLEX(dp), DIMENSION(:), POINTER :: cc => NULL()
53 : END TYPE cp_1d_z_p_type
54 :
55 : TYPE mixing_storage_type
56 : INTEGER :: ig_max = -1, ncall = -1, ncall_p(2) = -1, nbuffer = -1, n_simple_mix = -1, &
57 : nskip_mixing = -1, p_metric_method = -1
58 : INTEGER, POINTER, DIMENSION(:) :: ig_global_index => NULL()
59 : LOGICAL :: gmix_p = .FALSE.
60 : LOGICAL, POINTER, DIMENSION(:) :: paw => NULL()
61 : CHARACTER(len=15) :: iter_method = ""
62 : REAL(KIND=dp) :: alpha = -1.0_dp, bconst = -1.0_dp, beta = -1.0_dp, broy_w0 = -1.0_dp, &
63 : max_g2 = -1.0_dp, max_gvec_exp = -1.0_dp, pulay_alpha = -1.0_dp, &
64 : pulay_beta = -1.0_dp, r_step = -1.0_dp, reg_par = -1.0_dp, &
65 : sigma_max = -1.0_dp, wc = -1.0_dp, wmax = -1.0_dp
66 : REAL(KIND=dp), DIMENSION(:), POINTER :: p_metric => NULL()
67 : REAL(KIND=dp), DIMENSION(:), POINTER :: kerker_factor => NULL()
68 : REAL(KIND=dp), DIMENSION(:), POINTER :: special_metric => NULL()
69 : REAL(KIND=dp), DIMENSION(:, :), POINTER :: weight => NULL()
70 : REAL(KIND=dp), DIMENSION(:, :), POINTER :: norm_res_buffer => NULL()
71 : REAL(KIND=dp), DIMENSION(:, :, :), POINTER :: fmat => NULL(), gmat => NULL(), pulay_matrix => NULL(), smat => NULL()
72 : !
73 : INTEGER :: nat_local = -1, max_shell = -1
74 : REAL(KIND=dp), DIMENSION(:, :, :), POINTER :: acharge => NULL()
75 : REAL(KIND=dp), DIMENSION(:, :, :), POINTER :: dacharge => NULL()
76 : REAL(KIND=dp), DIMENSION(:, :, :), POINTER :: dfbroy => NULL()
77 : REAL(KIND=dp), DIMENSION(:, :, :), POINTER :: ubroy => NULL()
78 : REAL(KIND=dp), DIMENSION(:, :), POINTER :: abroy => NULL()
79 : REAL(KIND=dp), DIMENSION(:), POINTER :: wbroy => NULL()
80 : INTEGER, DIMENSION(:), POINTER :: atlist => NULL()
81 : !
82 : TYPE(cp_1d_z_p_type), DIMENSION(:), POINTER :: last_res => NULL(), rhoin => NULL(), rhoin_old => NULL()
83 : TYPE(cp_1d_z_p_type), DIMENSION(:, :), POINTER :: delta_res => NULL(), u_vec => NULL(), z_vec => NULL()
84 : TYPE(cp_1d_z_p_type), DIMENSION(:, :), POINTER :: drho_buffer => NULL(), rhoin_buffer => NULL(), res_buffer => NULL()
85 : !
86 : TYPE(rho_atom_coeff), DIMENSION(:, :), POINTER :: cpc_h_lastres => NULL(), cpc_s_lastres => NULL()
87 : TYPE(rho_atom_coeff), DIMENSION(:, :), POINTER :: cpc_h_in => NULL(), cpc_s_in => NULL()
88 : TYPE(rho_atom_coeff), DIMENSION(:, :), POINTER :: cpc_h_old => NULL(), cpc_s_old => NULL()
89 : TYPE(rho_atom_coeff), DIMENSION(:, :, :), POINTER :: cpc_h_in_buffer => NULL(), cpc_s_in_buffer => NULL()
90 : TYPE(rho_atom_coeff), DIMENSION(:, :, :), POINTER :: cpc_h_res_buffer => NULL(), cpc_s_res_buffer => NULL()
91 : TYPE(rho_atom_coeff), DIMENSION(:, :, :), POINTER :: dcpc_h_in => NULL(), dcpc_s_in => NULL()
92 : END TYPE mixing_storage_type
93 :
94 : CONTAINS
95 :
96 : ! **************************************************************************************************
97 : !> \brief creates a mixing_storage
98 : !> \param mixing_store ...
99 : !> \param mixing_section ...
100 : !> \param mixing_method ...
101 : !> \param ecut ...
102 : !> \par History
103 : !> 05.2009 created [MI]
104 : !> \author [MI]
105 : ! **************************************************************************************************
106 17769 : SUBROUTINE mixing_storage_create(mixing_store, mixing_section, mixing_method, ecut)
107 : TYPE(mixing_storage_type), INTENT(OUT) :: mixing_store
108 : TYPE(section_vals_type), POINTER :: mixing_section
109 : INTEGER, INTENT(IN) :: mixing_method
110 : REAL(dp), INTENT(IN) :: ecut
111 :
112 : REAL(dp) :: alpha, eps, gcut
113 :
114 5923 : mixing_store%nbuffer = 0
115 5923 : mixing_store%n_simple_mix = 0
116 5923 : mixing_store%ncall = 0
117 17769 : mixing_store%ncall_p = 0
118 5923 : mixing_store%alpha = 1.0_dp
119 5923 : mixing_store%pulay_beta = 1.0_dp
120 5923 : mixing_store%beta = 1.0_dp
121 5923 : mixing_store%iter_method = "NoMix"
122 5923 : mixing_store%max_g2 = 2._dp*ecut
123 5923 : mixing_store%gmix_p = .FALSE.
124 :
125 5923 : NULLIFY (mixing_store%p_metric)
126 5923 : NULLIFY (mixing_store%kerker_factor)
127 5923 : NULLIFY (mixing_store%special_metric)
128 5923 : NULLIFY (mixing_store%pulay_matrix)
129 5923 : NULLIFY (mixing_store%weight)
130 5923 : NULLIFY (mixing_store%fmat)
131 5923 : NULLIFY (mixing_store%gmat)
132 5923 : NULLIFY (mixing_store%smat)
133 5923 : NULLIFY (mixing_store%acharge)
134 5923 : NULLIFY (mixing_store%dacharge)
135 5923 : NULLIFY (mixing_store%dfbroy)
136 5923 : NULLIFY (mixing_store%ubroy)
137 5923 : NULLIFY (mixing_store%abroy)
138 5923 : NULLIFY (mixing_store%wbroy)
139 5923 : NULLIFY (mixing_store%atlist)
140 5923 : NULLIFY (mixing_store%last_res)
141 5923 : NULLIFY (mixing_store%rhoin)
142 5923 : NULLIFY (mixing_store%rhoin_old)
143 5923 : NULLIFY (mixing_store%delta_res)
144 5923 : NULLIFY (mixing_store%u_vec)
145 5923 : NULLIFY (mixing_store%z_vec)
146 5923 : NULLIFY (mixing_store%drho_buffer)
147 5923 : NULLIFY (mixing_store%rhoin_buffer)
148 5923 : NULLIFY (mixing_store%res_buffer)
149 5923 : NULLIFY (mixing_store%norm_res_buffer)
150 5923 : NULLIFY (mixing_store%ig_global_index)
151 5923 : NULLIFY (mixing_store%paw)
152 5923 : NULLIFY (mixing_store%cpc_h_in)
153 5923 : NULLIFY (mixing_store%cpc_s_in)
154 5923 : NULLIFY (mixing_store%cpc_h_old)
155 5923 : NULLIFY (mixing_store%cpc_s_old)
156 5923 : NULLIFY (mixing_store%dcpc_h_in)
157 5923 : NULLIFY (mixing_store%dcpc_s_in)
158 5923 : NULLIFY (mixing_store%cpc_h_lastres)
159 5923 : NULLIFY (mixing_store%cpc_s_lastres)
160 5923 : NULLIFY (mixing_store%cpc_h_in_buffer)
161 5923 : NULLIFY (mixing_store%cpc_s_in_buffer)
162 5923 : NULLIFY (mixing_store%cpc_h_res_buffer)
163 5923 : NULLIFY (mixing_store%cpc_s_res_buffer)
164 :
165 5923 : CALL section_vals_val_get(mixing_section, "ALPHA", r_val=mixing_store%alpha)
166 5923 : CALL section_vals_val_get(mixing_section, "BETA", r_val=mixing_store%beta)
167 5923 : CALL section_vals_val_get(mixing_section, "N_SIMPLE_MIX", i_val=mixing_store%n_simple_mix)
168 5923 : CALL section_vals_val_get(mixing_section, "NBUFFER", i_val=mixing_store%nbuffer)
169 5923 : CALL section_vals_val_get(mixing_section, "NSKIP", i_val=mixing_store%nskip_mixing)
170 5923 : CALL section_vals_val_get(mixing_section, "MAX_GVEC_EXP", r_val=mixing_store%max_gvec_exp)
171 5923 : CALL section_vals_val_get(mixing_section, "GMIX_P", l_val=mixing_store%gmix_p)
172 :
173 5923 : IF (mixing_store%max_gvec_exp > 0._dp) THEN
174 0 : alpha = 0.25_dp/mixing_store%max_gvec_exp
175 0 : eps = 1.e-4_dp
176 0 : gcut = exp_radius(3, alpha, eps, 1.0_dp)
177 0 : mixing_store%max_g2 = gcut*gcut
178 : END IF
179 :
180 5933 : SELECT CASE (mixing_method)
181 : CASE (gspace_mixing_nr)
182 10 : mixing_store%nbuffer = 1
183 : CASE (pulay_mixing_nr)
184 36 : CALL section_vals_val_get(mixing_section, "PULAY_ALPHA", r_val=mixing_store%pulay_alpha)
185 36 : CALL section_vals_val_get(mixing_section, "PULAY_BETA", r_val=mixing_store%pulay_beta)
186 : CASE (broyden_mixing_nr)
187 500 : CALL section_vals_val_get(mixing_section, "BROY_W0", r_val=mixing_store%broy_w0)
188 500 : mixing_store%bconst = 20.0_dp
189 : CASE (multisecant_mixing_nr)
190 0 : CALL section_vals_val_get(mixing_section, "REGULARIZATION", r_val=mixing_store%reg_par)
191 0 : CALL section_vals_val_get(mixing_section, "MAX_STEP", r_val=mixing_store%sigma_max)
192 5923 : CALL section_vals_val_get(mixing_section, "R_FACTOR", r_val=mixing_store%r_step)
193 : END SELECT
194 :
195 5923 : END SUBROUTINE mixing_storage_create
196 :
197 : ! **************************************************************************************************
198 : !> \brief releases a mixing_storage
199 : !> \param mixing_store ...
200 : !> \par History
201 : !> 05.2009 created [MI]
202 : !> \author [MI]
203 : ! **************************************************************************************************
204 5923 : SUBROUTINE mixing_storage_release(mixing_store)
205 : TYPE(mixing_storage_type), INTENT(INOUT) :: mixing_store
206 :
207 : INTEGER :: i, j, k
208 :
209 5923 : IF (ASSOCIATED(mixing_store%kerker_factor)) THEN
210 186 : DEALLOCATE (mixing_store%kerker_factor)
211 : END IF
212 :
213 5923 : IF (ASSOCIATED(mixing_store%special_metric)) THEN
214 186 : DEALLOCATE (mixing_store%special_metric)
215 : END IF
216 :
217 5923 : IF (ASSOCIATED(mixing_store%pulay_matrix)) THEN
218 34 : DEALLOCATE (mixing_store%pulay_matrix)
219 : END IF
220 :
221 5923 : IF (ASSOCIATED(mixing_store%rhoin_buffer)) THEN
222 72 : DO i = 1, SIZE(mixing_store%rhoin_buffer, 2)
223 292 : DO j = 1, SIZE(mixing_store%rhoin_buffer, 1)
224 258 : DEALLOCATE (mixing_store%rhoin_buffer(j, i)%cc)
225 : END DO
226 : END DO
227 34 : DEALLOCATE (mixing_store%rhoin_buffer)
228 : END IF
229 :
230 5923 : IF (ASSOCIATED(mixing_store%paw)) THEN
231 16 : DEALLOCATE (mixing_store%paw)
232 : END IF
233 5923 : IF (ASSOCIATED(mixing_store%cpc_h_in)) THEN
234 38 : DO j = 1, SIZE(mixing_store%cpc_h_in, 2)
235 214 : DO k = 1, SIZE(mixing_store%cpc_h_in, 1)
236 198 : IF (ASSOCIATED(mixing_store%cpc_h_in(k, j)%r_coef)) THEN
237 106 : DEALLOCATE (mixing_store%cpc_h_in(k, j)%r_coef)
238 106 : DEALLOCATE (mixing_store%cpc_s_in(k, j)%r_coef)
239 : END IF
240 : END DO
241 : END DO
242 16 : DEALLOCATE (mixing_store%cpc_h_in)
243 16 : DEALLOCATE (mixing_store%cpc_s_in)
244 : END IF
245 5923 : IF (ASSOCIATED(mixing_store%cpc_h_old)) THEN
246 30 : DO j = 1, SIZE(mixing_store%cpc_h_old, 2)
247 174 : DO k = 1, SIZE(mixing_store%cpc_h_old, 1)
248 162 : IF (ASSOCIATED(mixing_store%cpc_h_old(k, j)%r_coef)) THEN
249 102 : DEALLOCATE (mixing_store%cpc_h_old(k, j)%r_coef)
250 102 : DEALLOCATE (mixing_store%cpc_s_old(k, j)%r_coef)
251 : END IF
252 : END DO
253 : END DO
254 12 : DEALLOCATE (mixing_store%cpc_h_old)
255 12 : DEALLOCATE (mixing_store%cpc_s_old)
256 : END IF
257 5923 : IF (ASSOCIATED(mixing_store%cpc_h_in_buffer)) THEN
258 4 : DO i = 1, SIZE(mixing_store%cpc_h_in_buffer, 3)
259 20 : DO j = 1, SIZE(mixing_store%cpc_h_in_buffer, 2)
260 98 : DO k = 1, SIZE(mixing_store%cpc_h_in_buffer, 1)
261 96 : IF (ASSOCIATED(mixing_store%cpc_h_in_buffer(k, j, i)%r_coef)) THEN
262 10 : DEALLOCATE (mixing_store%cpc_h_in_buffer(k, j, i)%r_coef)
263 10 : DEALLOCATE (mixing_store%cpc_s_in_buffer(k, j, i)%r_coef)
264 : END IF
265 : END DO
266 : END DO
267 : END DO
268 2 : DEALLOCATE (mixing_store%cpc_h_in_buffer)
269 2 : DEALLOCATE (mixing_store%cpc_s_in_buffer)
270 : END IF
271 5923 : IF (ASSOCIATED(mixing_store%cpc_h_res_buffer)) THEN
272 4 : DO i = 1, SIZE(mixing_store%cpc_h_res_buffer, 3)
273 20 : DO j = 1, SIZE(mixing_store%cpc_h_res_buffer, 2)
274 98 : DO k = 1, SIZE(mixing_store%cpc_h_res_buffer, 1)
275 96 : IF (ASSOCIATED(mixing_store%cpc_h_res_buffer(k, j, i)%r_coef)) THEN
276 10 : DEALLOCATE (mixing_store%cpc_h_res_buffer(k, j, i)%r_coef)
277 10 : DEALLOCATE (mixing_store%cpc_s_res_buffer(k, j, i)%r_coef)
278 : END IF
279 : END DO
280 : END DO
281 : END DO
282 2 : DEALLOCATE (mixing_store%cpc_h_res_buffer)
283 2 : DEALLOCATE (mixing_store%cpc_s_res_buffer)
284 : END IF
285 :
286 5923 : IF (ASSOCIATED(mixing_store%dcpc_h_in)) THEN
287 30 : DO i = 1, SIZE(mixing_store%dcpc_h_in, 3)
288 174 : DO j = 1, SIZE(mixing_store%dcpc_h_in, 2)
289 1266 : DO k = 1, SIZE(mixing_store%dcpc_h_in, 1)
290 1248 : IF (ASSOCIATED(mixing_store%dcpc_h_in(k, j, i)%r_coef)) THEN
291 810 : DEALLOCATE (mixing_store%dcpc_h_in(k, j, i)%r_coef)
292 810 : DEALLOCATE (mixing_store%dcpc_s_in(k, j, i)%r_coef)
293 : END IF
294 : END DO
295 : END DO
296 : END DO
297 12 : DEALLOCATE (mixing_store%dcpc_h_in)
298 12 : DEALLOCATE (mixing_store%dcpc_s_in)
299 : END IF
300 5923 : IF (ASSOCIATED(mixing_store%cpc_h_lastres)) THEN
301 30 : DO j = 1, SIZE(mixing_store%cpc_h_lastres, 2)
302 174 : DO k = 1, SIZE(mixing_store%cpc_h_lastres, 1)
303 162 : IF (ASSOCIATED(mixing_store%cpc_h_lastres(k, j)%r_coef)) THEN
304 102 : DEALLOCATE (mixing_store%cpc_h_lastres(k, j)%r_coef)
305 102 : DEALLOCATE (mixing_store%cpc_s_lastres(k, j)%r_coef)
306 : END IF
307 : END DO
308 : END DO
309 12 : DEALLOCATE (mixing_store%cpc_h_lastres)
310 12 : DEALLOCATE (mixing_store%cpc_s_lastres)
311 : END IF
312 :
313 5923 : IF (ASSOCIATED(mixing_store%res_buffer)) THEN
314 382 : DO i = 1, SIZE(mixing_store%res_buffer, 2)
315 2142 : DO j = 1, SIZE(mixing_store%res_buffer, 1)
316 1966 : DEALLOCATE (mixing_store%res_buffer(j, i)%cc)
317 : END DO
318 : END DO
319 176 : DEALLOCATE (mixing_store%res_buffer)
320 : END IF
321 :
322 5923 : IF (ASSOCIATED(mixing_store%norm_res_buffer)) THEN
323 0 : DEALLOCATE (mixing_store%norm_res_buffer)
324 : END IF
325 :
326 5923 : IF (ASSOCIATED(mixing_store%ig_global_index)) THEN
327 0 : DEALLOCATE (mixing_store%ig_global_index)
328 : END IF
329 :
330 5923 : IF (ASSOCIATED(mixing_store%drho_buffer)) THEN
331 310 : DO i = 1, SIZE(mixing_store%drho_buffer, 2)
332 1850 : DO j = 1, SIZE(mixing_store%drho_buffer, 1)
333 1708 : DEALLOCATE (mixing_store%drho_buffer(j, i)%cc)
334 : END DO
335 : END DO
336 142 : DEALLOCATE (mixing_store%drho_buffer)
337 : END IF
338 :
339 5923 : IF (ASSOCIATED(mixing_store%last_res)) THEN
340 310 : DO i = 1, SIZE(mixing_store%last_res)
341 310 : DEALLOCATE (mixing_store%last_res(i)%cc)
342 : END DO
343 142 : DEALLOCATE (mixing_store%last_res)
344 : END IF
345 :
346 5923 : IF (ASSOCIATED(mixing_store%rhoin)) THEN
347 402 : DO i = 1, SIZE(mixing_store%rhoin)
348 402 : DEALLOCATE (mixing_store%rhoin(i)%cc)
349 : END DO
350 186 : DEALLOCATE (mixing_store%rhoin)
351 : END IF
352 :
353 5923 : IF (ASSOCIATED(mixing_store%rhoin_old)) THEN
354 310 : DO i = 1, SIZE(mixing_store%rhoin_old)
355 310 : DEALLOCATE (mixing_store%rhoin_old(i)%cc)
356 : END DO
357 142 : DEALLOCATE (mixing_store%rhoin_old)
358 : END IF
359 :
360 5923 : IF (ASSOCIATED(mixing_store%p_metric)) THEN
361 142 : DEALLOCATE (mixing_store%p_metric)
362 : END IF
363 :
364 5923 : IF (ASSOCIATED(mixing_store%weight)) THEN
365 0 : DEALLOCATE (mixing_store%weight)
366 : END IF
367 :
368 5923 : IF (ASSOCIATED(mixing_store%fmat)) THEN
369 0 : DEALLOCATE (mixing_store%fmat)
370 : END IF
371 :
372 5923 : IF (ASSOCIATED(mixing_store%acharge)) THEN
373 16 : DEALLOCATE (mixing_store%acharge)
374 : END IF
375 5923 : IF (ASSOCIATED(mixing_store%dacharge)) THEN
376 16 : DEALLOCATE (mixing_store%dacharge)
377 : END IF
378 5923 : IF (ASSOCIATED(mixing_store%dfbroy)) THEN
379 16 : DEALLOCATE (mixing_store%dfbroy)
380 : END IF
381 5923 : IF (ASSOCIATED(mixing_store%ubroy)) THEN
382 16 : DEALLOCATE (mixing_store%ubroy)
383 : END IF
384 5923 : IF (ASSOCIATED(mixing_store%abroy)) THEN
385 16 : DEALLOCATE (mixing_store%abroy)
386 : END IF
387 5923 : IF (ASSOCIATED(mixing_store%wbroy)) THEN
388 16 : DEALLOCATE (mixing_store%wbroy)
389 : END IF
390 5923 : IF (ASSOCIATED(mixing_store%atlist)) THEN
391 16 : DEALLOCATE (mixing_store%atlist)
392 : END IF
393 :
394 5923 : IF (ASSOCIATED(mixing_store%delta_res)) THEN
395 0 : DO i = 1, SIZE(mixing_store%delta_res, 2)
396 0 : DO j = 1, SIZE(mixing_store%delta_res, 1)
397 0 : DEALLOCATE (mixing_store%delta_res(j, i)%cc)
398 : END DO
399 : END DO
400 0 : DEALLOCATE (mixing_store%delta_res)
401 : END IF
402 :
403 5923 : IF (ASSOCIATED(mixing_store%u_vec)) THEN
404 0 : DO i = 1, SIZE(mixing_store%u_vec, 2)
405 0 : DO j = 1, SIZE(mixing_store%u_vec, 1)
406 0 : DEALLOCATE (mixing_store%u_vec(j, i)%cc)
407 : END DO
408 : END DO
409 0 : DEALLOCATE (mixing_store%u_vec)
410 : END IF
411 :
412 5923 : IF (ASSOCIATED(mixing_store%z_vec)) THEN
413 0 : DO i = 1, SIZE(mixing_store%z_vec, 2)
414 0 : DO j = 1, SIZE(mixing_store%z_vec, 1)
415 0 : DEALLOCATE (mixing_store%z_vec(j, i)%cc)
416 : END DO
417 : END DO
418 0 : DEALLOCATE (mixing_store%z_vec)
419 : END IF
420 :
421 5923 : END SUBROUTINE mixing_storage_release
422 :
423 : ! **************************************************************************************************
424 : !> \brief Create CP2K input section for the mixing of the density matrix to
425 : !> be used only with diagonalization methods, i.e. not with OT
426 : !> \param section ...
427 : !> \param ls_scf ...
428 : !> \date 20.02.2009
429 : !> \par History
430 : !> 02.2015 moved here from input_cp2k_dft.F, modified for use in LS SCF
431 : !> [Patrick Seewald]
432 : !> \author MI
433 : !> \version 1.0
434 : ! **************************************************************************************************
435 56939 : SUBROUTINE create_mixing_section(section, ls_scf)
436 :
437 : TYPE(section_type), POINTER :: section
438 : LOGICAL, INTENT(IN), OPTIONAL :: ls_scf
439 :
440 : CHARACTER(LEN=default_string_length) :: section_name
441 : INTEGER :: default_mix
442 : LOGICAL :: ls
443 : TYPE(keyword_type), POINTER :: keyword
444 :
445 56939 : CPASSERT(.NOT. ASSOCIATED(section))
446 :
447 56939 : IF (PRESENT(ls_scf)) THEN
448 17077 : IF (ls_scf) THEN
449 : ls = .TRUE.
450 : ELSE
451 : ls = .FALSE.
452 : END IF
453 : ELSE
454 : ls = .FALSE.
455 : END IF
456 :
457 : IF (ls) THEN
458 8547 : section_name = "RHO_MIXING"
459 : ELSE
460 48392 : section_name = "MIXING"
461 : END IF
462 :
463 : CALL section_create(section, __LOCATION__, &
464 : name=section_name, &
465 : description="Define type and parameters for mixing "// &
466 : "procedures to be applied to the density matrix. Normally, "// &
467 : "only one type of mixing method should be accepted. The mixing "// &
468 : "procedures activated by this section are only active for diagonalization "// &
469 : "methods and linear scaling SCF, i.e. not with minimization methods based "// &
470 : "on OT.", &
471 : n_keywords=16, &
472 : n_subsections=0, &
473 56939 : repeats=.FALSE.)
474 :
475 56939 : NULLIFY (keyword)
476 :
477 : CALL keyword_create(keyword, __LOCATION__, &
478 : name="_SECTION_PARAMETERS_", &
479 : description="Controls the activation of the mixing procedure", &
480 : usage="&MIXING ON", &
481 : default_l_val=.TRUE., &
482 56939 : lone_keyword_l_val=.TRUE.)
483 56939 : CALL section_add_keyword(section, keyword)
484 56939 : CALL keyword_release(keyword)
485 :
486 56939 : IF (.NOT. ls) THEN
487 48392 : default_mix = direct_p_mix
488 : ELSE
489 8547 : default_mix = broy_mix
490 : END IF
491 :
492 : CALL keyword_create(keyword, __LOCATION__, &
493 : name="METHOD", &
494 : description="Mixing method to be applied", &
495 : repeats=.FALSE., &
496 : usage="METHOD KERKER_MIXING", &
497 : default_i_val=default_mix, &
498 : enum_c_vals=s2a("NONE", &
499 : "DIRECT_P_MIXING", &
500 : "KERKER_MIXING", &
501 : "PULAY_MIXING", &
502 : "BROYDEN_MIXING", &
503 : "MULTISECANT_MIXING"), &
504 : enum_i_vals=(/no_mix, direct_p_mix, kerker_mix, pulay_mix, broy_mix, &
505 : multisec_mix/), &
506 : enum_desc=s2a("No mixing is applied", &
507 : "Direct mixing of new and old density matrices", &
508 : "Mixing of the potential in reciprocal space using the Kerker damping", &
509 : "Pulay mixing", "Broyden mixing", &
510 56939 : "Multisecant scheme for mixing"))
511 :
512 56939 : CALL section_add_keyword(section, keyword)
513 56939 : CALL keyword_release(keyword)
514 :
515 : CALL keyword_create(keyword, __LOCATION__, &
516 : name="ALPHA", &
517 : description="Fraction of new density to be included", &
518 : repeats=.FALSE., &
519 : n_var=1, &
520 : type_of_var=real_t, &
521 : default_r_val=0.4_dp, &
522 56939 : usage="ALPHA 0.2")
523 56939 : CALL section_add_keyword(section, keyword)
524 56939 : CALL keyword_release(keyword)
525 :
526 : CALL keyword_create(keyword, __LOCATION__, &
527 : name="BETA", &
528 : description="Denominator parameter in Kerker damping "// &
529 : "introduced to suppress charge sloshing: "// &
530 : "rho_mix(g) = rho_in(g) + alpha*g^2/(g^2 + beta^2)*(rho_out(g)-rho_in(g))", &
531 : repeats=.FALSE., &
532 : n_var=1, &
533 : type_of_var=real_t, &
534 : default_r_val=0.5_dp, &
535 : unit_str="bohr^-1", &
536 56939 : usage="BETA 1.5")
537 56939 : CALL section_add_keyword(section, keyword)
538 56939 : CALL keyword_release(keyword)
539 :
540 : CALL keyword_create(keyword, __LOCATION__, &
541 : name="PULAY_ALPHA", &
542 : description="Fraction of new density to be added to the Pulay expansion", &
543 : repeats=.FALSE., &
544 : n_var=1, &
545 : type_of_var=real_t, &
546 : default_r_val=0.0_dp, &
547 56939 : usage="PULAY_ALPHA 0.2")
548 56939 : CALL section_add_keyword(section, keyword)
549 56939 : CALL keyword_release(keyword)
550 :
551 : CALL keyword_create(keyword, __LOCATION__, &
552 : name="PULAY_BETA", &
553 : description="Fraction of residual contribution to be added to Pulay expansion", &
554 : repeats=.FALSE., &
555 : n_var=1, &
556 : type_of_var=real_t, &
557 : default_r_val=1.0_dp, &
558 56939 : usage="PULAY_BETA 0.2")
559 56939 : CALL section_add_keyword(section, keyword)
560 56939 : CALL keyword_release(keyword)
561 :
562 : CALL keyword_create(keyword, __LOCATION__, name="NMIXING", &
563 : description="Minimal number of density mixing (should be greater than 0), "// &
564 : "before starting DIIS", &
565 56939 : usage="NMIXING 1", default_i_val=2)
566 56939 : CALL section_add_keyword(section, keyword)
567 56939 : CALL keyword_release(keyword)
568 :
569 : CALL keyword_create(keyword, __LOCATION__, name="NBUFFER", &
570 : variants=s2a("NPULAY", "NBROYDEN", "NMULTISECANT"), &
571 : description="Number of previous steps stored for the actual mixing scheme", &
572 56939 : usage="NBUFFER 2", default_i_val=4)
573 56939 : CALL section_add_keyword(section, keyword)
574 56939 : CALL keyword_release(keyword)
575 :
576 : CALL keyword_create(keyword, __LOCATION__, &
577 : name="BROY_W0", &
578 : description=" w0 parameter used in Broyden mixing", &
579 : repeats=.FALSE., &
580 : n_var=1, &
581 : type_of_var=real_t, &
582 : default_r_val=0.01_dp, &
583 56939 : usage="BROY_W0 0.03")
584 56939 : CALL section_add_keyword(section, keyword)
585 56939 : CALL keyword_release(keyword)
586 :
587 : CALL keyword_create(keyword, __LOCATION__, &
588 : name="BROY_WREF", &
589 : description="", &
590 : repeats=.FALSE., &
591 : n_var=1, &
592 : type_of_var=real_t, &
593 : default_r_val=100.0_dp, &
594 56939 : usage="BROY_WREF 0.2")
595 56939 : CALL section_add_keyword(section, keyword)
596 56939 : CALL keyword_release(keyword)
597 :
598 : CALL keyword_create(keyword, __LOCATION__, &
599 : name="BROY_WMAX", &
600 : description="", &
601 : repeats=.FALSE., &
602 : n_var=1, &
603 : type_of_var=real_t, &
604 : default_r_val=30.0_dp, &
605 56939 : usage="BROY_WMAX 10.0")
606 56939 : CALL section_add_keyword(section, keyword)
607 56939 : CALL keyword_release(keyword)
608 :
609 : CALL keyword_create(keyword, __LOCATION__, &
610 : name="REGULARIZATION", &
611 : description="Regularization parameter to stabilize "// &
612 : "the inversion of the residual matrix {Yn^t Yn} in the "// &
613 : "multisecant mixing scheme (noise)", &
614 : repeats=.FALSE., &
615 : n_var=1, &
616 : type_of_var=real_t, &
617 : default_r_val=0.00001_dp, &
618 56939 : usage="REGULARIZATION 0.000001")
619 56939 : CALL section_add_keyword(section, keyword)
620 56939 : CALL keyword_release(keyword)
621 :
622 : CALL keyword_create(keyword, __LOCATION__, &
623 : name="MAX_STEP", &
624 : description="Upper bound for the magnitude of the "// &
625 : "unpredicted step size in the update by the "// &
626 : "multisecant mixing scheme", &
627 : repeats=.FALSE., &
628 : n_var=1, &
629 : type_of_var=real_t, &
630 : default_r_val=0.1_dp, &
631 56939 : usage="MAX_STEP .2")
632 56939 : CALL section_add_keyword(section, keyword)
633 56939 : CALL keyword_release(keyword)
634 :
635 : CALL keyword_create(keyword, __LOCATION__, &
636 : name="R_FACTOR", &
637 : description="Control factor for the magnitude of the "// &
638 : "unpredicted step size in the update by the "// &
639 : "multisecant mixing scheme", &
640 : repeats=.FALSE., &
641 : n_var=1, &
642 : type_of_var=real_t, &
643 : default_r_val=0.05_dp, &
644 56939 : usage="R_FACTOR .12")
645 56939 : CALL section_add_keyword(section, keyword)
646 56939 : CALL keyword_release(keyword)
647 :
648 : CALL keyword_create(keyword, __LOCATION__, name="NSKIP", &
649 : variants=(/"NSKIP_MIXING"/), &
650 : description="Number of initial iteration for which the mixing is skipped", &
651 113878 : usage="NSKIP 10", default_i_val=0)
652 56939 : CALL section_add_keyword(section, keyword)
653 56939 : CALL keyword_release(keyword)
654 :
655 : CALL keyword_create(keyword, __LOCATION__, name="N_SIMPLE_MIX", &
656 : variants=(/"NSIMPLEMIX"/), &
657 : description="Number of kerker damping iterations before starting other mixing procedures", &
658 113878 : usage="NSIMPLEMIX", default_i_val=0)
659 56939 : CALL section_add_keyword(section, keyword)
660 56939 : CALL keyword_release(keyword)
661 :
662 : CALL keyword_create(keyword, __LOCATION__, name="MAX_GVEC_EXP", &
663 : description="Restricts the G-space mixing to lower part of G-vector spectrum,"// &
664 : " up to a G0, by assigning the exponent of the Gaussian that can be "// &
665 : "represented by vectors smaller than G0 within a certain accuracy. ", &
666 : repeats=.FALSE., &
667 : n_var=1, &
668 : type_of_var=real_t, &
669 : default_r_val=-1._dp, &
670 56939 : usage="MAX_GVEC_EXP 3.")
671 56939 : CALL section_add_keyword(section, keyword)
672 56939 : CALL keyword_release(keyword)
673 :
674 : CALL keyword_create(keyword, __LOCATION__, name="GMIX_P", &
675 : description="Activate the mixing of the density matrix, using the same"// &
676 : " mixing coefficient applied for the g-space mixing.", &
677 : repeats=.FALSE., &
678 : lone_keyword_l_val=.TRUE., &
679 : default_l_val=.FALSE., &
680 56939 : usage="GMIX_P")
681 56939 : CALL section_add_keyword(section, keyword)
682 56939 : CALL keyword_release(keyword)
683 :
684 56939 : END SUBROUTINE create_mixing_section
685 :
686 0 : END MODULE qs_density_mixing_types
|