multigrid_solver_m Module

Multigrid solver for the Helmholtz problem


Used by


Interfaces

interface

  • public module subroutine create_multigrid_solver(self, multigrid, bnd_type_core, bnd_type_wall, bnd_type_dome, bnd_type_out, co, lambda, xi)

    Creates multigrid solver

    Arguments

    Type IntentOptional Attributes Name
    class(multigrid_solver_t), intent(inout) :: self

    Instance of the type

    type(multigrid_t), intent(in), target :: multigrid

    Multigrid on which to solve the Helmholtz problem

    integer, intent(in) :: bnd_type_core

    Boundary descriptor for core boundary

    integer, intent(in) :: bnd_type_wall

    Boundary descriptor for wall boundary

    integer, intent(in) :: bnd_type_dome

    Boundary descriptor for dome boundary

    integer, intent(in) :: bnd_type_out

    Boundary descriptor for outer(mask) boundary

    real(kind=FP), intent(in), dimension(multigrid%get_np(1)) :: co

    Coefficient co

    real(kind=FP), intent(in), dimension(multigrid%get_np_inner(1)) :: lambda

    Coefficient lambda

    real(kind=FP), intent(in), dimension(multigrid%get_np_inner(1)) :: xi

    Coefficient xi

interface

  • public module subroutine initialize_multigrid_solver(self, ncycle, smoother, npresmooth, npostsmooth, dirsolver)

    Initialises multigrid solver with parameters and solvers

    Arguments

    Type IntentOptional Attributes Name
    class(multigrid_solver_t), intent(inout) :: self

    Instance of the type

    integer, intent(in) :: ncycle

    Number of multigrid cycles 1=V, 2=W

    class(splitting_t), intent(inout), allocatable :: smoother

    Smoother On output the object is deallocated

    integer, intent(in) :: npresmooth

    Number of presmoothing steps

    integer, intent(in) :: npostsmooth

    Number of postsmoothing steps

    class(direct_solver_t), intent(inout), allocatable :: dirsolver

    Direct solver, used on coarsest level On output the object is deallocated

interface

  • public module subroutine update_multigrid_solver(self, co, lambda, xi, bnd_type_core, bnd_type_wall, bnd_type_dome, bnd_type_out)

    Updates multigrid solver with new values of coefficients

    Arguments

    Type IntentOptional Attributes Name
    class(multigrid_solver_t), intent(inout) :: self

    Instance of the type

    real(kind=FP), intent(in), dimension(self%multigrid%get_np(1)) :: co

    Coefficient co

    real(kind=FP), intent(in), dimension(self%multigrid%get_np_inner(1)) :: lambda

    Coefficient lambda

    real(kind=FP), intent(in), dimension(self%multigrid%get_np_inner(1)) :: xi

    Coefficient xi

    integer, intent(in), optional :: bnd_type_core

    Boundary descriptor for core boundary

    integer, intent(in), optional :: bnd_type_wall

    Boundary descriptor for wall boundary

    integer, intent(in), optional :: bnd_type_dome

    Boundary descriptor for dome boundary

    integer, intent(in), optional :: bnd_type_out

    Boundary descriptor for outer(mask) boundary

interface

  • public recursive module subroutine cycle(self, u, b, lvl)

    Performs a multigrid cycle

    Arguments

    Type IntentOptional Attributes Name
    class(multigrid_solver_t), intent(inout) :: self

    Instance of the type

    real(kind=FP), intent(inout), dimension(:) :: u

    On input initial guess, on output result after one cycle

    real(kind=FP), intent(inout), dimension(:) :: b

    Right hand side

    integer, intent(in) :: lvl

    Level

interface

  • public module subroutine residuum(self, u, b, res, resmax)

    Computes the residuum ||Hu-b|| / ||b||

    Arguments

    Type IntentOptional Attributes Name
    class(multigrid_solver_t), intent(in) :: self

    Instance of the type

    real(kind=FP), intent(inout), dimension(:) :: u

    Guess for solution

    real(kind=FP), intent(inout), dimension(:) :: b

    Right hand side

    real(kind=FP), intent(out) :: res

    Residuum (root mean square) : ||Hu-b|| / ||b||+eps

    real(kind=FP), intent(out), optional :: resmax

    Residuum maximum deviation max(Hu-b)

interface

  • public module subroutine expose_multigrid_data(self, intermediate_object, data_object)

    Calls multigrid expose data

    Arguments

    Type IntentOptional Attributes Name
    class(multigrid_solver_t), intent(in) :: self

    Instance of the type

    type(multigrid_intermediate_data_t), intent(out) :: intermediate_object

    Intermediate object

    type(multigrid_data_t), intent(out) :: data_object

    Output object

interface

  • public module subroutine expose_hcsr(self, lvl, res)

    Exposes the Helmholtz matrix for given level Required for the GPU solver.

    Arguments

    Type IntentOptional Attributes Name
    class(multigrid_solver_t), intent(in) :: self

    Instance of the type

    integer, intent(in) :: lvl

    Level for which matrix shall be returned

    type(csrmat_data_t), intent(out) :: res

    Helmholtz matrix for level lvl

interface

  • public module subroutine expose_hdiags_inv(self, res)

    Exposes the inverse diagonal of Helmholtz matrices Required for the GPU solver.

    Arguments

    Type IntentOptional Attributes Name
    class(multigrid_solver_t), intent(in), target :: self

    Instance of the type

    type(c_ptr), intent(out) :: res

    Pointer to inverse diagonal of Helmhotz matrices


Derived Types

type, public ::  multigrid_solver_t

Multigrid solver object

Finalizations Procedures

final :: destructor_multigrid_solver

Type-Bound Procedures

procedure, public :: create => create_multigrid_solver
procedure, public :: update => update_multigrid_solver
procedure, public :: init => initialize_multigrid_solver
procedure, public :: cycle
procedure, public :: residuum
procedure, public :: expose_multigrid_data
procedure, public :: expose_hcsr
procedure, public :: expose_hdiags_inv
procedure, public :: get_hcsr_finest_pointer

Functions

public function get_hcsr_finest_pointer(self) result(ptr)

Returns pointer to Helmholtz matrix on finest level

Arguments

Type IntentOptional Attributes Name
class(multigrid_solver_t), intent(in), target :: self

Instance of the type

Return Value type(csrmat_t), pointer

Pointer to Helmholtz matrix on finest level


Subroutines

public subroutine destructor_multigrid_solver(self)

Frees memory associated with multigrid solver

Arguments

Type IntentOptional Attributes Name
type(multigrid_solver_t), intent(inout) :: self

Instance of the type