26 use,
intrinsic :: iso_fortran_env
52 type(poisson_corr_t) :: corrector
53 type(multigrid_t) :: mgrid
54 type(mg_solver_t) :: mg_solver
62 type(poisson_mg_solver_t),
intent(out) :: this
63 type(namespace_t),
intent(in) :: namespace
64 class(space_t),
intent(in) :: space
65 type(mesh_t),
intent(inout) :: mesh
66 type(derivatives_t),
intent(in) :: der
67 type(stencil_t),
intent(in) :: stencil
68 type(multicomm_t),
intent(in) :: mc
69 integer,
intent(in) :: ml
70 real(real64),
intent(in) :: thr
78 call multigrid_init(this%mgrid, namespace, space, mesh, der, stencil, mc)
82 do i = 1, this%mgrid%n_levels
83 this%mgrid%level(i - 1)%der%lapl%coarser => this%mgrid%level(i)%der%lapl
94 type(poisson_mg_solver_t),
intent(inout) :: this
108 type(poisson_mg_solver_t),
intent(in) :: this
109 type(namespace_t),
intent(in) :: namespace
110 type(derivatives_t),
intent(in) :: der
111 real(real64),
intent(inout) :: pot(:)
112 real(real64),
contiguous,
intent(in) :: rho(:)
115 real(real64) :: resnorm
116 real(real64),
allocatable :: vh_correction(:), res(:), cor(:), err(:)
121 safe_allocate(vh_correction(1:der%mesh%np_part))
122 safe_allocate(res(1:der%mesh%np))
123 safe_allocate(cor(1:der%mesh%np_part))
124 safe_allocate(err(1:der%mesh%np))
126 call correct_rho(this%corrector, der, rho, res, vh_correction)
129 do ip = 1, der%mesh%np
130 cor(ip) = pot(ip) - vh_correction(ip)
133 do iter = 1, this%mg_solver%maxcycles
135 call multigrid_solver_cycle(this%mg_solver, this%mgrid%level(0)%der, this%mgrid%level(0)%der%lapl, cor, res)
137 do ip = 1, der%mesh%np
138 err(ip) = res(ip) - err(ip)
142 if (resnorm < this%mg_solver%threshold)
exit
145 write(
message(1),
'(a,i5,a,e13.6)')
"Multigrid: base level: iter ", iter,
" res ", resnorm
151 if (resnorm >= this%mg_solver%threshold)
then
152 message(1) =
'Multigrid Poisson solver did not converge.'
153 write(
message(2),
'(a,e14.6)')
' Norm of the residue = ', resnorm
157 write(
message(1),
'(a,i4,a)')
"Multigrid Poisson solver converged in ", iter,
" iterations."
158 write(
message(2),
'(a,e14.6)')
' Norm of the residue = ', resnorm
163 do ip = 1, der%mesh%np
164 pot(ip) = cor(ip) + vh_correction(ip)
167 safe_deallocate_a(vh_correction)
168 safe_deallocate_a(res)
169 safe_deallocate_a(cor)
170 safe_deallocate_a(err)
scales a vector by a constant
Module implementing boundary conditions in Octopus.
type(debug_t), save, public debug
This module calculates the derivatives (gradients, Laplacians, etc.) of a function.
subroutine, public dderivatives_lapl(der, ff, op_ff, ghost_update, set_bc, factor)
apply the Laplacian to a mesh function
real(real64), parameter, public m_four
real(real64), parameter, public m_pi
some mathematical constants
This module defines various routines, operating on mesh functions.
This module defines the meshes, which are used in Octopus.
subroutine, public messages_warning(no_lines, all_nodes, namespace)
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
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 modules provides the routines for solving Ax=b using the V-shaped multigrid method.
recursive subroutine, public multigrid_solver_cycle(this, der, op, sol, rhs)
Performs one cycle of a V-shaped multigrid solver.
subroutine, public multigrid_solver_init(this, namespace, space, mesh, thr)
subroutine, public poisson_corrections_end(this)
subroutine, public poisson_corrections_init(this, namespace, space, ml, mesh)
subroutine, public correct_rho(this, der, rho, rho_corrected, vh_correction)
subroutine, public poisson_multigrid_solver(this, namespace, der, pot, rho)
subroutine, public poisson_multigrid_end(this)
subroutine, public poisson_multigrid_init(this, namespace, space, mesh, der, stencil, mc, ml, thr)
This module defines stencils used in Octopus.