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()
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()
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()
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()
109 INTEGER,
INTENT(IN) :: mixing_method
110 REAL(
dp),
INTENT(IN) :: ecut
112 REAL(
dp) :: alpha, eps, gcut
114 mixing_store%nbuffer = 0
115 mixing_store%n_simple_mix = 0
116 mixing_store%ncall = 0
117 mixing_store%ncall_p = 0
118 mixing_store%alpha = 1.0_dp
119 mixing_store%pulay_beta = 1.0_dp
120 mixing_store%beta = 1.0_dp
121 mixing_store%iter_method =
"NoMix"
122 mixing_store%max_g2 = 2._dp*ecut
123 mixing_store%gmix_p = .false.
125 NULLIFY (mixing_store%p_metric)
126 NULLIFY (mixing_store%kerker_factor)
127 NULLIFY (mixing_store%special_metric)
128 NULLIFY (mixing_store%pulay_matrix)
129 NULLIFY (mixing_store%weight)
130 NULLIFY (mixing_store%fmat)
131 NULLIFY (mixing_store%gmat)
132 NULLIFY (mixing_store%smat)
133 NULLIFY (mixing_store%acharge)
134 NULLIFY (mixing_store%dacharge)
135 NULLIFY (mixing_store%dfbroy)
136 NULLIFY (mixing_store%ubroy)
137 NULLIFY (mixing_store%abroy)
138 NULLIFY (mixing_store%wbroy)
139 NULLIFY (mixing_store%atlist)
140 NULLIFY (mixing_store%last_res)
141 NULLIFY (mixing_store%rhoin)
142 NULLIFY (mixing_store%rhoin_old)
143 NULLIFY (mixing_store%delta_res)
144 NULLIFY (mixing_store%u_vec)
145 NULLIFY (mixing_store%z_vec)
146 NULLIFY (mixing_store%drho_buffer)
147 NULLIFY (mixing_store%rhoin_buffer)
148 NULLIFY (mixing_store%res_buffer)
149 NULLIFY (mixing_store%norm_res_buffer)
150 NULLIFY (mixing_store%ig_global_index)
151 NULLIFY (mixing_store%paw)
152 NULLIFY (mixing_store%cpc_h_in)
153 NULLIFY (mixing_store%cpc_s_in)
154 NULLIFY (mixing_store%cpc_h_old)
155 NULLIFY (mixing_store%cpc_s_old)
156 NULLIFY (mixing_store%dcpc_h_in)
157 NULLIFY (mixing_store%dcpc_s_in)
158 NULLIFY (mixing_store%cpc_h_lastres)
159 NULLIFY (mixing_store%cpc_s_lastres)
160 NULLIFY (mixing_store%cpc_h_in_buffer)
161 NULLIFY (mixing_store%cpc_s_in_buffer)
162 NULLIFY (mixing_store%cpc_h_res_buffer)
163 NULLIFY (mixing_store%cpc_s_res_buffer)
173 IF (mixing_store%max_gvec_exp > 0._dp)
THEN
174 alpha = 0.25_dp/mixing_store%max_gvec_exp
177 mixing_store%max_g2 = gcut*gcut
180 SELECT CASE (mixing_method)
182 mixing_store%nbuffer = 1
188 mixing_store%bconst = 20.0_dp
209 IF (
ASSOCIATED(mixing_store%kerker_factor))
THEN
210 DEALLOCATE (mixing_store%kerker_factor)
213 IF (
ASSOCIATED(mixing_store%special_metric))
THEN
214 DEALLOCATE (mixing_store%special_metric)
217 IF (
ASSOCIATED(mixing_store%pulay_matrix))
THEN
218 DEALLOCATE (mixing_store%pulay_matrix)
221 IF (
ASSOCIATED(mixing_store%rhoin_buffer))
THEN
222 DO i = 1,
SIZE(mixing_store%rhoin_buffer, 2)
223 DO j = 1,
SIZE(mixing_store%rhoin_buffer, 1)
224 DEALLOCATE (mixing_store%rhoin_buffer(j, i)%cc)
227 DEALLOCATE (mixing_store%rhoin_buffer)
230 IF (
ASSOCIATED(mixing_store%paw))
THEN
231 DEALLOCATE (mixing_store%paw)
233 IF (
ASSOCIATED(mixing_store%cpc_h_in))
THEN
234 DO j = 1,
SIZE(mixing_store%cpc_h_in, 2)
235 DO k = 1,
SIZE(mixing_store%cpc_h_in, 1)
236 IF (
ASSOCIATED(mixing_store%cpc_h_in(k, j)%r_coef))
THEN
237 DEALLOCATE (mixing_store%cpc_h_in(k, j)%r_coef)
238 DEALLOCATE (mixing_store%cpc_s_in(k, j)%r_coef)
242 DEALLOCATE (mixing_store%cpc_h_in)
243 DEALLOCATE (mixing_store%cpc_s_in)
245 IF (
ASSOCIATED(mixing_store%cpc_h_old))
THEN
246 DO j = 1,
SIZE(mixing_store%cpc_h_old, 2)
247 DO k = 1,
SIZE(mixing_store%cpc_h_old, 1)
248 IF (
ASSOCIATED(mixing_store%cpc_h_old(k, j)%r_coef))
THEN
249 DEALLOCATE (mixing_store%cpc_h_old(k, j)%r_coef)
250 DEALLOCATE (mixing_store%cpc_s_old(k, j)%r_coef)
254 DEALLOCATE (mixing_store%cpc_h_old)
255 DEALLOCATE (mixing_store%cpc_s_old)
257 IF (
ASSOCIATED(mixing_store%cpc_h_in_buffer))
THEN
258 DO i = 1,
SIZE(mixing_store%cpc_h_in_buffer, 3)
259 DO j = 1,
SIZE(mixing_store%cpc_h_in_buffer, 2)
260 DO k = 1,
SIZE(mixing_store%cpc_h_in_buffer, 1)
261 IF (
ASSOCIATED(mixing_store%cpc_h_in_buffer(k, j, i)%r_coef))
THEN
262 DEALLOCATE (mixing_store%cpc_h_in_buffer(k, j, i)%r_coef)
263 DEALLOCATE (mixing_store%cpc_s_in_buffer(k, j, i)%r_coef)
268 DEALLOCATE (mixing_store%cpc_h_in_buffer)
269 DEALLOCATE (mixing_store%cpc_s_in_buffer)
271 IF (
ASSOCIATED(mixing_store%cpc_h_res_buffer))
THEN
272 DO i = 1,
SIZE(mixing_store%cpc_h_res_buffer, 3)
273 DO j = 1,
SIZE(mixing_store%cpc_h_res_buffer, 2)
274 DO k = 1,
SIZE(mixing_store%cpc_h_res_buffer, 1)
275 IF (
ASSOCIATED(mixing_store%cpc_h_res_buffer(k, j, i)%r_coef))
THEN
276 DEALLOCATE (mixing_store%cpc_h_res_buffer(k, j, i)%r_coef)
277 DEALLOCATE (mixing_store%cpc_s_res_buffer(k, j, i)%r_coef)
282 DEALLOCATE (mixing_store%cpc_h_res_buffer)
283 DEALLOCATE (mixing_store%cpc_s_res_buffer)
286 IF (
ASSOCIATED(mixing_store%dcpc_h_in))
THEN
287 DO i = 1,
SIZE(mixing_store%dcpc_h_in, 3)
288 DO j = 1,
SIZE(mixing_store%dcpc_h_in, 2)
289 DO k = 1,
SIZE(mixing_store%dcpc_h_in, 1)
290 IF (
ASSOCIATED(mixing_store%dcpc_h_in(k, j, i)%r_coef))
THEN
291 DEALLOCATE (mixing_store%dcpc_h_in(k, j, i)%r_coef)
292 DEALLOCATE (mixing_store%dcpc_s_in(k, j, i)%r_coef)
297 DEALLOCATE (mixing_store%dcpc_h_in)
298 DEALLOCATE (mixing_store%dcpc_s_in)
300 IF (
ASSOCIATED(mixing_store%cpc_h_lastres))
THEN
301 DO j = 1,
SIZE(mixing_store%cpc_h_lastres, 2)
302 DO k = 1,
SIZE(mixing_store%cpc_h_lastres, 1)
303 IF (
ASSOCIATED(mixing_store%cpc_h_lastres(k, j)%r_coef))
THEN
304 DEALLOCATE (mixing_store%cpc_h_lastres(k, j)%r_coef)
305 DEALLOCATE (mixing_store%cpc_s_lastres(k, j)%r_coef)
309 DEALLOCATE (mixing_store%cpc_h_lastres)
310 DEALLOCATE (mixing_store%cpc_s_lastres)
313 IF (
ASSOCIATED(mixing_store%res_buffer))
THEN
314 DO i = 1,
SIZE(mixing_store%res_buffer, 2)
315 DO j = 1,
SIZE(mixing_store%res_buffer, 1)
316 DEALLOCATE (mixing_store%res_buffer(j, i)%cc)
319 DEALLOCATE (mixing_store%res_buffer)
322 IF (
ASSOCIATED(mixing_store%norm_res_buffer))
THEN
323 DEALLOCATE (mixing_store%norm_res_buffer)
326 IF (
ASSOCIATED(mixing_store%ig_global_index))
THEN
327 DEALLOCATE (mixing_store%ig_global_index)
330 IF (
ASSOCIATED(mixing_store%drho_buffer))
THEN
331 DO i = 1,
SIZE(mixing_store%drho_buffer, 2)
332 DO j = 1,
SIZE(mixing_store%drho_buffer, 1)
333 DEALLOCATE (mixing_store%drho_buffer(j, i)%cc)
336 DEALLOCATE (mixing_store%drho_buffer)
339 IF (
ASSOCIATED(mixing_store%last_res))
THEN
340 DO i = 1,
SIZE(mixing_store%last_res)
341 DEALLOCATE (mixing_store%last_res(i)%cc)
343 DEALLOCATE (mixing_store%last_res)
346 IF (
ASSOCIATED(mixing_store%rhoin))
THEN
347 DO i = 1,
SIZE(mixing_store%rhoin)
348 DEALLOCATE (mixing_store%rhoin(i)%cc)
350 DEALLOCATE (mixing_store%rhoin)
353 IF (
ASSOCIATED(mixing_store%rhoin_old))
THEN
354 DO i = 1,
SIZE(mixing_store%rhoin_old)
355 DEALLOCATE (mixing_store%rhoin_old(i)%cc)
357 DEALLOCATE (mixing_store%rhoin_old)
360 IF (
ASSOCIATED(mixing_store%p_metric))
THEN
361 DEALLOCATE (mixing_store%p_metric)
364 IF (
ASSOCIATED(mixing_store%weight))
THEN
365 DEALLOCATE (mixing_store%weight)
368 IF (
ASSOCIATED(mixing_store%fmat))
THEN
369 DEALLOCATE (mixing_store%fmat)
372 IF (
ASSOCIATED(mixing_store%acharge))
THEN
373 DEALLOCATE (mixing_store%acharge)
375 IF (
ASSOCIATED(mixing_store%dacharge))
THEN
376 DEALLOCATE (mixing_store%dacharge)
378 IF (
ASSOCIATED(mixing_store%dfbroy))
THEN
379 DEALLOCATE (mixing_store%dfbroy)
381 IF (
ASSOCIATED(mixing_store%ubroy))
THEN
382 DEALLOCATE (mixing_store%ubroy)
384 IF (
ASSOCIATED(mixing_store%abroy))
THEN
385 DEALLOCATE (mixing_store%abroy)
387 IF (
ASSOCIATED(mixing_store%wbroy))
THEN
388 DEALLOCATE (mixing_store%wbroy)
390 IF (
ASSOCIATED(mixing_store%atlist))
THEN
391 DEALLOCATE (mixing_store%atlist)
394 IF (
ASSOCIATED(mixing_store%delta_res))
THEN
395 DO i = 1,
SIZE(mixing_store%delta_res, 2)
396 DO j = 1,
SIZE(mixing_store%delta_res, 1)
397 DEALLOCATE (mixing_store%delta_res(j, i)%cc)
400 DEALLOCATE (mixing_store%delta_res)
403 IF (
ASSOCIATED(mixing_store%u_vec))
THEN
404 DO i = 1,
SIZE(mixing_store%u_vec, 2)
405 DO j = 1,
SIZE(mixing_store%u_vec, 1)
406 DEALLOCATE (mixing_store%u_vec(j, i)%cc)
409 DEALLOCATE (mixing_store%u_vec)
412 IF (
ASSOCIATED(mixing_store%z_vec))
THEN
413 DO i = 1,
SIZE(mixing_store%z_vec, 2)
414 DO j = 1,
SIZE(mixing_store%z_vec, 1)
415 DEALLOCATE (mixing_store%z_vec(j, i)%cc)
418 DEALLOCATE (mixing_store%z_vec)
438 LOGICAL,
INTENT(IN),
OPTIONAL :: ls_scf
440 CHARACTER(LEN=default_string_length) :: section_name
441 INTEGER :: default_mix
445 cpassert(.NOT.
ASSOCIATED(section))
447 IF (
PRESENT(ls_scf))
THEN
458 section_name =
"RHO_MIXING"
460 section_name =
"MIXING"
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 "// &
478 name=
"_SECTION_PARAMETERS_", &
479 description=
"Controls the activation of the mixing procedure", &
480 usage=
"&MIXING ON", &
481 default_l_val=.true., &
482 lone_keyword_l_val=.true.)
494 description=
"Mixing method to be applied", &
496 usage=
"METHOD KERKER_MIXING", &
497 default_i_val=default_mix, &
498 enum_c_vals=
s2a(
"NONE", &
503 "MULTISECANT_MIXING"), &
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 "Multisecant scheme for mixing"))
517 description=
"Fraction of new density to be included", &
521 default_r_val=0.4_dp, &
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))", &
534 default_r_val=0.5_dp, &
535 unit_str=
"bohr^-1", &
541 name=
"PULAY_ALPHA", &
542 description=
"Fraction of new density to be added to the Pulay expansion", &
546 default_r_val=0.0_dp, &
547 usage=
"PULAY_ALPHA 0.2")
553 description=
"Fraction of residual contribution to be added to Pulay expansion", &
557 default_r_val=1.0_dp, &
558 usage=
"PULAY_BETA 0.2")
563 description=
"Minimal number of density mixing (should be greater than 0), "// &
564 "before starting DIIS", &
565 usage=
"NMIXING 1", default_i_val=2)
570 variants=
s2a(
"NPULAY",
"NBROYDEN",
"NMULTISECANT"), &
571 description=
"Number of previous steps stored for the actual mixing scheme", &
572 usage=
"NBUFFER 2", default_i_val=4)
578 description=
" w0 parameter used in Broyden mixing", &
582 default_r_val=0.01_dp, &
583 usage=
"BROY_W0 0.03")
593 default_r_val=100.0_dp, &
594 usage=
"BROY_WREF 0.2")
604 default_r_val=30.0_dp, &
605 usage=
"BROY_WMAX 10.0")
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)", &
617 default_r_val=0.00001_dp, &
618 usage=
"REGULARIZATION 0.000001")
624 description=
"Upper bound for the magnitude of the "// &
625 "unpredicted step size in the update by the "// &
626 "multisecant mixing scheme", &
630 default_r_val=0.1_dp, &
637 description=
"Control factor for the magnitude of the "// &
638 "unpredicted step size in the update by the "// &
639 "multisecant mixing scheme", &
643 default_r_val=0.05_dp, &
644 usage=
"R_FACTOR .12")
649 variants=(/
"NSKIP_MIXING"/), &
650 description=
"Number of initial iteration for which the mixing is skipped", &
651 usage=
"NSKIP 10", default_i_val=0)
656 variants=(/
"NSIMPLEMIX"/), &
657 description=
"Number of kerker damping iterations before starting other mixing procedures", &
658 usage=
"NSIMPLEMIX", default_i_val=0)
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. ", &
669 default_r_val=-1._dp, &
670 usage=
"MAX_GVEC_EXP 3.")
675 description=
"Activate the mixing of the density matrix, using the same"// &
676 " mixing coefficient applied for the g-space mixing.", &
678 lone_keyword_l_val=.true., &
679 default_l_val=.false., &