Octopus
mix.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2014 M. Marques, A. Castro, A. Rubio, G. Bertsch, M. Oliveira
2!! Copyright (C) 2024 A. Buccheri
3!!
4!! This program is free software; you can redistribute it and/or modify
5!! it under the terms of the GNU General Public License as published by
6!! the Free Software Foundation; either version 2, or (at your option)
7!! any later version.
8!!
9!! This program is distributed in the hope that it will be useful,
10!! but WITHOUT ANY WARRANTY; without even the implied warranty of
11!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12!! GNU General Public License for more details.
13!!
14!! You should have received a copy of the GNU General Public License
15!! along with this program; if not, write to the Free Software
16!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
17!! 02110-1301, USA.
18!!
19
20#include "global.h"
21
22module mix_oct_m
23 use comm_oct_m
24 use debug_oct_m
26 use global_oct_m
27 use, intrinsic :: iso_fortran_env
30 use math_oct_m
31 use mesh_oct_m
36 use parser_oct_m
41 use space_oct_m
43 use types_oct_m
45
46 implicit none
47
48 private
49 public :: &
50 mix_t, &
51 mix_init, &
52 mix_clear, &
53 mix_end, &
54 mix_dump, &
55 mix_load, &
56 mixing, &
57 dmixing, &
58 zmixing, &
60 mix_scheme, &
61 mix_d3, &
63 mixfield_t, &
71
72 ! A better design would be to have mixfield_t and mixfield_ptr_t separate from mix_t:
73 ! mix_t would contain constants, and should be immutable with only getters.
74 ! mixfield_type encapsulates the data used in mixing, and has bound procedures for
75 ! operating on this data.
76
78 type mixfield_t
79 private
80 ! Real versions of the data
81 real(real64), allocatable :: ddf(:, :, :)
82 real(real64), allocatable :: ddv(:, :, :)
83 real(real64), allocatable :: df_old(:, :)
84 real(real64), allocatable :: dvin_old(:, :)
85 real(real64), allocatable :: dvin(:, :)
86 real(real64), allocatable :: dvout(:, :)
87 real(real64), allocatable :: dvnew(:, :)
88 real(real64), allocatable :: dresidual(:, :)
89
90 ! Complex versions of the data
91 complex(real64), allocatable :: zdf(:, :, :)
92 complex(real64), allocatable :: zdv(:, :, :)
93 complex(real64), allocatable :: zf_old(:, :)
94 complex(real64), allocatable :: zvin_old(:, :)
95 complex(real64), allocatable :: zvin(:, :)
96 complex(real64), allocatable :: zvout(:, :)
97 complex(real64), allocatable :: zvnew(:, :)
98 complex(real64), allocatable :: zresidual(:, :)
99
100 type(type_t) :: func_type
101 integer :: d1, d2, d3
102 ! d1 is mesh%np, d2 vary depending on where this called
103 ! d3 is for SCF history of a quantity.
104 logical :: mix_spin_density_matrix
105 end type mixfield_t
106
107 type mixfield_ptr_t
108 private
109 type(mixfield_t), pointer :: p
110 end type mixfield_ptr_t
111
112 integer, parameter :: MAX_AUXMIXFIELD = 5
113
121 type mix_t
122 private
123 type(derivatives_t), pointer :: der
124
125 integer :: scheme
126 real(real64), allocatable :: coeff(:)
127 real(real64) :: residual_coeff
128 integer :: iter
129 ! !< include the iterations done in previous calculations.
130 integer, public :: ns
131 integer, public :: ns_restart
132 integer :: interval
133
134 integer :: last_ipos
135 ! This should have been an attribute of type(mixfield_t)
136
137 ! Fields
138 type(mixfield_t) :: mixfield
139 integer :: nauxmixfield
140 type(mixfield_ptr_t) :: auxmixfield(MAX_AUXMIXFIELD)
141 integer :: ipos
142 ! This should have been an attribute of type(mixfield_ptr_t)
143
144 ! Preconditioning
145 logical :: kerker
146 real(real64) :: kerker_factor
147 logical :: precondition
148 type(nl_operator_t) :: preconditioner
149 ! [GPAW](https://wiki.fysik.dtu.dk/gpaw/documentation/densitymix/densitymix.html)
150
151 logical :: mix_spin_density_matrix
152 contains
153 procedure :: compute_residuals_aux_field
154
155 end type mix_t
156
157 interface mixfield_set_vin
158 module procedure dmixfield_set_vin, zmixfield_set_vin
159 end interface mixfield_set_vin
160
161 interface mixfield_set_vout
162 module procedure dmixfield_set_vout, zmixfield_set_vout
163 end interface mixfield_set_vout
164
165 interface mixfield_get_vnew
166 module procedure dmixfield_get_vnew, zmixfield_get_vnew
167 end interface mixfield_get_vnew
168
169contains
170
172 subroutine mix_init(smix, namespace, space, der, d1, d2, def_, func_type_, prefix_)
173 type(mix_t), intent(out) :: smix
174 type(namespace_t), intent(in) :: namespace
175 class(space_t), intent(in) :: space
176 type(derivatives_t), target, intent(in) :: der
177 integer, intent(in) :: d1
178 integer, intent(in) :: d2
179 integer, optional, intent(in) :: def_
180 type(type_t), optional, intent(in) :: func_type_
181 character(len=*), optional, intent(in) :: prefix_
182
183 integer :: def, ii
184 character(len=32) :: prefix
185 type(type_t) :: func_type
186 real(real64) :: coeff
188 push_sub(mix_init)
190 smix%der => der
192 def = option__mixingscheme__broyden
193 if (present(def_)) def = def_
194 if (present(func_type_)) then
195 func_type = func_type_
196 else
197 func_type = type_float
198 end if
199 prefix = ''
200 if (present(prefix_)) prefix = prefix_
201
202 call messages_obsolete_variable(namespace, 'TypeOfMixing', 'MixingScheme')
203
204 !%Variable MixingScheme
205 !%Type integer
206 !%Default broyden
207 !%Section SCF::Mixing
208 !%Description
209 !% The scheme used to produce, at each iteration in the self-consistent cycle
210 !% that attempts to solve the Kohn-Sham equations, the input density from the value
211 !% of the input and output densities of previous iterations.
212 !%Option linear 0
213 !% Simple linear mixing.
214 !%Option broyden 2
215 !% Broyden scheme [C. G Broyden, <i>Math. Comp.</i> <b>19</b>, 577 (1965);
216 !% D. D. Johnson, <i>Phys. Rev. B</i> <b>38</b>, 12807 (1988)].
217 !% The scheme is slightly adapted, see the comments in the code.
218 !% For complex functions (e.g. Sternheimer with <tt>EMEta</tt> > 0), we use the generalization
219 !% with a complex dot product.
220 !%Option diis 9
221 !% Direct inversion in the iterative subspace (diis)
222 !% scheme [P. Pulay, <i>Chem. Phys. Lett.</i>, <b>73</b>, 393
223 !% (1980)] as described in [G. Kresse, and J. Furthmueller,
224 !% <i>Phys. Rev. B</i> <b>54</b>, 11169 (1996)].
225 !%End
226 call parse_variable(namespace, trim(prefix)//'MixingScheme', def, smix%scheme)
227 if (.not. varinfo_valid_option('MixingScheme', smix%scheme)) then
228 call messages_input_error(namespace, 'MixingScheme', 'invalid option')
229 end if
230 call messages_print_var_option("MixingScheme", smix%scheme, namespace=namespace)
232 !%Variable MixingPreconditioner
233 !%Type logical
234 !%Default false
235 !%Section SCF::Mixing
236 !%Description
237 !% (Experimental) If set to yes, Octopus will use a preconditioner
238 !% for the mixing operator.
239 !% This preconditioner is disabled for systems with dimension other than 3.
240 !%End
241 call parse_variable(namespace, trim(prefix)+'MixingPreconditioner', .false., smix%precondition)
242 if (der%dim /= 3) smix%precondition = .false.
243 if (smix%precondition) call messages_experimental('MixingPreconditioner', namespace=namespace)
245 !%Variable Mixing
246 !%Type float
247 !%Default 0.3
248 !%Section SCF::Mixing
249 !%Description
250 !% The linear, Broyden and DIIS scheme depend on a "mixing parameter", set by this variable.
251 !% Must be 0 < <tt>Mixing</tt> <= 1.
252 !%End
253 call parse_variable(namespace, trim(prefix)+'Mixing', 0.3_real64, coeff)
254 if (coeff <= m_zero .or. coeff > m_one) then
255 call messages_input_error(namespace, 'Mixing', 'Value should be positive and smaller than one')
256 end if
257 safe_allocate(smix%coeff(1:d2))
258 smix%coeff = coeff
259
260 if (d2 > 1) then
261 !%Variable MixingSpinDensityMatrix
262 !%Type logical
263 !%Default false
264 !%Section SCF::Mixing
265 !%Description
266 !% If set to yes, Octopus mixes the components up, down, and real and imaginary parts of
267 !% the up down (for spinor calculations) of the density or potential.
268 !% By default, Octopus mixes the magnetization and the charge density with a different weight,
269 !% where the magnetization mixing coefficient is given by <tt>MixingMagnetization</tt>
270 !%End
271 call parse_variable(namespace, trim(prefix)+'MixingSpinDensityMatrix', .false., smix%mix_spin_density_matrix)
272
273 !%Variable MixingMagnetization
274 !%Type float
275 !%Default 1.5
276 !%Section SCF::Mixing
277 !%Description
278 !% Same as <tt>Mixing</tt>, but for the "magnetization".
279 !% The default value is taken from D. D. Johnson, <i>Phys. Rev. B</i> <b>38</b>, 12807 (1988).
280 !%End
281 call parse_variable(namespace, trim(prefix)+'MixingMagnetization', 1.5_real64, coeff)
282
283 if (.not. smix%mix_spin_density_matrix) smix%coeff(2:d2) = coeff
284 else
285 smix%mix_spin_density_matrix = .true.
286 end if
287
288 !%Variable MixingResidual
289 !%Type float
290 !%Default 0.05
291 !%Section SCF::Mixing
292 !%Description
293 !% In the DIIS mixing it is benefitial to include a bit of
294 !% residual into the mixing. This parameter controls this amount.
295 !%End
296 call parse_variable(namespace, trim(prefix)+'MixingResidual', 0.05_real64, smix%residual_coeff)
297 if (smix%residual_coeff <= m_zero .or. smix%residual_coeff > m_one) then
298 call messages_input_error(namespace, 'MixingResidual', 'Value should be positive and smaller than one.')
299 end if
300
301 !%Variable MixNumberSteps
302 !%Type integer
303 !%Default 4
304 !%Section SCF::Mixing
305 !%Description
306 !% In the Broyden scheme, the new input density or potential is constructed
307 !% from the values of the densities/potentials of a given number of previous iterations.
308 !% This number is set by this variable. Must be greater than 1.
309 !%End
310 if (smix%scheme /= option__mixingscheme__linear) then
311 call parse_variable(namespace, trim(prefix)//'MixNumberSteps', 4, smix%ns)
312 if (smix%ns <= 1) call messages_input_error(namespace, 'MixNumberSteps')
313 else
314 smix%ns = 0
315 end if
316
317 !%Variable MixingRestart
318 !%Type integer
319 !%Default 20
320 !%Section SCF::Mixing
321 !%Description
322 !% In the Broyden scheme, the mixing is restarted after
323 !% the number of iterations given by this variable.
324 !% Set this to zero to disable restarting the mixing.
325 !%End
326 if (smix%scheme /= option__mixingscheme__linear) then
327 call parse_variable(namespace, trim(prefix)//'MixingRestart', 20, smix%ns_restart)
328 if (smix%ns_restart < 0) call messages_input_error(namespace, 'MixingRestart')
329 else
330 smix%ns_restart = 0
331 end if
332
333 write(message(1), '(A,I4,A,I4,A)') "Info: Mixing uses ", smix%ns, " steps and restarts after ", &
334 smix%ns_restart, " steps."
335 call messages_info(1, namespace=namespace)
336
337 !%Variable MixInterval
338 !%Type integer
339 !%Default 1
340 !%Section SCF::Mixing
341 !%Description
342 !% When this variable is set to a value different than 1 (the
343 !% default) a combined mixing scheme will be used, with MixInterval
344 !% - 1 steps of linear mixing followed by 1 step of the selected
345 !% mixing. For the moment this variable only works with DIIS mixing.
346 !%End
347 call parse_variable(namespace, trim(prefix)//'MixInterval', 1, smix%interval)
348 if (smix%interval < 1) call messages_input_error(namespace, 'MixInterval', 'MixInterval must be larger or equal than 1')
349
350 smix%iter = 0
351
352 !%Variable MixingKerker
353 !%Type logical
354 !%Default false
355 !%Section SCF::Mixing
356 !%Description
357 !% (Experimental) If set to yes, Octopus will use the Kerker preconditioner
358 !% for the mixing operator applied in the linear and Broyden mixing schemes.
359 !% When using preconditioning with the Broyden scheme, the user should increase the <tt>Mixing</tt> from its default
360 !% to between 0.5 and 0.8, for optimal results.
361 !% The implementation follows Yoshinori Shiihara et al., Modelling Simul. Mater. Sci. Eng. 16 (2008), 035004
362 !%End
363 call parse_variable(namespace, trim(prefix)+'MixingKerker', .false., smix%kerker)
364 if(smix%kerker) call messages_experimental('MixingKerker')
365
366 !%Variable MixingKerkerFactor
367 !%Type float
368 !%Default 1.0
369 !%Section SCF::Mixing
370 !%Description
371 !% The screening factor, $q_0$ in the Kerker preconditioner in units of inverse length.
372 !% For small wave vectors, q, screening behaves like $\frac{Aq}{q_0}$, where A is the mixing coefficient.
373 !% An optimal value is determined empirically for a given system and mixing coeffient, however the default
374 !% is a reasonable choice in many cases.
375 !%End
376 call parse_variable(namespace, trim(prefix)+'MixingKerkerFactor', 1._real64, smix%kerker_factor)
377
378 smix%nauxmixfield = 0
379 do ii = 1,max_auxmixfield
380 nullify(smix%auxmixfield(ii)%p)
381 end do
382
383 call mixfield_init(smix, smix%mixfield, d1, d2, smix%ns, func_type)
384 call mix_clear(smix)
385 if (smix%precondition) call init_preconditioner()
386
387 pop_sub(mix_init)
388
389 contains
390
391 subroutine init_preconditioner()
392
393 integer :: ns, maxp, ip, is
394 real(real64), parameter :: weight = 50.0_real64
395
396 ! This the mixing preconditioner from GPAW:
397 !
398 ! https://wiki.fysik.dtu.dk/gpaw/documentation/densitymix/densitymix.html
399 !
400
401 assert(.not. der%mesh%use_curvilinear)
402 assert(der%dim == 3)
403
404 call nl_operator_init(smix%preconditioner, "Mixing preconditioner")
405 call stencil_cube_get_lapl(smix%preconditioner%stencil, der%dim, 1)
406 call nl_operator_build(space, der%mesh, smix%preconditioner, der%mesh%np, const_w = .not. der%mesh%use_curvilinear)
407
408 ns = smix%preconditioner%stencil%size
409
410 if (smix%preconditioner%const_w) then
411 maxp = 1
412 else
413 maxp = der%mesh%np
414 end if
415
416 do ip = 1, maxp
417
418 do is = 1, ns
419 select case (sum(abs(smix%preconditioner%stencil%points(1:der%dim, is))))
420 case (0)
421 smix%preconditioner%w(is, ip) = m_one + weight/8.0_real64
422 case (1)
423 smix%preconditioner%w(is, ip) = weight/16.0_real64
424 case (2)
425 smix%preconditioner%w(is, ip) = weight/32.0_real64
426 case (3)
427 smix%preconditioner%w(is, ip) = weight/64.0_real64
428 case default
429 assert(.false.)
430 end select
431
432 end do
433 end do
434
435 call nl_operator_allocate_gpu_buffers(smix%preconditioner)
436 call nl_operator_update_gpu_buffers(smix%preconditioner)
437 call nl_operator_output_weights(smix%preconditioner)
438
439 end subroutine init_preconditioner
440
441 end subroutine mix_init
442
443
444 ! ---------------------------------------------------------
445 subroutine mix_clear(smix)
446 type(mix_t), intent(inout) :: smix
447
448 push_sub(mix_clear)
449
450 call mixfield_clear(smix%scheme, smix%mixfield)
451
452 smix%iter = 0
453 smix%last_ipos = 0
454
455 pop_sub(mix_clear)
456 end subroutine mix_clear
457
458
459 ! ---------------------------------------------------------
460 subroutine mix_end(smix)
461 type(mix_t), intent(inout) :: smix
462
463 integer :: ii
464
465 push_sub(mix_end)
466
467 if (smix%precondition) call nl_operator_end(smix%preconditioner)
468
469 call mixfield_end(smix, smix%mixfield)
470
471 smix%nauxmixfield = 0
472 do ii = 1,max_auxmixfield
473 nullify(smix%auxmixfield(ii)%p)
474 end do
475
476 safe_deallocate_a(smix%coeff)
477
478 pop_sub(mix_end)
479 end subroutine mix_end
480
481
482 ! ---------------------------------------------------------
483 subroutine mix_dump(namespace, restart, smix, space, mesh, ierr)
484 type(namespace_t), intent(in) :: namespace
485 type(restart_t), intent(in) :: restart
486 type(mix_t), intent(in) :: smix
487 class(space_t), intent(in) :: space
488 class(mesh_t), intent(in) :: mesh
489 integer, intent(out) :: ierr
490
491 integer :: iunit, id2, id3, err, err2(4)
492 character(len=40) :: lines(7)
493 character(len=80) :: filename
494
495 push_sub(mix_dump)
496
497 ierr = 0
498
499 if (restart_skip(restart)) then
500 pop_sub(mix_dump)
501 return
502 end if
503
504 message(1) = "Debug: Writing mixing restart."
505 call messages_info(1, namespace=namespace, debug_only=.true.)
506
507 ! functions to be written need to be compatible with the mesh
508 assert(mesh%np == smix%mixfield%d1)
509
510 ! First we write some information about the mixing
511 iunit = restart_open(restart, 'mixing')
512 write(lines(1), '(a11,i1)') 'scheme= ', smix%scheme
513 ! Number of global mesh points have to be written, not only smix%d1
514 write(lines(2), '(a11,i10)') 'd1= ', mesh%np_global
515 write(lines(3), '(a11,i10)') 'd2= ', smix%mixfield%d2
516 write(lines(4), '(a11,i10)') 'd3= ', smix%mixfield%d3
517 write(lines(5), '(a11,i10)') 'iter= ', smix%iter
518 write(lines(6), '(a11,i10)') 'ns= ', smix%ns
519 write(lines(7), '(a11,i10)') 'last_ipos= ', smix%last_ipos
520 call restart_write(restart, iunit, lines, 7, err)
521 ierr = ierr + err
522 call restart_close(restart, iunit)
523
524 ! Now we write the different functions.
525 ! These are not needed when using linear mixing, so we will make sure we skip this step in that case.
526 err2 = 0
527 if (smix%scheme /= option__mixingscheme__linear) then
528 do id2 = 1, smix%mixfield%d2
529 do id3 = 1, smix%mixfield%d3
530
531 write(filename,'(a3,i2.2,i2.2)') 'df_', id2, id3
532 if (smix%mixfield%func_type == type_float) then
533 call restart_write_mesh_function(restart, space, filename, mesh, smix%mixfield%ddf(1:mesh%np, id2, id3), err)
534 else
535 call restart_write_mesh_function(restart, space, filename, mesh, smix%mixfield%zdf(1:mesh%np, id2, id3), err)
536 end if
537 err2(1) = err2(1) + err
539 write(filename,'(a3,i2.2,i2.2)') 'dv_', id2, id3
540 if (smix%mixfield%func_type == type_float) then
541 call restart_write_mesh_function(restart, space, filename, mesh, smix%mixfield%ddv(1:mesh%np, id2, id3), err)
542 else
543 call restart_write_mesh_function(restart, space, filename, mesh, smix%mixfield%zdv(1:mesh%np, id2, id3), err)
544 end if
545 err2(2) = err2(2) + err
546
547 end do
548
549 write(filename,'(a6,i2.2)') 'f_old_', id2
550 if (smix%mixfield%func_type == type_float) then
551 call restart_write_mesh_function(restart, space, filename, mesh, smix%mixfield%df_old(1:mesh%np, id2), err)
552 else
553 call restart_write_mesh_function(restart, space, filename, mesh, smix%mixfield%zf_old(1:mesh%np, id2), err)
554 end if
555 err2(3) = err2(3) + err
556
557 write(filename,'(a8,i2.2)') 'vin_old_', id2
558 if (smix%mixfield%func_type == type_float) then
559 call restart_write_mesh_function(restart, space, filename, mesh, smix%mixfield%dvin_old(1:mesh%np, id2), err)
560 else
561 call restart_write_mesh_function(restart, space, filename, mesh, smix%mixfield%zvin_old(1:mesh%np, id2), err)
562 end if
563 err2(4) = err2(4) + err
564
565 end do
566
567 if (err2(1) /= 0) ierr = ierr + 2
568 if (err2(2) /= 0) ierr = ierr + 4
569 if (err2(3) /= 0) ierr = ierr + 8
570 if (err2(4) /= 0) ierr = ierr + 16
571 end if
572
573 message(1) = "Debug: Writing mixing restart done."
574 call messages_info(1, namespace=namespace, debug_only=.true.)
575
576 pop_sub(mix_dump)
577 end subroutine mix_dump
578
579
580 !---------------------------------------------------------
581 subroutine mix_load(namespace, restart, smix, space, mesh, ierr)
582 type(namespace_t), intent(in) :: namespace
583 type(restart_t), intent(in) :: restart
584 type(mix_t), intent(inout) :: smix
585 class(space_t), intent(in) :: space
586 class(mesh_t), intent(in) :: mesh
587 integer, intent(out) :: ierr
588
589 integer :: iunit, err, err2(4)
590 integer :: scheme, d1, d2, d3, ns
591 integer :: id2, id3
592 character(len=11) :: str
593 character(len=80) :: filename
594 character(len=256) :: lines(7)
595
596 push_sub(mix_load)
597
598 ierr = 0
599
600 if (restart_skip(restart)) then
601 ierr = -1
602 pop_sub(mix_load)
603 return
604 end if
605
606 message(1) = "Debug: Reading mixing restart."
607 call messages_info(1, namespace=namespace, debug_only=.true.)
608
609 ! First we read some information about the mixing
610 iunit = restart_open(restart, 'mixing')
611 call restart_read(restart, iunit, lines, 7, err)
612 if (err /= 0) then
613 ierr = ierr + 1
614 else
615 read(lines(1), *) str, scheme
616 read(lines(2), *) str, d1
617 read(lines(3), *) str, d2
618 read(lines(4), *) str, d3
619 read(lines(5), *) str, smix%iter
620 read(lines(6), *) str, ns
621 read(lines(7), *) str, smix%last_ipos
622 end if
623 call restart_close(restart, iunit)
624
625
626 if (ierr == 0) then
627 ! We can only use the restart information if the mixing scheme and the number of steps used remained the same
628 if (scheme /= smix%scheme .or. ns /= smix%ns) then
629 message(1) = "The mixing scheme from the restart data is not the same as the one used in the current calculation."
630 call messages_warning(1, namespace=namespace)
631 ierr = ierr + 2
632 end if
633
634 ! Check the dimensions of the arrays to be read
635 if (mesh%np_global /= d1 .or. mesh%np /= smix%mixfield%d1 .or. d2 /= smix%mixfield%d2) then
636 message(1) = "The dimensions of the arrays from the mixing restart data"
637 message(2) = "are not the same as the ones used in this calculation."
638 call messages_warning(2, namespace=namespace)
639 ierr = ierr + 4
640 end if
641 end if
642
643
644 ! Now we read the different functions.
645 ! Note that we may have more or less functions than the ones needed (d3 /= smix%d3)
646 if (ierr == 0) then
647 if (smix%scheme /= option__mixingscheme__linear) then
648 err2 = 0
649 do id2 = 1, smix%mixfield%d2
650 do id3 = 1, smix%mixfield%d3
651
652 write(filename,'(a3,i2.2,i2.2)') 'df_', id2, id3
653 if (smix%mixfield%func_type == type_float) then
654 call restart_read_mesh_function(restart, space, filename, mesh, smix%mixfield%ddf(1:mesh%np, id2, id3), err)
655 else
656 call restart_read_mesh_function(restart, space, filename, mesh, smix%mixfield%zdf(1:mesh%np, id2, id3), err)
657 end if
658 if (err /= 0) err2(1) = err2(1) + 1
659
660 write(filename,'(a3,i2.2,i2.2)') 'dv_', id2, id3
661 if (smix%mixfield%func_type == type_float) then
662 call restart_read_mesh_function(restart, space, filename, mesh, smix%mixfield%ddv(1:mesh%np, id2, id3), err)
663 else
664 call restart_read_mesh_function(restart, space, filename, mesh, smix%mixfield%zdv(1:mesh%np, id2, id3), err)
665 end if
666 if (err /= 0) err2(2) = err2(2) + 1
667
668 end do
669
670 write(filename,'(a6,i2.2)') 'f_old_', id2
671 if (smix%mixfield%func_type == type_float) then
672 call restart_read_mesh_function(restart, space, filename, mesh, smix%mixfield%df_old(1:mesh%np, id2), err)
673 else
674 call restart_read_mesh_function(restart, space, filename, mesh, smix%mixfield%zf_old(1:mesh%np, id2), err)
675 end if
676 if (err /= 0) err2(3) = err2(3) + 1
677
678 write(filename,'(a8,i2.2)') 'vin_old_', id2
679 if (smix%mixfield%func_type == type_float) then
680 call restart_read_mesh_function(restart, space, filename, mesh, smix%mixfield%dvin_old(1:mesh%np, id2), err)
681 else
682 call restart_read_mesh_function(restart, space, filename, mesh, smix%mixfield%zvin_old(1:mesh%np, id2), err)
683 end if
684 if (err /= 0) err2(4) = err2(4) + 1
685
686 end do
687
688 if (err2(1) /= 0) ierr = ierr + 8
689 if (err2(2) /= 0) ierr = ierr + 16
690 if (err2(3) /= 0) ierr = ierr + 32
691 if (err2(4) /= 0) ierr = ierr + 64
692 end if
693 end if
694
695 if (ierr /= 0) then
696 ! Something went wront, so make sure we start from scratch
697 call mix_clear(smix)
698 end if
699
700 message(1) = "Debug: Reading mixing restart done."
701 call messages_info(1, namespace=namespace, debug_only=.true.)
702
703 pop_sub(mix_load)
704 end subroutine mix_load
705
706 real(real64) pure function mix_coefficient(this) result(coefficient)
707 type(mix_t), intent(in) :: this
708
709 coefficient = this%coeff(1)
710 end function mix_coefficient
711
712 integer pure function mix_scheme(this) result(scheme)
713 type(mix_t), intent(in) :: this
714
715 scheme = this%scheme
716 end function mix_scheme
717
718 integer pure function mix_d3(this)
719 type(mix_t), intent(in) :: this
720
721 mix_d3 = this%mixfield%d3
722 end function mix_d3
723
724 subroutine mix_get_field(this, mixfield)
725 type(mix_t), target, intent(in) :: this
726 type(mixfield_t), pointer, intent(out) :: mixfield
727
728 mixfield => this%mixfield
729 end subroutine mix_get_field
730
732 subroutine mixing(namespace, smix)
733 type(namespace_t), intent(in) :: namespace
734 type(mix_t), intent(inout) :: smix
735
736 push_sub(mixing)
737
738 if (smix%mixfield%func_type == type_float) then
739 call dmixing(namespace, smix, smix%mixfield%dvin, smix%mixfield%dvout, smix%mixfield%dvnew)
740 else
741 call zmixing(namespace, smix, smix%mixfield%zvin, smix%mixfield%zvout, smix%mixfield%zvnew)
742 end if
743
744 pop_sub(mixing)
745 end subroutine mixing
746
747 subroutine mix_add_auxmixfield(namespace, smix, mixfield)
748 type(namespace_t), intent(in) :: namespace
749 type(mix_t), intent(inout) :: smix
750 type(mixfield_t), target, intent(in) :: mixfield
751
752 push_sub(mix_add_auxmixfield)
753
754 smix%nauxmixfield = smix%nauxmixfield + 1
755 smix%auxmixfield(smix%nauxmixfield)%p => mixfield
756
757 if (smix%scheme == option__mixingscheme__diis) then
758 message(1) = 'Mixing scheme DIIS is not implemented for auxiliary mixing fields'
759 call messages_fatal(1, namespace=namespace)
760 end if
761
762 pop_sub(mix_add_auxmixfield)
763 end subroutine mix_add_auxmixfield
764
766 subroutine mixfield_init(smix, mixfield, d1, d2, d3, func_type)
767 type(mix_t), intent(in) :: smix
768 type(mixfield_t), intent(inout) :: mixfield
769 integer, intent(in) :: d1, d2, d3
770 type(type_t), intent(in) :: func_type
771
772 push_sub(mixfield_init)
773
774 mixfield%d1 = d1
775 mixfield%d2 = d2
776 mixfield%d3 = d3
777
778 mixfield%func_type = func_type
779
780 mixfield%mix_spin_density_matrix = smix%mix_spin_density_matrix
781
782 if (smix%scheme /= option__mixingscheme__linear) then
783 if (mixfield%func_type == type_float) then
784 safe_allocate( mixfield%ddf(1:d1, 1:d2, 1:d3))
785 safe_allocate( mixfield%ddv(1:d1, 1:d2, 1:d3))
786 safe_allocate(mixfield%dvin_old(1:d1, 1:d2))
787 safe_allocate( mixfield%df_old(1:d1, 1:d2))
788 else
789 safe_allocate( mixfield%zdf(1:d1, 1:d2, 1:d3))
790 safe_allocate( mixfield%zdv(1:d1, 1:d2, 1:d3))
791 safe_allocate(mixfield%zvin_old(1:d1, 1:d2))
792 safe_allocate( mixfield%zf_old(1:d1, 1:d2))
793 end if
794 end if
795
796 if (mixfield%func_type == type_float) then
797 safe_allocate(mixfield%dvin(1:d1, 1:d2))
798 safe_allocate(mixfield%dvout(1:d1, 1:d2))
799 safe_allocate(mixfield%dvnew(1:d1, 1:d2))
800 safe_allocate(mixfield%dresidual(1:d1, 1:d2))
801 else
802 safe_allocate(mixfield%zvin(1:d1, 1:d2))
803 safe_allocate(mixfield%zvout(1:d1, 1:d2))
804 safe_allocate(mixfield%zvnew(1:d1, 1:d2))
805 safe_allocate(mixfield%zresidual(1:d1, 1:d2))
806 end if
807
808 pop_sub(mixfield_init)
809 end subroutine mixfield_init
810
812 subroutine mixfield_end(smix, mixfield)
813 type(mix_t), intent(inout) :: smix
814 type(mixfield_t), intent(inout) :: mixfield
815
816 push_sub(mixfield_end)
818 ! Arrays got allocated for all mixing schemes, except linear mixing
819 if (smix%scheme /= option__mixingscheme__linear) then
820 if (mixfield%func_type == type_float) then
821 safe_deallocate_a(mixfield%ddf)
822 safe_deallocate_a(mixfield%ddv)
823 safe_deallocate_a(mixfield%dvin_old)
824 safe_deallocate_a(mixfield%df_old)
825 else
826 safe_deallocate_a(mixfield%zdf)
827 safe_deallocate_a(mixfield%zdv)
828 safe_deallocate_a(mixfield%zvin_old)
829 safe_deallocate_a(mixfield%zf_old)
830 end if
831 end if
832
833 if (mixfield%func_type == type_float) then
834 safe_deallocate_a(mixfield%dvin)
835 safe_deallocate_a(mixfield%dvout)
836 safe_deallocate_a(mixfield%dvnew)
837 safe_deallocate_a(mixfield%dresidual)
838 else
839 safe_deallocate_a(mixfield%zvin)
840 safe_deallocate_a(mixfield%zvout)
841 safe_deallocate_a(mixfield%zvnew)
842 safe_deallocate_a(mixfield%zresidual)
843 end if
844
845 pop_sub(mixfield_end)
846 end subroutine mixfield_end
847
849 subroutine mixfield_clear(scheme, mixfield)
850 integer, intent(in) :: scheme
851 type(mixfield_t), intent(inout) :: mixfield
852 integer :: d1, d2, d3
853
854 push_sub(mixfield_clear)
855
856 d1 = mixfield%d1
857 d2 = mixfield%d2
858 d3 = mixfield%d3
860 if (scheme /= option__mixingscheme__linear) then
861 if (mixfield%func_type == type_float) then
862 assert(allocated(mixfield%ddf))
863 mixfield%ddf(1:d1, 1:d2, 1:d3) = m_zero
864 mixfield%ddv(1:d1, 1:d2, 1:d3) = m_zero
865 mixfield%dvin_old(1:d1, 1:d2) = m_zero
866 mixfield%df_old(1:d1, 1:d2) = m_zero
867 else
868 assert(allocated(mixfield%zdf))
869 mixfield%zdf(1:d1, 1:d2, 1:d3) = m_z0
870 mixfield%zdv(1:d1, 1:d2, 1:d3) = m_z0
871 mixfield%zvin_old(1:d1, 1:d2) = m_z0
872 mixfield%zf_old(1:d1, 1:d2) = m_z0
873 end if
874 end if
875
876 if (mixfield%func_type == type_float) then
877 mixfield%dvin(1:d1, 1:d2) = m_zero
878 mixfield%dvout(1:d1, 1:d2) = m_zero
879 mixfield%dvnew(1:d1, 1:d2) = m_zero
880 mixfield%dresidual(1:d1, 1:d2) = m_zero
881 else
882 mixfield%zvin(1:d1, 1:d2) = m_z0
883 mixfield%zvout(1:d1, 1:d2) = m_z0
884 mixfield%zvnew(1:d1, 1:d2) = m_z0
885 mixfield%zresidual(1:d1, 1:d2) = m_z0
886 end if
887
888 pop_sub(mixfield_clear)
889 end subroutine mixfield_clear
890
899 subroutine compute_residuals_aux_field(this)
900 class(mix_t), intent(inout) :: this
901
902 type(mixfield_t), pointer :: aux_field
903 integer :: dims(2)
904 integer :: i
907
908 do i = 1, this%nauxmixfield
909 aux_field => this%auxmixfield(i)%p
910 dims = [aux_field%d1, aux_field%d2]
911
912 if (aux_field%func_type == type_float) then
913 call dcompute_residual(this, dims, aux_field%dvin, aux_field%dvout, aux_field%dresidual)
914 else
915 call zcompute_residual(this, dims, aux_field%zvin, aux_field%zvout, aux_field%zresidual)
916 end if
917
918 end do
919 nullify(aux_field)
920
922
923 end subroutine compute_residuals_aux_field
924
936 subroutine linear_mixing_aux_field(smix)
937 type(mix_t), intent(inout) :: smix
938
939 type(mixfield_t), pointer :: field
940 integer :: i
941
943
944 call smix%compute_residuals_aux_field()
945
946 do i = 1, smix%nauxmixfield
947 field => smix%auxmixfield(i)%p
948
949 if (field%func_type == type_float) then
950 call dmixing_linear(field%d1, field%d2, smix%coeff, field%dvin, field%dresidual, field%dvnew)
951 else
952 call zmixing_linear(field%d1, field%d2, smix%coeff, field%zvin, field%zresidual, field%zvnew)
953 end if
954
955 end do
956
957 nullify(field)
958
960 end subroutine linear_mixing_aux_field
961
962#include "undef.F90"
963#include "real.F90"
964
965#include "mix_inc.F90"
966
967#include "undef.F90"
968#include "complex.F90"
969
970#include "mix_inc.F90"
971
972end module mix_oct_m
973
974!! Local Variables:
975!! mode: f90
976!! coding: utf-8
977!! End:
subroutine init_preconditioner()
Definition: mix.F90:485
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
real(real64), parameter, public m_zero
Definition: global.F90:188
real(real64), parameter, public m_one
Definition: global.F90:189
This module is intended to contain "only mathematical" functions and procedures.
Definition: math.F90:115
This module defines various routines, operating on mesh functions.
This module defines the meshes, which are used in Octopus.
Definition: mesh.F90:118
subroutine, public messages_warning(no_lines, all_nodes, namespace)
Definition: messages.F90:537
subroutine, public messages_obsolete_variable(namespace, name, rep)
Definition: messages.F90:1045
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_input_error(namespace, var, details, row, column)
Definition: messages.F90:713
subroutine, public messages_experimental(name, namespace)
Definition: messages.F90:1085
subroutine, public messages_info(no_lines, iunit, debug_only, stress, all_nodes, namespace)
Definition: messages.F90:616
subroutine, public mixfield_end(smix, mixfield)
Deallocate all arrays of a mixfield instance.
Definition: mix.F90:906
integer pure function, public mix_scheme(this)
Definition: mix.F90:806
subroutine dmixfield_set_vin(mixfield, vin)
Definition: mix.F90:1672
real(real64) pure function, public mix_coefficient(this)
Definition: mix.F90:800
subroutine, public mixing(namespace, smix)
Main entry-point to SCF mixer.
Definition: mix.F90:826
subroutine, public mixfield_init(smix, mixfield, d1, d2, d3, func_type)
Initialise all attributes of a mixfield instance.
Definition: mix.F90:860
subroutine zmixfield_get_vnew(mixfield, vnew)
Definition: mix.F90:2431
subroutine dcompute_residual(smix, dims, vin, vout, residual)
Compute the residual of the potential (or density) for SCF mixing.
Definition: mix.F90:1215
subroutine, public mix_get_field(this, mixfield)
Definition: mix.F90:818
subroutine compute_residuals_aux_field(this)
Compute the residuals of the auxilliary fields.
Definition: mix.F90:993
subroutine zmixfield_set_vout(mixfield, vout)
Definition: mix.F90:2412
subroutine, public mix_add_auxmixfield(namespace, smix, mixfield)
Definition: mix.F90:841
subroutine dmixfield_get_vnew(mixfield, vnew)
Definition: mix.F90:1738
subroutine dmixing_linear(d1, d2, coeff, vin, residual, vnew)
Linear mixing of the input and output potentials.
Definition: mix.F90:1183
subroutine, public mix_dump(namespace, restart, smix, space, mesh, ierr)
Definition: mix.F90:577
subroutine, public mixfield_clear(scheme, mixfield)
Zero all potential and field attributes of a mixfield instance.
Definition: mix.F90:943
subroutine, public mix_load(namespace, restart, smix, space, mesh, ierr)
Definition: mix.F90:675
subroutine, public mix_init(smix, namespace, space, der, d1, d2, def_, func_type_, prefix_)
Initialise mix_t instance.
Definition: mix.F90:266
subroutine zmixfield_set_vin(mixfield, vin)
Definition: mix.F90:2393
subroutine, public zmixing(namespace, smix, vin, vout, vnew)
Mix the input and output potentials (or densities) according to some scheme.
Definition: mix.F90:1850
integer pure function, public mix_d3(this)
Definition: mix.F90:812
subroutine dmixfield_set_vout(mixfield, vout)
Definition: mix.F90:1705
subroutine zcompute_residual(smix, dims, vin, vout, residual)
Compute the residual of the potential (or density) for SCF mixing.
Definition: mix.F90:1936
subroutine, public dmixing(namespace, smix, vin, vout, vnew)
Mix the input and output potentials (or densities) according to some scheme.
Definition: mix.F90:1129
subroutine linear_mixing_aux_field(smix)
Linear mixing of the auxilliary fields.
Definition: mix.F90:1030
subroutine zmixing_linear(d1, d2, coeff, vin, residual, vnew)
Linear mixing of the input and output potentials.
Definition: mix.F90:1904
subroutine, public mix_end(smix)
Definition: mix.F90:554
subroutine, public mix_clear(smix)
Definition: mix.F90:539
This module defines non-local operators.
subroutine, public nl_operator_init(op, label)
initialize an instance of a non-local operator by setting the label
subroutine, public nl_operator_update_gpu_buffers(op)
subroutine, public nl_operator_output_weights(this)
subroutine, public nl_operator_end(op)
subroutine, public nl_operator_build(space, mesh, op, np, const_w, regenerate)
subroutine, public nl_operator_allocate_gpu_buffers(op)
subroutine, public restart_read(restart, iunit, lines, nlines, ierr)
Definition: restart.F90:936
subroutine, public restart_close(restart, iunit)
Close a file previously opened with restart_open.
Definition: restart.F90:953
subroutine, public restart_write(restart, iunit, lines, nlines, ierr)
Definition: restart.F90:909
logical pure function, public restart_skip(restart)
Returns true if the restart information should neither be read nor written. This might happen because...
Definition: restart.F90:970
integer function, public restart_open(restart, filename, status, position, silent)
Open file "filename" found inside the current restart directory. Depending on the type of restart,...
Definition: restart.F90:862
This module is intended to contain "only mathematical" functions and procedures.
Definition: solvers.F90:115
This module defines routines, generating operators for a cubic stencil.
subroutine, public stencil_cube_get_lapl(this, dim, order)
type(type_t), public type_float
Definition: types.F90:133
class representing derivatives
Describes mesh distribution to nodes.
Definition: mesh.F90:186
God class for mixing.
Definition: mix.F90:214
Quantities used in mixing: Input, output and new potentials, and the residuals.
Definition: mix.F90:171
int true(void)