ORB5  v4.9.4
parmove_mod Module Reference

Routines for moving markers across parallel subdomains. More...

Data Types

interface  exec
 

Functions/Subroutines

subroutine, public init_module (ld_, nsd_, me_sd_, comm_sd_, natts_max_, nspecies, nsubstep, p_nthreads_, natts_max_l_, natts_max_i8_, natts_max_r4_)
 Initialize module variables. More...
 
subroutine, public init (pos, np, np_new, npmax, run_on_device)
 Prepare the communications (who will send what where) More...
 
subroutine exec_real (arr, natts, npmax, np, run_on_device)
 Perform the communications of marker real attributes accross subdomains. More...
 
subroutine exec_logical (arr, natts, npmax, np, run_on_device)
 Perform the communications of marker logical attributes accross subdomains. More...
 
subroutine exec_integer8 (arr, natts, npmax, np, run_on_device)
 Perform the communications of marker i8 attributes accross subdomains. More...
 
subroutine exec_real4 (arr, natts, npmax, np, run_on_device)
 Perform the communications of marker r4 attributes accross subdomains. More...
 
subroutine, public diag (iter, isp)
 Store some diagnostics about last parmove operation. More...
 

Variables

integer, save nsd
 Number of subdomains. More...
 
real, save lsd_inv
 Inverse of subdomain length. More...
 
integer, save me_sd
 Subdomain MPI rank. More...
 
type(mpi_comm), save comm_sd
 Subdomain communicator. More...
 
integer, dimension(:), allocatable, save scount
 Number of markers leaving towards subdomain i. More...
 
integer, save stot
 Total number of leaving markers. More...
 
integer, dimension(:), allocatable, save sdispl
 Offset in iphole to access markers going to subdomain i. More...
 
integer, dimension(:), allocatable, save iphole
 List of holes indices, sorted by destination subdomain. More...
 
integer, dimension(:), allocatable, save rcount
 Number of markers incoming from subdomain i. More...
 
integer, save rtot
 Total number of incoming markers. More...
 
integer, dimension(:), allocatable, save rdispl
 Offset in iprecv to access markers coming from subdomain i. More...
 
real, dimension(:), allocatable, save sbuf_r
 MPI send buffer for real attributes. More...
 
real, dimension(:), allocatable, save rbuf_r
 MPI receive buffer for real attributes. More...
 
logical, dimension(:), allocatable, save sbuf_l
 MPI send buffer for logical attributes. More...
 
logical, dimension(:), allocatable, save rbuf_l
 MPI receive buffer for logical attributes. More...
 
integer(kind=i8), dimension(:), allocatable, save sbuf_i8
 MPI send buffer for integer8 attributes. More...
 
integer(kind=i8), dimension(:), allocatable, save rbuf_i8
 MPI receive buffer for integer8 attributes. More...
 
integer(kind=r4), dimension(:), allocatable, save sbuf_r4
 MPI send buffer for real4 attributes. More...
 
integer(kind=r4), dimension(:), allocatable, save rbuf_r4
 MPI receive buffer for real4 attributes. More...
 
integer, save salloc
 Allocated size of send buffers. More...
 
integer, save ralloc
 Allocated size of receive buffers. More...
 
integer, save natts_max_r8
 Maximal number of r8 attributes that will be moved at a time. More...
 
integer, save natts_max_l
 Maximal number of logical attributes that will be moved at a time. More...
 
integer, save natts_max_i8
 Maximal number of i8 attributes that will be moved at a time. More...
 
integer, save natts_max_r4
 Maximal number of r4 attributes that will be moved at a time. More...
 
integer, dimension(:,:), allocatable, save cursor
 Current index in subdomains for each OpenMP thread. More...
 
integer, save nbf
 Number of backfill operations. More...
 
integer, dimension(:), allocatable, save obf
 Backfill origin indices (tail) More...
 
integer, dimension(:), allocatable, save tbf
 Backfill target indices (remaining holes) More...
 
integer, save p_nthreads
 Number of OpenMP threads. More...
 
integer, dimension(:,:), allocatable, save scount_threads
 scount decomposed in OpenMP threads More...
 
integer, dimension(:,:), allocatable, save, public np_leaving
 Number of markers leaving the subdomain. More...
 
integer, dimension(:,:), allocatable, save, public ndest
 Number of destinations. More...
 

Detailed Description

Routines for moving markers across parallel subdomains.

Function/Subroutine Documentation

◆ diag()

subroutine, public parmove_mod::diag ( integer, intent(in)  iter,
integer, intent(in)  isp 
)

Store some diagnostics about last parmove operation.

Author
N. Ohana
Date
11.2017
Parameters
[in]iterTime integrator iteration
[in]ispSpecies index
+ Here is the caller graph for this function:

◆ exec_integer8()

subroutine parmove_mod::exec_integer8 ( integer(kind=i8), dimension(npmax, natts), intent(inout)  arr,
  natts,
  npmax,
  np,
  run_on_device 
)
private

Perform the communications of marker i8 attributes accross subdomains.

This routine can be called as many times as necessary after init on different attribute arrays.

Author
N. Ohana
Date
11.2017
Parameters
[in,out]arrMarker attributes to be moved

◆ exec_logical()

subroutine parmove_mod::exec_logical ( logical, dimension(npmax, natts), intent(inout)  arr,
  natts,
  npmax,
  np,
  run_on_device 
)
private

Perform the communications of marker logical attributes accross subdomains.

This routine can be called as many times as necessary after init on different attribute arrays.

Author
N. Ohana
Date
11.2017
Parameters
[in,out]arrMarker attributes to be moved

◆ exec_real()

subroutine parmove_mod::exec_real ( real, dimension(npmax, natts), intent(inout)  arr,
  natts,
  npmax,
  np,
  run_on_device 
)
private

Perform the communications of marker real attributes accross subdomains.

This routine can be called as many times as necessary after init on different attribute arrays.

Author
N. Ohana
Date
11.2017
Parameters
[in,out]arrMarker attributes to be moved

◆ exec_real4()

subroutine parmove_mod::exec_real4 ( real(kind=r4), dimension(npmax, natts), intent(inout)  arr,
  natts,
  npmax,
  np,
  run_on_device 
)
private

Perform the communications of marker r4 attributes accross subdomains.

This routine can be called as many times as necessary after init on different attribute arrays.

Author
N. Ohana
Date
11.2017
Parameters
[in,out]arrMarker attributes to be moved

◆ init()

subroutine, public parmove_mod::init ( real, dimension(:), intent(inout)  pos,
integer, intent(in)  np,
integer, intent(out)  np_new,
integer, intent(in)  npmax,
logical, intent(in)  run_on_device 
)

Prepare the communications (who will send what where)

Author
N. Ohana
Date
11.2017
Parameters
[in,out]posMarker positions in the partitionned direction
[in]npmaxNumber of markers allocated
[in]npLocal number of markers before parmove
[out]np_newLocal number of markers after parmove
[in]run_on_deviceRun kernels on the accelerator
  1. Count number of leaving markers
  2. Communicate scount to get rcount
  3. Build send displacement array
  4. Allocate send arrays
Note
Allocate arrays bigger than necessary to prevent too much future reallocations
Allocate backfill arrays here because nbf <= stot-rtot <= stot
  1. Build list of holes, sorted by destination
  2. Wait for the end of 3.
  3. Build receive displacement array
  4. Allocate receive arrays
Note
Allocate arrays bigger than necessary to prevent too much future reallocations
  1. Check for particle array overflow
  2. Build backfill arrays
    1. Targets (remaining holes)
  1. Origins (tail indices that are not holes)
  2. Check that there are as many targets as origins
  3. Return future local number of markers after parmove
+ Here is the call graph for this function:
+ Here is the caller graph for this function:

◆ init_module()

subroutine, public parmove_mod::init_module ( real, intent(in)  ld_,
integer, intent(in)  nsd_,
integer, intent(in)  me_sd_,
type(mpi_comm), intent(in)  comm_sd_,
integer, intent(in)  natts_max_,
integer, intent(in)  nspecies,
integer, intent(in)  nsubstep,
integer, intent(in)  p_nthreads_,
integer, intent(in), optional  natts_max_l_,
integer, intent(in), optional  natts_max_i8_,
integer, intent(in), optional  natts_max_r4_ 
)

Initialize module variables.

Author
N. Ohana
Date
11.2017
Parameters
[in]ld_Domain length in the partitioned direction
[in]nspeciesNumber of species
[in]nsubstepNumber of iterations of the time integrator

Variable Documentation

◆ comm_sd

type(mpi_comm), save parmove_mod::comm_sd
private

Subdomain communicator.

◆ cursor

integer, dimension(:,:), allocatable, save parmove_mod::cursor
private

Current index in subdomains for each OpenMP thread.

◆ iphole

integer, dimension(:), allocatable, save parmove_mod::iphole
private

List of holes indices, sorted by destination subdomain.

◆ lsd_inv

real, save parmove_mod::lsd_inv
private

Inverse of subdomain length.

◆ me_sd

integer, save parmove_mod::me_sd
private

Subdomain MPI rank.

◆ natts_max_i8

integer, save parmove_mod::natts_max_i8
private

Maximal number of i8 attributes that will be moved at a time.

◆ natts_max_l

integer, save parmove_mod::natts_max_l
private

Maximal number of logical attributes that will be moved at a time.

◆ natts_max_r4

integer, save parmove_mod::natts_max_r4
private

Maximal number of r4 attributes that will be moved at a time.

◆ natts_max_r8

integer, save parmove_mod::natts_max_r8
private

Maximal number of r8 attributes that will be moved at a time.

◆ nbf

integer, save parmove_mod::nbf
private

Number of backfill operations.

◆ ndest

integer, dimension(:,:), allocatable, save, public parmove_mod::ndest

Number of destinations.

◆ np_leaving

integer, dimension(:,:), allocatable, save, public parmove_mod::np_leaving

Number of markers leaving the subdomain.

◆ nsd

integer, save parmove_mod::nsd
private

Number of subdomains.

◆ obf

integer, dimension(:), allocatable, save parmove_mod::obf
private

Backfill origin indices (tail)

◆ p_nthreads

integer, save parmove_mod::p_nthreads
private

Number of OpenMP threads.

◆ ralloc

integer, save parmove_mod::ralloc
private

Allocated size of receive buffers.

◆ rbuf_i8

integer(kind=i8), dimension(:), allocatable, save parmove_mod::rbuf_i8
private

MPI receive buffer for integer8 attributes.

◆ rbuf_l

logical, dimension(:), allocatable, save parmove_mod::rbuf_l
private

MPI receive buffer for logical attributes.

◆ rbuf_r

real, dimension(:), allocatable, save parmove_mod::rbuf_r
private

MPI receive buffer for real attributes.

◆ rbuf_r4

integer(kind=r4), dimension(:), allocatable, save parmove_mod::rbuf_r4
private

MPI receive buffer for real4 attributes.

◆ rcount

integer, dimension(:), allocatable, save parmove_mod::rcount
private

Number of markers incoming from subdomain i.

◆ rdispl

integer, dimension(:), allocatable, save parmove_mod::rdispl
private

Offset in iprecv to access markers coming from subdomain i.

◆ rtot

integer, save parmove_mod::rtot
private

Total number of incoming markers.

◆ salloc

integer, save parmove_mod::salloc
private

Allocated size of send buffers.

◆ sbuf_i8

integer(kind=i8), dimension(:), allocatable, save parmove_mod::sbuf_i8
private

MPI send buffer for integer8 attributes.

◆ sbuf_l

logical, dimension(:), allocatable, save parmove_mod::sbuf_l
private

MPI send buffer for logical attributes.

◆ sbuf_r

real, dimension(:), allocatable, save parmove_mod::sbuf_r
private

MPI send buffer for real attributes.

◆ sbuf_r4

integer(kind=r4), dimension(:), allocatable, save parmove_mod::sbuf_r4
private

MPI send buffer for real4 attributes.

◆ scount

integer, dimension(:), allocatable, save parmove_mod::scount
private

Number of markers leaving towards subdomain i.

◆ scount_threads

integer, dimension(:,:), allocatable, save parmove_mod::scount_threads
private

scount decomposed in OpenMP threads

◆ sdispl

integer, dimension(:), allocatable, save parmove_mod::sdispl
private

Offset in iphole to access markers going to subdomain i.

◆ stot

integer, save parmove_mod::stot
private

Total number of leaving markers.

◆ tbf

integer, dimension(:), allocatable, save parmove_mod::tbf
private

Backfill target indices (remaining holes)