Octopus
par_vec_oct_m Module Reference

Some general things and nomenclature: More...

Detailed Description

Some general things and nomenclature:

  • Points that are stored only on one process are called local points.
  • Local points that are stored redundantly on another process because of the partitioning are called ghost points.
  • Boundary points are stored locally such that each process has all points it needs for the finite differences
  • np is the total number of inner points.

A globally defined vector v has two parts:

  • v(1:np) are the inner points
  • v(np+1:np_part) are the boundary points In the typical case of zero boundary conditions v(np+1:np_part) is 0. The two parts are split according to the partitions. The result of this split are local vectors vl on each process which consist of three parts:
  • vl(1:np_local) local points.
  • vl(np_local+1:np_local+np_ghost) ghost points.
  • vl(np_local+np_ghost+1:np_local+np_ghost+np_bndry) boundary points.

Usage example for par_vec routines.

 ! Initialize parallelization with mesh and operator op
 ! initialized and given.
 ! mesh = sys%gr%mesh
 ! stencil = op%stencil

 real(real64) :: uu(np_global), vv(np_global)
 real(real64), allocatable :: ul(:), vl(:), wl(:)
 type(mesh_t) :: mesh

 ! Fill uu, vv with sensible values.
 ! ...

 ! Allocate space for local vectors.
 allocate(ul(np_part))
 allocate(vl(np_part))
 allocate(wl(np_part))

 ! Distribute vectors.
 call vec_scatter(vp, uu, ul)
 call vec_scatter(vp, vv, vl)

 ! Compute some operator op: vl = op ul
 call X(vec_ghost_update)(vp, ul)
 call X(nl_operator_operate)(op, ul, vl)
 !! Gather result of op in one vector vv.
 call vec_gather(vp, vv, vl)

 ! Clean up.
 deallocate(ul, vl, wl)

Data Types

interface  par_vec_allgather
 
interface  par_vec_gather
 
interface  par_vec_scatter
 
type  par_vec_t
 Parallel information. More...
 

Functions/Subroutines

subroutine, public par_vec_init (mpi_grp, np_global, idx, stencil, space, partition, pv, namespace)
 Initializes a par_vec_type object (parallel vector). More...
 
subroutine, public par_vec_end (pv)
 Deallocate memory used by pv. More...
 
integer function, public par_vec_global2local (pv, ipg)
 Returns local number of global point ip on the local node If the result is zero, the point is not available on the local node. More...
 
integer(int64) function, public par_vec_local2global (pv, ip)
 Returns global index of local point ip. More...
 
subroutine gather_local_vec (pv, root, local_vec)
 
subroutine zpar_vec_scatter (pv, root, v_local, v)
 Generally: Xpar_vec_gather and Xpar_vec_scatter only consider inner points. Xpar_vec_scatter_bndry takes care of boundary points (there is no Xpar_vec_gather_bndry as they are only written and not read). Xpar_vec_scatter_all is Xpar_vec_scatter followd by Xpar_vec_scatter_bndry. More...
 
subroutine zpar_vec_gather (pv, root, v_local, v)
 Reverse operation of Xpar_vec_scatter. All v_locals from the nodes are packed together into v on node root in correct order. More...
 
subroutine zpar_vec_allgather (pv, v, v_local)
 Like Xpar_vec_gather but the result is gathered on all nodes, i. e. v has to be a properly allocated array on all nodes. More...
 
subroutine dpar_vec_scatter (pv, root, v_local, v)
 Generally: Xpar_vec_gather and Xpar_vec_scatter only consider inner points. Xpar_vec_scatter_bndry takes care of boundary points (there is no Xpar_vec_gather_bndry as they are only written and not read). Xpar_vec_scatter_all is Xpar_vec_scatter followd by Xpar_vec_scatter_bndry. More...
 
subroutine dpar_vec_gather (pv, root, v_local, v)
 Reverse operation of Xpar_vec_scatter. All v_locals from the nodes are packed together into v on node root in correct order. More...
 
subroutine dpar_vec_allgather (pv, v, v_local)
 Like Xpar_vec_gather but the result is gathered on all nodes, i. e. v has to be a properly allocated array on all nodes. More...
 
subroutine ipar_vec_scatter (pv, root, v_local, v)
 Generally: Xpar_vec_gather and Xpar_vec_scatter only consider inner points. Xpar_vec_scatter_bndry takes care of boundary points (there is no Xpar_vec_gather_bndry as they are only written and not read). Xpar_vec_scatter_all is Xpar_vec_scatter followd by Xpar_vec_scatter_bndry. More...
 
subroutine ipar_vec_gather (pv, root, v_local, v)
 Reverse operation of Xpar_vec_scatter. All v_locals from the nodes are packed together into v on node root in correct order. More...
 
subroutine ipar_vec_allgather (pv, v, v_local)
 Like Xpar_vec_gather but the result is gathered on all nodes, i. e. v has to be a properly allocated array on all nodes. More...
 

Function/Subroutine Documentation

◆ par_vec_init()

subroutine, public par_vec_oct_m::par_vec_init ( type(mpi_grp_t), intent(in)  mpi_grp,
integer(int64), intent(in)  np_global,
type(index_t), intent(in)  idx,
type(stencil_t), intent(in)  stencil,
class(space_t), intent(in)  space,
type(partition_t), intent(in)  partition,
type(par_vec_t), intent(inout)  pv,
type(namespace_t), intent(in)  namespace 
)

Initializes a par_vec_type object (parallel vector).

It computes the local-to-global and global-to-local index tables and the ghost point exchange.

Warning
The naming scheme for the np_ variables is different from how it is in the rest of the code (for historical reasons and also because the vec_init has more a global than local point of view on the mesh): See the comments in the parameter list.
Parameters
[in]mpi_grpMPI group to use.
[in]np_globalmeshnp_global
[in]stencilThe stencil for which to calculate ghost points.
[in,out]pvDescription of partition.

Definition at line 293 of file par_vec.F90.

◆ par_vec_end()

subroutine, public par_vec_oct_m::par_vec_end ( type(par_vec_t), intent(inout)  pv)

Deallocate memory used by pv.

Definition at line 743 of file par_vec.F90.

◆ par_vec_global2local()

integer function, public par_vec_oct_m::par_vec_global2local ( type(par_vec_t), intent(in)  pv,
integer(int64), intent(in)  ipg 
)

Returns local number of global point ip on the local node If the result is zero, the point is not available on the local node.

Definition at line 781 of file par_vec.F90.

◆ par_vec_local2global()

integer(int64) function, public par_vec_oct_m::par_vec_local2global ( type(par_vec_t), intent(in)  pv,
integer, intent(in)  ip 
)

Returns global index of local point ip.

Definition at line 802 of file par_vec.F90.

◆ gather_local_vec()

subroutine par_vec_oct_m::gather_local_vec ( type(par_vec_t), intent(in)  pv,
integer, intent(in)  root,
integer(int64), dimension(:), intent(inout), allocatable  local_vec 
)
private

Definition at line 825 of file par_vec.F90.

◆ zpar_vec_scatter()

subroutine par_vec_oct_m::zpar_vec_scatter ( type(par_vec_t), intent(in)  pv,
integer, intent(in)  root,
complex(real64), dimension(:), intent(out)  v_local,
complex(real64), dimension(:), intent(in)  v 
)
private

Generally: Xpar_vec_gather and Xpar_vec_scatter only consider inner points. Xpar_vec_scatter_bndry takes care of boundary points (there is no Xpar_vec_gather_bndry as they are only written and not read). Xpar_vec_scatter_all is Xpar_vec_scatter followd by Xpar_vec_scatter_bndry.

Definition at line 922 of file par_vec.F90.

◆ zpar_vec_gather()

subroutine par_vec_oct_m::zpar_vec_gather ( type(par_vec_t), intent(in)  pv,
integer, intent(in)  root,
complex(real64), dimension(:), intent(in)  v_local,
complex(real64), dimension(:), intent(out), optional  v 
)
private

Reverse operation of Xpar_vec_scatter. All v_locals from the nodes are packed together into v on node root in correct order.

Parameters
[out]vin order to prevent unassociated pointer errors,

Definition at line 985 of file par_vec.F90.

◆ zpar_vec_allgather()

subroutine par_vec_oct_m::zpar_vec_allgather ( type(par_vec_t), intent(in)  pv,
complex(real64), dimension(:), intent(out)  v,
complex(real64), dimension(:), intent(in)  v_local 
)
private

Like Xpar_vec_gather but the result is gathered on all nodes, i. e. v has to be a properly allocated array on all nodes.

Definition at line 1047 of file par_vec.F90.

◆ dpar_vec_scatter()

subroutine par_vec_oct_m::dpar_vec_scatter ( type(par_vec_t), intent(in)  pv,
integer, intent(in)  root,
real(real64), dimension(:), intent(out)  v_local,
real(real64), dimension(:), intent(in)  v 
)
private

Generally: Xpar_vec_gather and Xpar_vec_scatter only consider inner points. Xpar_vec_scatter_bndry takes care of boundary points (there is no Xpar_vec_gather_bndry as they are only written and not read). Xpar_vec_scatter_all is Xpar_vec_scatter followd by Xpar_vec_scatter_bndry.

Definition at line 1150 of file par_vec.F90.

◆ dpar_vec_gather()

subroutine par_vec_oct_m::dpar_vec_gather ( type(par_vec_t), intent(in)  pv,
integer, intent(in)  root,
real(real64), dimension(:), intent(in)  v_local,
real(real64), dimension(:), intent(out), optional  v 
)
private

Reverse operation of Xpar_vec_scatter. All v_locals from the nodes are packed together into v on node root in correct order.

Parameters
[out]vin order to prevent unassociated pointer errors,

Definition at line 1213 of file par_vec.F90.

◆ dpar_vec_allgather()

subroutine par_vec_oct_m::dpar_vec_allgather ( type(par_vec_t), intent(in)  pv,
real(real64), dimension(:), intent(out)  v,
real(real64), dimension(:), intent(in)  v_local 
)
private

Like Xpar_vec_gather but the result is gathered on all nodes, i. e. v has to be a properly allocated array on all nodes.

Definition at line 1275 of file par_vec.F90.

◆ ipar_vec_scatter()

subroutine par_vec_oct_m::ipar_vec_scatter ( type(par_vec_t), intent(in)  pv,
integer, intent(in)  root,
integer, dimension(:), intent(out)  v_local,
integer, dimension(:), intent(in)  v 
)
private

Generally: Xpar_vec_gather and Xpar_vec_scatter only consider inner points. Xpar_vec_scatter_bndry takes care of boundary points (there is no Xpar_vec_gather_bndry as they are only written and not read). Xpar_vec_scatter_all is Xpar_vec_scatter followd by Xpar_vec_scatter_bndry.

Definition at line 1378 of file par_vec.F90.

◆ ipar_vec_gather()

subroutine par_vec_oct_m::ipar_vec_gather ( type(par_vec_t), intent(in)  pv,
integer, intent(in)  root,
integer, dimension(:), intent(in)  v_local,
integer, dimension(:), intent(out), optional  v 
)
private

Reverse operation of Xpar_vec_scatter. All v_locals from the nodes are packed together into v on node root in correct order.

Parameters
[out]vin order to prevent unassociated pointer errors,

Definition at line 1441 of file par_vec.F90.

◆ ipar_vec_allgather()

subroutine par_vec_oct_m::ipar_vec_allgather ( type(par_vec_t), intent(in)  pv,
integer, dimension(:), intent(out)  v,
integer, dimension(:), intent(in)  v_local 
)
private

Like Xpar_vec_gather but the result is gathered on all nodes, i. e. v has to be a properly allocated array on all nodes.

Definition at line 1503 of file par_vec.F90.