Octopus
poisson_multigrid.F90
Go to the documentation of this file.
1!! Copyright (C) 2005-2006 M. Marques, A. Castro, A. Rubio, G. Bertsch, X. Andrade
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
23 use debug_oct_m
25 use global_oct_m
26 use, intrinsic :: iso_fortran_env
28 use mesh_oct_m
37 use space_oct_m
39
40 implicit none
41
42 private
43 public :: &
48
50 private
51
52 type(poisson_corr_t) :: corrector
53 type(multigrid_t) :: mgrid ! multigrid object
54 type(mg_solver_t) :: mg_solver
55
56 end type poisson_mg_solver_t
57
58contains
59
60 ! ---------------------------------------------------------
61 subroutine poisson_multigrid_init(this, namespace, space, mesh, der, stencil, mc, ml, thr)
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
71
72 integer :: i
73
75
76 call poisson_corrections_init(this%corrector, namespace, space, ml, mesh)
77
78 call multigrid_init(this%mgrid, namespace, space, mesh, der, stencil, mc)
79
80 ! For the multigrid solver to work, we need to set a pointer from one operator
81 ! to the corresponding one on the coarser grid.
82 do i = 1, this%mgrid%n_levels
83 this%mgrid%level(i - 1)%der%lapl%coarser => this%mgrid%level(i)%der%lapl
84 end do
85
86 call multigrid_solver_init(this%mg_solver, namespace, space, mesh, thr)
87
89 end subroutine poisson_multigrid_init
90
91
92 ! ---------------------------------------------------------
93 subroutine poisson_multigrid_end(this)
94 type(poisson_mg_solver_t), intent(inout) :: this
95
96 push_sub(poisson_multigrid_end)
97
98 call poisson_corrections_end(this%corrector)
99
100 call multigrid_end(this%mgrid)
101
102 pop_sub(poisson_multigrid_end)
103 end subroutine poisson_multigrid_end
104
105
106 ! ---------------------------------------------------------
107 subroutine poisson_multigrid_solver(this, namespace, der, pot, rho)
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(:)
113
114 integer :: iter, ip
115 real(real64) :: resnorm
116 real(real64), allocatable :: vh_correction(:), res(:), cor(:), err(:)
117
119
120 ! correction for treating boundaries
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))
125
126 call correct_rho(this%corrector, der, rho, res, vh_correction)
127 call lalg_scal(der%mesh%np, -m_four*m_pi, res)
128
129 do ip = 1, der%mesh%np
130 cor(ip) = pot(ip) - vh_correction(ip)
131 end do
132
133 do iter = 1, this%mg_solver%maxcycles
134
135 call multigrid_solver_cycle(this%mg_solver, this%mgrid%level(0)%der, this%mgrid%level(0)%der%lapl, cor, res)
136 call dderivatives_lapl(der, cor, err)
137 do ip = 1, der%mesh%np
138 err(ip) = res(ip) - err(ip)
139 end do
140 resnorm = dmf_nrm2(der%mesh, err)
141
142 if (resnorm < this%mg_solver%threshold) exit
143
144 if (debug%info) then
145 write(message(1), '(a,i5,a,e13.6)') "Multigrid: base level: iter ", iter, " res ", resnorm
146 call messages_info(1, namespace=namespace)
147 end if
148
149 end do
150
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
154 call messages_warning(2, namespace=namespace)
155 else
156 if (debug%info) then
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
159 call messages_info(2, namespace=namespace)
160 end if
161 end if
162
163 do ip = 1, der%mesh%np
164 pot(ip) = cor(ip) + vh_correction(ip)
165 end do
166
167 safe_deallocate_a(vh_correction)
168 safe_deallocate_a(res)
169 safe_deallocate_a(cor)
170 safe_deallocate_a(err)
171
173 end subroutine poisson_multigrid_solver
174
176
177!! Local Variables:
178!! mode: f90
179!! coding: utf-8
180!! End:
scales a vector by a constant
Definition: lalg_basic.F90:156
Module implementing boundary conditions in Octopus.
Definition: boundaries.F90:122
type(debug_t), save, public debug
Definition: debug.F90:151
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
Definition: global.F90:191
real(real64), parameter, public m_pi
some mathematical constants
Definition: global.F90:185
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:543
subroutine, public messages_info(no_lines, iunit, verbose_limit, stress, all_nodes, namespace)
Definition: messages.F90:624
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
Definition: messages.F90:160
This module handles the communicators for the various parallelization strategies.
Definition: multicomm.F90:145
subroutine, public multigrid_end(mgrid)
Definition: multigrid.F90:501
subroutine, public multigrid_init(mgrid, namespace, space, mesh, der, stencil, mc, nlevels)
Definition: multigrid.F90:184
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.
Definition: stencil.F90:135