31 use,
intrinsic :: iso_fortran_env
50 integer,
public,
parameter :: &
69 integer :: which = pre_none
71 type(nl_operator_t),
allocatable :: op_array(:)
72 type(nl_operator_t),
pointer,
public :: op
74 real(real64),
allocatable :: diag_lapl(:)
75 integer :: npre, npost, nmiddle
77 type(multigrid_t) :: mgrid
79 type(derivatives_t),
pointer :: der => null()
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
92 real(real64) :: alpha, default_alpha, omega
95 integer :: maxp, is, ns, ip, ip2
96 character(len=32) :: name
100 safe_allocate(this%op_array(1))
101 this%op => this%op_array(1)
127 if (gr%use_curvilinear)
then
133 call parse_variable(namespace,
'Preconditioner', default, this%which)
137 select case (this%which)
140 name =
"Preconditioner"
162 if (space%is_periodic()) default_alpha = 0.6_real64
164 call parse_variable(namespace,
'PreconditionerFilterFactor', default_alpha, alpha)
173 ns = this%op%stencil%size
175 if (this%op%const_w)
then
182 this%op%w = -
m_half * this%op%w
184 safe_allocate(this%diag_lapl(1:this%op%np))
189 if (gr%use_curvilinear) vol = sum(gr%vol_pp(ip + this%op%ri(1:ns, this%op%rimap(ip))))
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
205 this%op%w(is, ip) = this%op%w(is, ip) * omega / this%diag_lapl(ip)
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)
214 safe_deallocate_a(this%diag_lapl)
220 safe_allocate(this%diag_lapl(1:gr%np))
233 call parse_variable(namespace,
'PreconditionerIterationsPre', 1, this%npre)
242 call parse_variable(namespace,
'PreconditionerIterationsMiddle', 1, this%nmiddle)
251 call parse_variable(namespace,
'PreconditionerIterationsPost', 2, this%npost)
253 call multigrid_init(this%mgrid, namespace, space, gr, gr%der, gr%stencil, mc, nlevels=3)
265 select case (this%which)
270 safe_deallocate_a(this%diag_lapl)
273 safe_deallocate_a(this%diag_lapl)
279 safe_deallocate_a(this%op_array)
287 character(len=*),
intent(in) :: old_prefix
288 character(len=*),
intent(in) :: new_prefix
294#include "complex.F90"
295#include "preconditioners_inc.F90"
299#include "preconditioners_inc.F90"
scales a vector by a constant
Prints out to iunit a message in the form: ["InputVariable" = value] where "InputVariable" is given b...
This module implements batches of mesh functions.
This module implements common operations on batches of mesh functions.
Module implementing boundary conditions in Octopus.
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
real(real64), parameter, public m_half
real(real64), parameter, public m_one
This module implements the underlying real-space grid.
This module defines the meshes, which are used in Octopus.
subroutine, public messages_obsolete_variable(namespace, name, rep)
subroutine, public messages_input_error(namespace, var, details, row, column)
This module handles the communicators for the various parallelization strategies.
subroutine, public multigrid_end(mgrid)
subroutine, public multigrid_init(mgrid, namespace, space, mesh, der, stencil, mc, nlevels)
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.