Octopus
preconditioners.F90
Go to the documentation of this file.
1!! Copyright (C) 2006 X. Andrade, 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
25 use debug_oct_m
27 use global_oct_m
28 use grid_oct_m
31 use, intrinsic :: iso_fortran_env
33 use mesh_oct_m
39 use parser_oct_m
43 use space_oct_m
46
47 implicit none
48 private
49
50 integer, public, parameter :: &
51 PRE_NONE = 0, &
52 pre_filter = 1, &
53 pre_jacobi = 2, &
54 pre_poisson = 3, &
56
57 public :: &
66
68 private
69 integer :: which = pre_none
70
71 type(nl_operator_t), allocatable :: op_array(:)
72 type(nl_operator_t), pointer, public :: op
73
74 real(real64), allocatable :: diag_lapl(:)
75 integer :: npre, npost, nmiddle
76
77 type(multigrid_t) :: mgrid ! multigrid object
78
79 type(derivatives_t), pointer :: der => null()
80 end type preconditioner_t
81
82contains
83
84 ! ---------------------------------------------------------
85 subroutine preconditioner_init(this, namespace, gr, mc, space)
86 type(preconditioner_t), target, intent(out) :: this
87 type(namespace_t), intent(in) :: namespace
88 type(grid_t), target, intent(in) :: gr
89 type(multicomm_t), intent(in) :: mc
90 class(space_t), intent(in) :: space
91
92 real(real64) :: alpha, default_alpha, omega
93 real(real64) :: vol
94 integer :: default
95 integer :: maxp, is, ns, ip, ip2
96 character(len=32) :: name
97
98 push_sub(preconditioner_init)
99
100 safe_allocate(this%op_array(1))
101 this%op => this%op_array(1)
102
103 this%der => gr%der
104
105 !%Variable Preconditioner
106 !%Type integer
107 !%Section SCF::Eigensolver
108 !%Description
109 !% Which preconditioner to use in order to solve the Kohn-Sham
110 !% equations or the linear-response equations. The default is
111 !% pre_filter, except for curvilinear coordinates, where no
112 !% preconditioner is applied by default.
113 !%Option no 0
114 !% Do not apply preconditioner.
115 !%Option pre_filter 1
116 !% Filter preconditioner.
117 !%Option pre_jacobi 2
118 !% Jacobi preconditioner. Only the local part of the pseudopotential is used.
119 !% Not very helpful.
120 !%Option pre_poisson 3
121 !% Uses the full Laplacian as preconditioner. The inverse is calculated through
122 !% the solution of the Poisson equation. This is, of course, very slow.
123 !%Option pre_multigrid 7
124 !% Multigrid preconditioner.
125 !%End
126
127 if (gr%use_curvilinear) then
128 default = pre_none
129 else
130 default = pre_filter
131 end if
132
133 call parse_variable(namespace, 'Preconditioner', default, this%which)
134 if (.not. varinfo_valid_option('Preconditioner', this%which)) call messages_input_error(namespace, 'Preconditioner')
135 call messages_print_var_option('Preconditioner', this%which, namespace=namespace)
136
137 select case (this%which)
138 case (pre_filter)
139 ! the smoothing is performed uing the same stencil as the Laplacian
140 name = "Preconditioner"
141 call derivatives_get_lapl(gr%der, namespace, this%op_array, space, name, 1)
142
143 !%Variable PreconditionerFilterFactor
144 !%Type float
145 !%Section SCF::Eigensolver
146 !%Description
147 !% This variable controls how much filter preconditioner is
148 !% applied. A value of 1.0 means no preconditioning, 0.5 is the
149 !% standard.
150 !%
151 !% The default is 0.5, except for periodic systems where the
152 !% default is 0.6.
153 !%
154 !% If you observe that the first eigenvectors are not converging
155 !% properly, especially for periodic systems, you should
156 !% increment this value.
157 !%
158 !% The allowed range for this parameter is between 0.5 and 1.0.
159 !% For other values, the SCF may converge to wrong results.
160 !%End
161 default_alpha = m_half
162 if (space%is_periodic()) default_alpha = 0.6_real64
163
164 call parse_variable(namespace, 'PreconditionerFilterFactor', default_alpha, alpha)
166 call messages_print_var_value('PreconditionerFilterFactor', alpha, namespace=namespace)
168 ! check for correct interval of alpha
169 if (alpha < m_half .or. alpha > m_one) then
170 call messages_input_error(namespace, 'PreconditionerFilterFactor')
171 end if
173 ns = this%op%stencil%size
174
175 if (this%op%const_w) then
176 maxp = 1
177 else
178 maxp = gr%np
179 end if
180
181 !We change the weights to be the one of the kinetic energy operator
182 this%op%w = -m_half * this%op%w
183
184 safe_allocate(this%diag_lapl(1:this%op%np))
185 call dnl_operator_operate_diag(this%op, this%diag_lapl)
186
187 do ip = 1, maxp
188
189 if (gr%use_curvilinear) vol = sum(gr%vol_pp(ip + this%op%ri(1:ns, this%op%rimap(ip))))
190
191 !The filter preconditioner is given by two iterations of the Relaxation Jacobi method
192 !This leads to \tilde{\psi} = \omega D^{-1}(2\psi - \omega D^{-1} (-0.5\Laplacian) \psi),
193 ! where \omega = 2(1-\alpha), and D is the diagonal part of (-0.5\Laplacian)
194 !In order to have this to work in all cases, such as different spacings, nonorthogonal cells, ...
195 !We directly apply this formula to renormalize the weights of the Laplacian
196 !and get the correct preconditioner
197
198 omega = m_two * (m_one-alpha)
199
200 do is = 1, ns
201 this%op%w(is, ip) = - omega / this%diag_lapl(ip) * this%op%w(is, ip)
202 if (is == this%op%stencil%center) then
203 this%op%w(is, ip) = this%op%w(is, ip) + m_two
204 end if
205 this%op%w(is, ip) = this%op%w(is, ip) * omega / this%diag_lapl(ip)
206
207 if (gr%use_curvilinear) then
208 ip2 = ip + this%op%ri(is, this%op%rimap(ip))
209 this%op%w(is, ip) = this%op%w(is, ip)*(ns*gr%vol_pp(ip2)/vol)
210 end if
211 end do
212 end do
213
214 safe_deallocate_a(this%diag_lapl)
215
217 call nl_operator_output_weights(this%op)
218
220 safe_allocate(this%diag_lapl(1:gr%np))
221 call derivatives_lapl_diag(gr%der, this%diag_lapl)
222 call lalg_scal(gr%np, -m_half, this%diag_lapl(:))
223 end select
224
225 if (this%which == pre_multigrid) then
226 !%Variable PreconditionerIterationsPre
227 !%Type integer
228 !%Section SCF::Eigensolver
229 !%Description
230 !% This variable is the number of pre-smoothing iterations for the multigrid
231 !% preconditioner. The default is 1.
232 !%End
233 call parse_variable(namespace, 'PreconditionerIterationsPre', 1, this%npre)
234
235 !%Variable PreconditionerIterationsMiddle
236 !%Type integer
237 !%Section SCF::Eigensolver
238 !%Description
239 !% This variable is the number of smoothing iterations on the coarsest grid for the multigrid
240 !% preconditioner. The default is 1.
241 !%End
242 call parse_variable(namespace, 'PreconditionerIterationsMiddle', 1, this%nmiddle)
243
244 !%Variable PreconditionerIterationsPost
245 !%Type integer
246 !%Section SCF::Eigensolver
247 !%Description
248 !% This variable is the number of post-smoothing iterations for the multigrid
249 !% preconditioner. The default is 2.
250 !%End
251 call parse_variable(namespace, 'PreconditionerIterationsPost', 2, this%npost)
252
253 call multigrid_init(this%mgrid, namespace, space, gr, gr%der, gr%stencil, mc, nlevels=3)
254 end if
255
256 pop_sub(preconditioner_init)
257 end subroutine preconditioner_init
258
259 ! ---------------------------------------------------------
260 subroutine preconditioner_end(this)
261 type(preconditioner_t), intent(inout) :: this
262
263 push_sub(preconditioner_end)
264
265 select case (this%which)
266 case (pre_filter)
267 call nl_operator_end(this%op)
268
269 case (pre_jacobi)
270 safe_deallocate_a(this%diag_lapl)
271
272 case (pre_multigrid)
273 safe_deallocate_a(this%diag_lapl)
274 call multigrid_end(this%mgrid)
275
276 end select
277
278 nullify(this%op)
279 safe_deallocate_a(this%op_array)
280
281 pop_sub(preconditioner_end)
282 end subroutine preconditioner_end
283
284 ! ---------------------------------------------------------
285 subroutine preconditioner_obsolete_variables(namespace, old_prefix, new_prefix)
286 type(namespace_t), intent(in) :: namespace
287 character(len=*), intent(in) :: old_prefix
288 character(len=*), intent(in) :: new_prefix
289
290 call messages_obsolete_variable(namespace, trim(old_prefix)//'Preconditioner', trim(new_prefix)//'Preconditioner')
292
293#include "undef.F90"
294#include "complex.F90"
295#include "preconditioners_inc.F90"
296
297#include "undef.F90"
298#include "real.F90"
299#include "preconditioners_inc.F90"
300
301end module preconditioners_oct_m
302
303!! Local Variables:
304!! mode: f90
305!! coding: utf-8
306!! End:
scales a vector by a constant
Definition: lalg_basic.F90:156
Prints out to iunit a message in the form: ["InputVariable" = value] where "InputVariable" is given b...
Definition: messages.F90:180
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
Module implementing boundary conditions in Octopus.
Definition: boundaries.F90:122
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
subroutine, public derivatives_lapl_diag(der, lapl)
Returns the diagonal elements of the Laplacian, needed for preconditioning.
subroutine, public derivatives_get_lapl(this, namespace, op, space, name, order)
real(real64), parameter, public m_two
Definition: global.F90:189
real(real64), parameter, public m_half
Definition: global.F90:193
real(real64), parameter, public m_one
Definition: global.F90:188
This module implements the underlying real-space grid.
Definition: grid.F90:117
This module defines the meshes, which are used in Octopus.
Definition: mesh.F90:118
subroutine, public messages_obsolete_variable(namespace, name, rep)
Definition: messages.F90:1057
subroutine, public messages_input_error(namespace, var, details, row, column)
Definition: messages.F90:723
This module handles the communicators for the various parallelization strategies.
Definition: multicomm.F90:145
subroutine, public multigrid_end(mgrid)
Definition: multigrid.F90:502
subroutine, public multigrid_init(mgrid, namespace, space, mesh, der, stencil, mc, nlevels)
Definition: multigrid.F90:185
This module defines non-local operators.
subroutine, public dnl_operator_operate_diag(op, fo)
subroutine, public nl_operator_update_gpu_buffers(op)
subroutine, public nl_operator_output_weights(this)
subroutine, public nl_operator_end(op)
integer, parameter, public pre_poisson
integer, parameter, public pre_multigrid
subroutine, public preconditioner_end(this)
subroutine, public zpreconditioner_apply_batch(pre, namespace, mesh, hm, aa, bb, ik, omega)
subroutine, public zpreconditioner_apply(pre, namespace, mesh, hm, a, b, ik, omega)
subroutine, public dpreconditioner_apply_batch(pre, namespace, mesh, hm, aa, bb, ik, omega)
integer, parameter, public pre_jacobi
subroutine, public dpreconditioner_apply(pre, namespace, mesh, hm, a, b, ik, omega)
subroutine, public preconditioner_obsolete_variables(namespace, old_prefix, new_prefix)
subroutine, public preconditioner_init(this, namespace, gr, mc, space)
integer, parameter, public pre_filter
This module defines routines, generating operators for a star stencil.