Octopus
eigensolver.F90
Go to the documentation of this file.
1!! Copyright (C) 2002-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch
2!!
3!! This program is free software; you can redistribute it and/or modify
4!! it under the terms of the GNU General Public License as published by
5!! the Free Software Foundation; either version 2, or (at your option)
6!! any later version.
7!!
8!! This program is distributed in the hope that it will be useful,
9!! but WITHOUT ANY WARRANTY; without even the implied warranty of
10!! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11!! GNU General Public License for more details.
12!!
13!! You should have received a copy of the GNU General Public License
14!! along with this program; if not, write to the Free Software
15!! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
16!! 02110-1301, USA.
17!!
18
19#include "global.h"
20
22 use batch_oct_m
24 use debug_oct_m
32 use global_oct_m
33 use grid_oct_m
37 use, intrinsic :: iso_fortran_env
41 use loct_oct_m
42 use mesh_oct_m
46 use mpi_oct_m
50 use parser_oct_m
54 use smear_oct_m
55 use space_oct_m
62 use types_oct_m
63 use unit_oct_m
66 use xc_oct_m
67
68 implicit none
69
70 private
71 public :: &
75
76 type eigensolver_t
77 private
78 integer, public :: es_type
79
80 real(real64), public :: tolerance
81 integer, public :: es_maxiter
82
83 real(real64) :: tau
84 real(real64) :: tau0
85 real(real64) :: time
86 integer :: it_propagator
87 type(potential_interpolation_t) :: vks_old
88 real(real64), allocatable :: normalization_energies(:, :)
89 ! !! evolution eigensolver
90 real(real64), allocatable :: normalization_energies_prev(:, :)
92 logical :: variable_timestep
93
95 real(real64), allocatable, public :: diff(:, :)
96 integer, public :: matvec
97 integer, allocatable, public :: converged(:)
98
100 type(preconditioner_t), public :: pre
101
103 type(subspace_t) :: sdiag
104
105 integer :: rmmdiis_minimization_iter
106
107 logical, public :: folded_spectrum
108
109 ! cg options
110 logical, public :: orthogonalize_to_all
111 integer, public :: conjugate_direction
112 logical, public :: additional_terms
113 real(real64), public :: energy_change_threshold
115 ! Chebyshev filtering options
116 type(eigen_chebyshev_t), public :: cheby_params
117
118 type(exponential_t) :: exponential_operator
119 contains
120 procedure :: run => eigensolver_run
121 end type eigensolver_t
122
123
124 integer, public, parameter :: &
125 RS_PLAN = 11, &
126 rs_cg = 5, &
127 rs_evo = 9, &
128 rs_rmmdiis = 10, &
129 rs_chebyshev = 12
130
131contains
132
133 ! ---------------------------------------------------------
134 subroutine eigensolver_init(eigens, namespace, gr, st, hm, mc, space, deactivate_oracle)
135 type(eigensolver_t), intent(out) :: eigens
136 type(namespace_t), intent(in) :: namespace
137 type(grid_t), intent(in) :: gr
138 type(states_elec_t), intent(in) :: st
139 type(hamiltonian_elec_t), intent(in) :: hm
140 type(multicomm_t), intent(in) :: mc
141 class(space_t), intent(in) :: space
142 logical, optional, intent(in) :: deactivate_oracle
143
144 integer :: default_iter, default_es
145 real(real64) :: default_tol
146 real(real64) :: mem
147
148 push_sub(eigensolver_init)
149
150 !%Variable Eigensolver
151 !%Type integer
152 !%Section SCF::Eigensolver
153 !%Description
154 !% Which eigensolver to use to obtain the lowest eigenvalues and
155 !% eigenfunctions of the Kohn-Sham Hamiltonian. The default is
156 !% conjugate gradients (<tt>cg</tt>), except that when parallelization in states is
157 !% enabled, the default is <tt>chebyshev_filter</tt>.
158 !%Option cg 5
159 !% Conjugate-gradients algorithm.
160 !%Option plan 11
161 !% Preconditioned Lanczos scheme. Ref: Y. Saad, A. Stathopoulos, J. Chelikowsky, K. Wu and S. Ogut,
162 !% "Solution of Large Eigenvalue Problems in Electronic Structure Calculations", <i>BIT</i> <b>36</b>, 1 (1996).
163 !%Option evolution 9
164 !% (Experimental) Propagation in imaginary time.
165 !% This eigensolver uses a time propagation in imaginary time (see, e.g., Aichinger, M. & Krotscheck, E.,
166 !% Computational Materials Science 34, 188–212 (2005), 10.1016/j.commatsci.2004.11.002).
167 !% The timestep is set using <tt>EigensolverImaginaryTime</tt>. The convergence typically depends
168 !% on the total imaginary time in a propagation which means that it should be faster with larger
169 !% timesteps. However, simulations typically diverge above a certain timestep that depends on the system.
170 !% In general, it is advisable to use an exponential method that always converges, especially for large
171 !% timesteps, i.e., set <tt>TDExponentialMethod</tt> to <tt>lanczos</tt> or <tt>chebyshev</tt>.
172 !% The propagation method can be set with <tt>ImaginaryTimePropagator</tt> and variable timestepping
173 !% can be enabled with <tt>ImaginaryTimeVariableTimestep</tt>.
174 !% Moreover, this method usually converges quite slowly, so you might need to increase <tt>MaximumIter</tt>.
175 !% It is incompatible with smearing for the occupations.
176 !%Option rmmdiis 10
177 !% Residual minimization scheme, direct inversion in the
178 !% iterative subspace eigensolver, based on the implementation of
179 !% Kresse and Furthm&uuml;ller [<i>Phys. Rev. B</i> <b>54</b>, 11169
180 !% (1996)]. This eigensolver requires almost no orthogonalization
181 !% so it can be considerably faster than the other options for
182 !% large systems. To improve its performance a large number of <tt>ExtraStates</tt>
183 !% are required (around 10-20% of the number of occupied states).
184 !% Note: with <tt>unocc</tt>, you will need to stop the calculation
185 !% by hand, since the highest states will probably never converge.
186 !% Usage with more than one block of states per node is experimental, unfortunately.
187 !%Option chebyshev_filter 12
188 !% Chebyshev polynomials are used to construct a spectral filter that is iteratively applied to a trial subspace,
189 !% amplifying a subset of the lowest eigenvalues of the Hamiltonian, which effectively isolates the invariant
190 !% subspace associated with the these states. The filtered subspace is projected to define a reduced eigenvalue problem,
191 !% which is then solved using dense diagonalisation. Finally, the eigenstates of the original Hamiltonian are recovered
192 !% via subspace rotation. For further details, see [Zhou et. al.](http://dx.doi.org/10.1016/j.jcp.2014.06.056)
193 !%End
194
195 if(st%parallel_in_states) then
196 default_es = rs_chebyshev
197 else
198 default_es = rs_cg
199 end if
201 call parse_variable(namespace, 'Eigensolver', default_es, eigens%es_type)
202
203 if(st%parallel_in_states .and. .not. eigensolver_parallel_in_states(eigens)) then
204 message(1) = "The selected eigensolver is not parallel in states."
205 message(2) = "Please use the rmmdiis or Chebyshev filtering eigensolvers."
206 call messages_fatal(2, namespace=namespace)
207 end if
208
209 call messages_obsolete_variable(namespace, 'EigensolverVerbose')
210 call messages_obsolete_variable(namespace, 'EigensolverSubspaceDiag', 'SubspaceDiagonalization')
212 default_iter = 25
214 select case(eigens%es_type)
215 case(rs_cg)
216 !%Variable CGOrthogonalizeAll
217 !%Type logical
218 !%Default no
219 !%Section SCF::Eigensolver
220 !%Description
221 !% Used by the cg solver only.
222 !% During the cg iterations, the current band can be orthogonalized
223 !% against all other bands or only against the lower bands. Orthogonalizing
224 !% against all other bands can improve convergence properties, whereas
225 !% orthogonalizing against lower bands needs less operations.
226 !% Moreover, orthogonalizing against all bands can make converging
227 !% the highest band or unoccupied bands more difficult.
228 !%End
229 call parse_variable(namespace, 'CGOrthogonalizeAll', .false., eigens%orthogonalize_to_all)
230
231 !%Variable CGDirection
232 !%Type integer
233 !%Section SCF::Eigensolver
234 !%Description
235 !% Used by the cg solver only.
236 !% The conjugate direction is updated using a certain coefficient to the previous
237 !% direction. This coeffiction can be computed in different ways. The default is
238 !% to use Fletcher-Reeves (FR), an alternative is Polak-Ribiere (PR).
239 !%Option fletcher 1
240 !% The coefficient for Fletcher-Reeves consists of the current norm of the
241 !% steepest descent vector divided by that of the previous iteration.
242 !%Option polak 2
243 !% For the Polak-Ribiere scheme, a product of the current with the previous
244 !% steepest descent vector is subtracted in the nominator.
245 !%End
246 call parse_variable(namespace, 'CGDirection', option__cgdirection__fletcher, eigens%conjugate_direction)
247
248 !%Variable CGAdditionalTerms
249 !%Type logical
250 !%Section SCF::Eigensolver
251 !%Default no
252 !%Description
253 !% Used by the cg solver only.
254 !% Add additional terms during the line minimization, see PTA92, eq. 5.31ff.
255 !% These terms can improve convergence for some systems, but they are quite costly.
256 !% If you experience convergence problems, you might try out this option.
257 !% This feature is still experimental.
258 !%End
259 call parse_variable(namespace, 'CGAdditionalTerms', .false., eigens%additional_terms)
260 if(eigens%additional_terms) then
261 call messages_experimental("The additional terms for the CG eigensolver are not tested for all cases.")
262 end if
263
264 !%Variable CGEnergyChangeThreshold
265 !%Type float
266 !%Section SCF::Eigensolver
267 !%Default 0.1
268 !%Description
269 !% Used by the cg solver only.
270 !% For each band, the CG iterations are stopped when the change in energy is smaller than the
271 !% change in the first iteration multiplied by this factor. This limits the number of CG
272 !% iterations for each band, while still showing good convergence for the SCF cycle. The criterion
273 !% is discussed in Sec. V.B.6 of Payne et al. (1992), Rev. Mod. Phys. 64, 4.
274 !% The default value is 0.1, which is usually a good choice for LDA and GGA potentials. If you
275 !% are solving the OEP equation, you might want to set this value to 1e-3 or smaller. In general,
276 !% smaller values might help if you experience convergence problems.
277 !% For very small convergence tolerances, choose 0 to disable this criterion.
278 !%End
279 call parse_variable(namespace, 'CGEnergyChangeThreshold', 0.1_real64, eigens%energy_change_threshold)
280
281 case(rs_plan)
282 case(rs_evo)
283 call messages_experimental("imaginary-time evolution eigensolver")
284
285 !%Variable EigensolverImaginaryTime
286 !%Type float
287 !%Default 0.1
288 !%Section SCF::Eigensolver
289 !%Description
290 !% The imaginary-time step that is used in the imaginary-time evolution
291 !% method (<tt>Eigensolver = evolution</tt>) to obtain the lowest eigenvalues/eigenvectors.
292 !% It must satisfy <tt>EigensolverImaginaryTime > 0</tt>.
293 !% Increasing this value can make the propagation faster, but could lead to unstable propagations.
294 !%End
295 call parse_variable(namespace, 'EigensolverImaginaryTime', 0.1_real64, eigens%tau)
296 if(eigens%tau <= m_zero) call messages_input_error(namespace, 'EigensolverImaginaryTime')
297 ! save initial timestep
298 eigens%tau0 = eigens%tau
299
300 call exponential_init(eigens%exponential_operator, namespace)
301
302 if(st%smear%method /= smear_semiconductor .and. st%smear%method /= smear_fixed_occ) then
303 message(1) = "Smearing of occupations is incompatible with imaginary time evolution."
304 call messages_fatal(1, namespace=namespace)
305 end if
306
307 !%Variable ImaginaryTimePropagator
308 !%Type integer
309 !%Section SCF::Eigensolver
310 !%Default it_forward_euler
311 !%Description
312 !% The propagation method for imaginary-time evolution.
313 !%Option it_forward_euler 1
314 !% Approximate the evolution operator by one forward Euler step with the exponential:
315 !% <math>
316 !% U_{\rm FE}(t+\delta t, t) = \exp \left( -\tau H_{t}\right)\,.
317 !% </math>
318 !% This scheme is first order.
319 !%Option it_expmid 2
320 !% Similar to forward Euler, but evaluate the Hamiltonian at the half-timestep by
321 !% extrapolation:
322 !% <math>
323 !% U_{\rm EM}(t+\delta t, t) = \exp \left( -\tau H_{t+\delta t/2}\right)\,.
324 !% </math>
325 !% This scheme is second order.
326 !%End
327 call parse_variable(namespace, 'ImaginaryTimePropagator', it_forward_euler, eigens%it_propagator)
328 ! initialize potential interpolation
329 if (eigens%it_propagator == it_expmid) then
330 call hm%ks_pot%init_interpolation(eigens%vks_old)
331 call hm%ks_pot%run_zero_iter(eigens%vks_old)
332 end if
333
334 !%Variable ImaginaryTimeVariableTimestep
335 !%Type logical
336 !%Default no
337 !%Section SCF::Eigensolver
338 !%Description
339 !% Enable variable timesteps for the imaginary time propagation.
340 !%End
341 call parse_variable(namespace, 'ImaginaryTimeVariableTimestep', .false., eigens%variable_timestep)
342
343 eigens%time = m_zero
344
345 safe_allocate(eigens%normalization_energies(1:st%nst, 1:st%nik))
346 safe_allocate(eigens%normalization_energies_prev(1:st%nst, 1:st%nik))
347
348 case(rs_rmmdiis)
349 default_iter = 5
350
351 !%Variable EigensolverMinimizationIter
352 !%Type integer
353 !%Default 0
354 !%Section SCF::Eigensolver
355 !%Description
356 !% During the first iterations, the RMMDIIS eigensolver requires
357 !% some steepest-descent minimizations to improve
358 !% convergence. This variable determines the number of those
359 !% minimizations.
360 !%End
361
362 call parse_variable(namespace, 'EigensolverMinimizationIter', 0, eigens%rmmdiis_minimization_iter)
363
364 if(gr%use_curvilinear) call messages_experimental("RMMDIIS eigensolver for curvilinear coordinates")
365
366 case(rs_chebyshev)
367 !%Variable ChebyshevFilterLanczosOrder
368 !%Type integer
369 !%Default 5
370 !%Section SCF::Eigensolver
371 !%Description
372 !% Used by the Chebyshev filter only.
373 !% The number of Lanczos iterations used to construct the tridiagonal matrix,
374 !% from which the upper bound of H is estimated.
375 !% A value in the range 4 <= ChebyshevFilterLanczosOrder <= 10 is reasonable.
376 !% Values greater than 10 will raise an assertion.
377 !%End
378 call parse_variable(namespace, 'ChebyshevFilterLanczosOrder', default_chebyshev_params%n_lanczos, &
379 eigens%cheby_params%n_lanczos)
380
381 ! TODO Rewrite this, having changed the behaviour
382 !%Variable ChebyshevFilterDegree
383 !%Type integer
384 !%Default 25
385 !%Section SCF::Eigensolver
386 !%Description
387 !% Used by the Chebyshev filter only.
388 !% The degree of the Chebyshev polynomial used to dampen the interval of eigenstates one is not interested in.
389 !% If used in conjunction with "OptimizeChebyshevFilterDegree", which is the default, "ChebyshevFilterDegree" defines the
390 !% the maximum Chebyshev polynomial degree Octopus will consider when determining an approximate, optimal degree.
391 !%
392 !% If not used in conjunction with "OptimizeChebyshevFilterDegree", this defines the polynomial degree used for all SCF steps.
393 !% The larger the degree, the larger the separation between the subspaces, which will reduce the number of SCF iterations
394 !% required to reach convergence. However, ChebyshevFilterDegree also directly correlates with the number of matrix-vector
395 !% products performed on the Hamiltonian per SCF step, and so larger values result in slower SCF cycles.
396 !% A value in the range 8 <= ChebyshevFilterDegree <= 20 is reasonable.
397 !%End
398 call parse_variable(namespace, 'ChebyshevFilterDegree', default_chebyshev_params%degree, eigens%cheby_params%degree)
399
400 !%Variable OptimizeChebyshevFilterDegree
401 !%Type logical
402 !%Default yes
403 !%Section SCF::Eigensolver
404 !%Description
405 !% Used by the Chebyshev filter only.
406 !% Octopus generates a best-estimate for the degree of the Chebyshev polynomial used to filter the subspace.
407 !% A separate estimate is generated for each state block, per SCF iteration. Note that if running parallelism
408 !% over states, the block/batch containing the largest eigenstates will converge more slowly and will
409 !% therefore use a larger degree relative to all other batches. One should therefore avoid setting "ChebyshevFilterDegree"
410 !% to an excessive value (for example > 50). For more details regarding how the degree is estimated, one can
411 !% refer to Section 5.4 in "Computer Physics Communications 187 (2015) 98–105"
412 !% (http://dx.doi.org/10.1016/j.cpc.2014.10.015).
413 !%
414 !% This is deactivated by default for spinors as this is not found to be advantageous in test systems.
415 !%End
416 if (st%d%ispin == spinors .or. optional_default(deactivate_oracle, .false.)) then
417 default_chebyshev_params%optimize_degree = .false.
418 end if
419 call parse_variable(namespace, 'OptimizeChebyshevFilterDegree', default_chebyshev_params%optimize_degree, &
420 eigens%cheby_params%optimize_degree)
421
422 !%Variable ChebyshevFilterBoundMixing
423 !%Type float
424 !%Default 0.5
425 !%Section SCF::Eigensolver
426 !%Description
427 !% In the first application of the filter, for the first SCF step, the initial lower bound estimate
428 !% is defined as a linear combination of the smallest and largest eigenvalues of the Hamiltonian.
429 !% The bound mixing determines the proportion of linear mixing, beta:
430 !% $b_{lower} = beta min{\lambda} + (\beta - 1) max{\lambda}$
431 !% of the smallest and largest eigenvalues.
432 !%End
433 call parse_variable(namespace, 'ChebyshevFilterBoundMixing', default_chebyshev_params%bound_mixing, &
434 eigens%cheby_params%bound_mixing)
435
436 !%Variable ChebyshevFilterNIter
437 !%Type integer
438 !%Default 5
439 !%Section SCF::Eigensolver
440 !%Description
441 !% The max number of iterations in the first SCF step of the Chebyshev solver. In practice this
442 !% does not need to exceed 10, as the eigenstates will vary alot between the first and second
443 !% SCF steps.
444 !%End
445 call parse_variable(namespace, 'ChebyshevFilterNIter', default_chebyshev_params%n_iter, &
446 eigens%cheby_params%n_iter)
447
448 case default
449 call messages_input_error(namespace, 'Eigensolver')
450 end select
451
452 call messages_print_with_emphasis(msg='Eigensolver', namespace=namespace)
453
454 call messages_print_var_option("Eigensolver", eigens%es_type, namespace=namespace)
455
456 call messages_obsolete_variable(namespace, 'EigensolverInitTolerance', 'EigensolverTolerance')
457 call messages_obsolete_variable(namespace, 'EigensolverFinalTolerance', 'EigensolverTolerance')
458 call messages_obsolete_variable(namespace, 'EigensolverFinalToleranceIteration')
459
460 ! this is an internal option that makes the solver use the
461 ! folded operator (H-shift)^2 to converge first eigenvalues around
462 ! the values of shift
463 ! c.f. L. W. Wang and A. Zunger
464 ! JCP 100, 2394 (1994); doi: http://dx.doi.org/10.1063/1.466486
465 eigens%folded_spectrum = .false.
466
467 !%Variable EigensolverTolerance
468 !%Type float
469 !%Section SCF::Eigensolver
470 !%Description
471 !% This is the tolerance for the eigenvectors. The default is 1e-7.
472 !% However, if <tt>ConvRelDens</tt> is defined, the default is set to a tenth of its value.
473 !%End
474 default_tol = 1e-7_real64
475 if (parse_is_defined(namespace, 'ConvRelDens')) then
476 call parse_variable(namespace, 'ConvRelDens', 1e-6_real64, default_tol)
477 default_tol = default_tol / 10.0_real64
478 end if
479 call parse_variable(namespace, 'EigensolverTolerance', default_tol, eigens%tolerance)
480
481 !%Variable EigensolverMaxIter
482 !%Type integer
483 !%Section SCF::Eigensolver
484 !%Description
485 !% Determines the maximum number of iterations that the
486 !% eigensolver will perform if the desired tolerance is not
487 !% achieved. The default is 25 iterations for all eigensolvers
488 !% except for <tt>rmdiis</tt>, which performs only 5 iterations.
489 !% Increasing this value for <tt>rmdiis</tt> increases the convergence speed,
490 !% at the cost of an increased memory footprint.
491 !%End
492 call parse_variable(namespace, 'EigensolverMaxIter', default_iter, eigens%es_maxiter)
493 if(eigens%es_maxiter < 1) call messages_input_error(namespace, 'EigensolverMaxIter')
494
495 if(eigens%es_maxiter > default_iter) then
496 call messages_write('You have specified a large number of eigensolver iterations (')
497 call messages_write(eigens%es_maxiter)
498 call messages_write(').', new_line = .true.)
499 call messages_write('This is not a good idea as it might slow down convergence, even for', new_line = .true.)
500 call messages_write('independent particles, as subspace diagonalization will not be used', new_line = .true.)
501 call messages_write('often enough.')
502 call messages_warning(namespace=namespace)
503 end if
504
505 if (any(eigens%es_type == (/rs_plan, rs_cg, rs_rmmdiis/))) then
506 call preconditioner_init(eigens%pre, namespace, gr, mc, space)
507 end if
508
509 safe_allocate(eigens%diff(1:st%nst, 1:st%nik))
510 eigens%diff(1:st%nst, 1:st%nik) = 0
511
512 safe_allocate(eigens%converged(1:st%nik))
513 eigens%converged(1:st%nik) = 0
514 eigens%matvec = 0
515
516 call eigens%sdiag%init(namespace, st)
517
518 ! print memory requirements
519 select case(eigens%es_type)
520 case(rs_rmmdiis)
521 call messages_write('Info: The rmmdiis eigensolver requires ')
522 mem = (m_two*eigens%es_maxiter - m_one)*st%block_size*real(gr%np_part, real64)
523 if(states_are_real(st)) then
524 mem = mem*8.0_real64
525 else
526 mem = mem*16.0_real64
527 end if
528 call messages_write(mem, units = unit_megabytes, fmt = '(f9.1)')
529 call messages_write(' of additional')
530 call messages_new_line()
531 call messages_write(' memory. This amount can be reduced by decreasing the value')
532 call messages_new_line()
533 call messages_write(' of the variable StatesBlockSize (currently set to ')
534 call messages_write(st%block_size)
535 call messages_write(').')
536 call messages_info()
537 end select
538
539 call messages_print_with_emphasis(namespace=namespace)
540
541 pop_sub(eigensolver_init)
542 end subroutine eigensolver_init
543
544
545 ! ---------------------------------------------------------
546 subroutine eigensolver_end(eigens)
547 type(eigensolver_t), intent(inout) :: eigens
548
549 push_sub(eigensolver_end)
550
551 select case(eigens%es_type)
552 case(rs_plan, rs_cg, rs_rmmdiis)
553 call preconditioner_end(eigens%pre)
554 end select
555
556 safe_deallocate_a(eigens%converged)
557 safe_deallocate_a(eigens%diff)
558
559 safe_deallocate_a(eigens%normalization_energies)
560 safe_deallocate_a(eigens%normalization_energies_prev)
561
562 pop_sub(eigensolver_end)
563 end subroutine eigensolver_end
564
565
566 ! ---------------------------------------------------------
567 subroutine eigensolver_run(eigens, namespace, gr, st, hm, space, ext_partners, iter, conv, nstconv)
568 class(eigensolver_t), intent(inout) :: eigens
569 type(namespace_t), intent(in) :: namespace
570 type(grid_t), intent(in) :: gr
571 type(states_elec_t), intent(inout) :: st
572 type(hamiltonian_elec_t), intent(inout) :: hm
573 class(space_t), intent(in) :: space
574 type(partner_list_t), intent(in) :: ext_partners
575 integer, intent(in) :: iter
576 logical, optional, intent(out) :: conv
577 integer, optional, intent(in) :: nstconv
578 ! !< the convergence criteria
579
580 integer :: nstconv_
581#ifdef HAVE_MPI
582 logical :: conv_reduced
583 integer :: ist, outcount, lmatvec
584 real(real64), allocatable :: ldiff(:), leigenval(:)
585 real(real64), allocatable :: ldiff_out(:), leigenval_out(:)
586 integer, allocatable :: lconv(:)
587#endif
588
589 call profiling_in("EIGEN_SOLVER")
590 push_sub(eigensolver_run)
591
592 if(present(conv)) conv = .false.
593 if(present(nstconv)) then
594 nstconv_ = nstconv
595 else
596 nstconv_ = st%nst
597 end if
598
599 eigens%matvec = 0
600
601 if(mpi_grp_is_root(mpi_world) .and. eigensolver_has_progress_bar(eigens) .and. .not. debug%info) then
602 call loct_progress_bar(-1, st%lnst*st%d%kpt%nlocal)
603 end if
604
605 if (states_are_real(st)) then
606 call deigensolver_run(eigens, namespace, gr, st, hm, space, ext_partners, iter)
607 else
608 call zeigensolver_run(eigens, namespace, gr, st, hm, space, ext_partners, iter)
609 end if
610
611 if(mpi_grp_is_root(mpi_world) .and. eigensolver_has_progress_bar(eigens) .and. .not. debug%info) then
612 write(stdout, '(1x)')
613 end if
614
615 if(present(conv)) conv = all(eigens%converged(st%d%kpt%start:st%d%kpt%end) >= nstconv_)
616
617#ifdef HAVE_MPI
618 if (st%d%kpt%parallel) then
619 if (present(conv)) then
620 call st%d%kpt%mpi_grp%allreduce(conv, conv_reduced, 1, mpi_logical, mpi_land)
621 conv = conv_reduced
622 end if
623
624 lmatvec = eigens%matvec
625 call st%d%kpt%mpi_grp%allreduce(lmatvec, eigens%matvec, 1, mpi_integer, mpi_sum)
626
627 safe_allocate(lconv(1:st%d%kpt%nlocal))
628 lconv(1:st%d%kpt%nlocal) = eigens%converged(st%d%kpt%start:st%d%kpt%end)
629 call lmpi_gen_allgatherv(st%d%kpt%nlocal, lconv, outcount, eigens%converged, st%d%kpt%mpi_grp)
630 assert(outcount == st%nik)
631 safe_deallocate_a(lconv)
632
633 ! every node needs to know all eigenvalues (and diff)
634 safe_allocate(ldiff(1:st%d%kpt%nlocal))
635 safe_allocate(leigenval(1:st%d%kpt%nlocal))
636 safe_allocate(ldiff_out(1:st%nik))
637 safe_allocate(leigenval_out(1:st%nik))
638 do ist = st%st_start, st%st_end
639 ldiff(1:st%d%kpt%nlocal) = eigens%diff(ist, st%d%kpt%start:st%d%kpt%end)
640 leigenval(1:st%d%kpt%nlocal) = st%eigenval(ist, st%d%kpt%start:st%d%kpt%end)
641 call lmpi_gen_allgatherv(st%d%kpt%nlocal, ldiff, outcount, ldiff_out, st%d%kpt%mpi_grp)
642 eigens%diff(ist, :) = ldiff_out
643 assert(outcount == st%nik)
644 call lmpi_gen_allgatherv(st%d%kpt%nlocal, leigenval, outcount, leigenval_out, st%d%kpt%mpi_grp)
645 st%eigenval(ist, :) = leigenval_out
646 assert(outcount == st%nik)
647 end do
648 safe_deallocate_a(ldiff)
649 safe_deallocate_a(ldiff_out)
650 safe_deallocate_a(leigenval)
651 safe_deallocate_a(leigenval_out)
652 end if
653#endif
654
655 pop_sub(eigensolver_run)
656 call profiling_out("EIGEN_SOLVER")
657 end subroutine eigensolver_run
658
659
660 ! ---------------------------------------------------------
661 logical function eigensolver_parallel_in_states(this) result(par_stat)
662 type(eigensolver_t), intent(in) :: this
663
665
666 par_stat = .false.
667
668 select case(this%es_type)
670 par_stat = .true.
671 end select
672
675
676
677 ! ---------------------------------------------------------
678 logical function eigensolver_has_progress_bar(this) result(has)
679 type(eigensolver_t), intent(in) :: this
680
682
683 has = .false.
684
685 select case(this%es_type)
686 case(rs_rmmdiis, rs_cg)
687 has = .true.
688 end select
689
692
693
694#include "undef.F90"
695#include "real.F90"
696#include "eigensolver_inc.F90"
697#include "eigen_plan_inc.F90"
698
699#include "undef.F90"
700#include "complex.F90"
701#include "eigensolver_inc.F90"
702#include "eigen_plan_inc.F90"
703
704end module eigensolver_oct_m
705
706
707!! Local Variables:
708!! mode: f90
709!! coding: utf-8
710!! End:
This module implements batches of mesh functions.
Definition: batch.F90:133
This module implements common operations on batches of mesh functions.
Definition: batch_ops.F90:116
type(debug_t), save, public debug
Definition: debug.F90:156
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
type(eigen_chebyshev_t), public default_chebyshev_params
Default Chebyshev input parameters Arguments 1 and 2 taken from 10.1016/j.jcp.2006....
integer, parameter, public it_expmid
integer, parameter, public it_forward_euler
subroutine zeigensolver_run(eigens, namespace, mesh, st, hm, space, ext_partners, iter)
integer, parameter, public rs_evo
subroutine, public eigensolver_init(eigens, namespace, gr, st, hm, mc, space, deactivate_oracle)
integer, parameter, public rs_cg
subroutine deigensolver_run(eigens, namespace, mesh, st, hm, space, ext_partners, iter)
subroutine eigensolver_run(eigens, namespace, gr, st, hm, space, ext_partners, iter, conv, nstconv)
logical function eigensolver_parallel_in_states(this)
integer, parameter, public rs_chebyshev
logical function eigensolver_has_progress_bar(this)
subroutine, public eigensolver_end(eigens)
integer, parameter, public rs_rmmdiis
integer, parameter, public spinors
subroutine, public exponential_init(te, namespace, full_batch)
real(real64), parameter, public m_two
Definition: global.F90:190
real(real64), parameter, public m_zero
Definition: global.F90:188
real(real64), parameter, public m_one
Definition: global.F90:189
This module implements the underlying real-space grid.
Definition: grid.F90:117
This module defines classes and functions for interaction partners.
A module to handle KS potential, without the external potential.
This module defines functions over batches of mesh functions.
Definition: mesh_batch.F90:116
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_print_with_emphasis(msg, iunit, namespace)
Definition: messages.F90:920
character(len=512), private msg
Definition: messages.F90:165
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
subroutine, public messages_new_line()
Definition: messages.F90:1134
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
Definition: messages.F90:414
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
This module contains some common usage patterns of MPI routines.
Definition: mpi_lib.F90:115
logical function mpi_grp_is_root(grp)
Is the current MPI process of grpcomm, root.
Definition: mpi.F90:434
type(mpi_grp_t), public mpi_world
Definition: mpi.F90:270
This module handles the communicators for the various parallelization strategies.
Definition: multicomm.F90:145
logical function, public parse_is_defined(namespace, name)
Definition: parser.F90:502
subroutine, public preconditioner_end(this)
subroutine, public preconditioner_init(this, namespace, gr, mc, space)
subroutine, public profiling_out(label)
Increment out counter and sum up difference between entry and exit time.
Definition: profiling.F90:623
subroutine, public profiling_in(label, exclude)
Increment in counter and save entry time.
Definition: profiling.F90:552
integer, parameter, public smear_semiconductor
Definition: smear.F90:171
integer, parameter, public smear_fixed_occ
Definition: smear.F90:171
pure logical function, public states_are_real(st)
This module handles spin dimensions of the states and the k-point distribution.
This module provides routines for communicating states when using states parallelization.
brief This module defines the class unit_t which is used by the unit_systems_oct_m module.
Definition: unit.F90:132
This module defines the unit system, used for input and output.
type(unit_t), public unit_megabytes
For large amounts of data (natural code units are bytes)
Definition: xc.F90:114
Description of the grid, containing information on derivatives, stencil, and symmetries.
Definition: grid.F90:169
The states_elec_t class contains all electronic wave functions.
int true(void)