shm_mpi3 Module

This module handles share memory using MPI3 and records the allocation in a linked list such that shared memory can be accessed later in arbitrary location of the code (hopefully)

To do: 1) node barrier with mpi_win_fence (?) 2) extend the redistribution to David's non-blocking mpi

Questions: Can the reference from application array to shm array done safe in fortran (allowing for copy in). Does target attribute helps? What happens if the size on a node is 0? Is base_ptr set to c_nul_ptr? More on the above questions

A clearer way to identify the segments is to return a tag whem shm_alloc is called and to use that tag to get the asociated arrays inside the node. the oply drawback of this is that the application must keep a record of the tags, but this seems similar to other 1-ish kind of tags.

Lucian Anton May 2014



Contents


Variables

Type Visibility Attributes Name Initial
logical, private :: initialized_shm = .false.
integer, private, parameter :: maxlen = 127
type(shm_node_pointers_t), private, pointer :: shm_pointers => null()
type(shm_node_pointers_t), private, pointer :: shm_ptr_head => null()
type(shm_info_t), public, save :: shm_info
integer, private, save :: counter = 0
integer, private, save :: info_noncontig = MPI_INFO_NULL
logical, private, parameter :: debug = .false.

Interfaces

public interface shm_alloc

  • private subroutine shm_alloc_c1(a, lubd, tag, label, ierror)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    complex, intent(inout), pointer :: a(:)
    integer, intent(in) :: lubd(:)
    integer, intent(out), optional :: tag
    character(len=maxlen), intent(in), optional :: label
    integer, intent(out), optional :: ierror
  • private subroutine shm_alloc_c2(a, lubd, tag, label, ierror)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    complex, intent(inout), pointer :: a(:,:)
    integer, intent(in) :: lubd(:)
    integer, intent(out), optional :: tag
    character(len=maxlen), intent(in), optional :: label
    integer, intent(out), optional :: ierror
  • private subroutine shm_alloc_c3(a, lubd, tag, label, ierror)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    complex, intent(inout), pointer :: a(:,:,:)
    integer, intent(in) :: lubd(:)
    integer, intent(out), optional :: tag
    character(len=maxlen), intent(in), optional :: label
    integer, intent(out), optional :: ierror
  • private subroutine shm_alloc_r1(a, lubd, tag, label, ierror)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    real, intent(inout), pointer :: a(:)
    integer, intent(in) :: lubd(:)
    integer, intent(out), optional :: tag
    character(len=maxlen), intent(in), optional :: label
    integer, intent(out), optional :: ierror
  • private subroutine shm_alloc_r2(a, lubd, tag, label, ierror)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    real, intent(inout), pointer :: a(:,:)
    integer, intent(in) :: lubd(:)
    integer, intent(out), optional :: tag
    character(len=maxlen), intent(in), optional :: label
    integer, intent(out), optional :: ierror
  • private subroutine shm_alloc_r3(a, lubd, tag, label, ierror)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    real, intent(inout), pointer :: a(:,:,:)
    integer, intent(in) :: lubd(:)
    integer, intent(out), optional :: tag
    character(len=maxlen), intent(in), optional :: label
    integer, intent(out), optional :: ierror

public interface shm_free

  • private subroutine shm_free_c1(a)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    complex, intent(inout) :: a(:)
  • private subroutine shm_free_c2(a)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    complex, intent(inout) :: a(:,:)
  • private subroutine shm_free_c3(a)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    complex, intent(inout) :: a(:,:,:)
  • private subroutine shm_free_r1(a)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    real, intent(inout) :: a(:)
  • private subroutine shm_free_r2(a)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    real, intent(inout) :: a(:,:)
  • private subroutine shm_free_r3(a)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    real, intent(inout) :: a(:,:,:)

public interface shm_get_node_pointer

  • private function shm_get_node_pointer_c1(pin, id, tag) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    complex, intent(in), target :: pin(:)
    integer, intent(in) :: id
    integer, intent(in), optional :: tag

    Return Value complex, pointer, (:)

  • private function shm_get_node_pointer_c2(pin, id, tag) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    complex, intent(in), target :: pin(:,:)
    integer, intent(in) :: id
    integer, intent(in), optional :: tag

    Return Value complex, pointer, (:,:)

  • private function shm_get_node_pointer_c3(pin, id, tag) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    complex, intent(in), target :: pin(:,:,:)
    integer, intent(in) :: id
    integer, intent(in), optional :: tag

    Return Value complex, pointer, (:,:,:)

  • private function shm_get_node_pointer_r1(pin, id, tag) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    real, intent(in), target :: pin(:)
    integer, intent(in) :: id
    integer, intent(in), optional :: tag

    Return Value real, pointer, (:)

  • private function shm_get_node_pointer_r2(pin, id, tag) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    real, intent(in), target :: pin(:,:)
    integer, intent(in) :: id
    integer, intent(in), optional :: tag

    Return Value real, pointer, (:,:)

  • private function shm_get_node_pointer_r3(pin, id, tag) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    real, intent(in), target :: pin(:,:,:)
    integer, intent(in) :: id
    integer, intent(in), optional :: tag

    Return Value real, pointer, (:,:,:)

private interface remap_bounds

  • private function remap_bounds_1c(lb1, array) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: lb1
    complex, intent(in), DIMENSION(lb1:), TARGET :: array

    Return Value complex, DIMENSION(:), POINTER

  • private function remap_bounds_2c(lb1, lb2, array) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: lb1
    integer, intent(in) :: lb2
    complex, intent(in), DIMENSION(lb1:, lb2:), TARGET :: array

    Return Value complex, DIMENSION(:,:), POINTER

  • private function remap_bounds_3c(lb1, lb2, lb3, array) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: lb1
    integer, intent(in) :: lb2
    integer, intent(in) :: lb3
    complex, intent(in), DIMENSION(lb1:,lb2:,lb3:), TARGET :: array

    Return Value complex, DIMENSION(:,:,:), POINTER

  • private function remap_bounds_1r(lb1, array) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: lb1
    real, intent(in), DIMENSION(lb1:), TARGET :: array

    Return Value real, DIMENSION(:), POINTER

  • private function remap_bounds_2r(lb1, lb2, array) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: lb1
    integer, intent(in) :: lb2
    real, intent(in), DIMENSION(lb1:, lb2:), TARGET :: array

    Return Value real, DIMENSION(:,:), POINTER

  • private function remap_bounds_3r(lb1, lb2, lb3, array) result(ptr)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: lb1
    integer, intent(in) :: lb2
    integer, intent(in) :: lb3
    real, intent(in), DIMENSION(lb1:,lb2:,lb3:), TARGET :: array

    Return Value real, DIMENSION(:,:,:), POINTER

public interface shm_fence

  • private subroutine shm_fence_c(a)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    complex, intent(in), target :: a
  • private subroutine shm_fence_r(a)

    FIXME : Add documentation

    Arguments

    Type IntentOptional Attributes Name
    real, intent(in), target :: a

Derived Types

type, private ::  shm_info_t

FIXME : Add documentation

Components

Type Visibility Attributes Name Initial
integer, public :: comm
integer, public :: wcomm
integer, public :: size
integer, public :: id
integer, public, allocatable :: wranks(:)

type, private ::  shm_node_pointers_t

FIXME : Add documentation

Components

Type Visibility Attributes Name Initial
integer, public :: id
integer, public :: win
integer, public :: ndim
type(c_ptr), public, allocatable :: nd(:)
type(shm_node_pointers_t), public, pointer :: next => null()
integer, public :: tag
integer, public, allocatable :: se(:,:)
character(len=maxlen), public :: label

Functions

public function shm_onnode(ip)

Checks if a node rank belong to the curent node

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: ip

Return Value logical

public function shm_node_id(ip)

returns node id corresponding to ip -1 in case of error

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: ip

Return Value integer

private function shm_get_node_pointer_c1(pin, id, tag) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(in), target :: pin(:)
integer, intent(in) :: id
integer, intent(in), optional :: tag

Return Value complex, pointer, (:)

private function shm_get_node_pointer_c2(pin, id, tag) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(in), target :: pin(:,:)
integer, intent(in) :: id
integer, intent(in), optional :: tag

Return Value complex, pointer, (:,:)

private function shm_get_node_pointer_c3(pin, id, tag) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(in), target :: pin(:,:,:)
integer, intent(in) :: id
integer, intent(in), optional :: tag

Return Value complex, pointer, (:,:,:)

private function shm_get_node_pointer_r1(pin, id, tag) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(in), target :: pin(:)
integer, intent(in) :: id
integer, intent(in), optional :: tag

Return Value real, pointer, (:)

private function shm_get_node_pointer_r2(pin, id, tag) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(in), target :: pin(:,:)
integer, intent(in) :: id
integer, intent(in), optional :: tag

Return Value real, pointer, (:,:)

private function shm_get_node_pointer_r3(pin, id, tag) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(in), target :: pin(:,:,:)
integer, intent(in) :: id
integer, intent(in), optional :: tag

Return Value real, pointer, (:,:,:)

private function remap_bounds_1c(lb1, array) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: lb1
complex, intent(in), DIMENSION(lb1:), TARGET :: array

Return Value complex, DIMENSION(:), POINTER

private function remap_bounds_2c(lb1, lb2, array) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: lb1
integer, intent(in) :: lb2
complex, intent(in), DIMENSION(lb1:, lb2:), TARGET :: array

Return Value complex, DIMENSION(:,:), POINTER

private function remap_bounds_3c(lb1, lb2, lb3, array) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: lb1
integer, intent(in) :: lb2
integer, intent(in) :: lb3
complex, intent(in), DIMENSION(lb1:,lb2:,lb3:), TARGET :: array

Return Value complex, DIMENSION(:,:,:), POINTER

private function remap_bounds_1r(lb1, array) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: lb1
real, intent(in), DIMENSION(lb1:), TARGET :: array

Return Value real, DIMENSION(:), POINTER

private function remap_bounds_2r(lb1, lb2, array) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: lb1
integer, intent(in) :: lb2
real, intent(in), DIMENSION(lb1:, lb2:), TARGET :: array

Return Value real, DIMENSION(:,:), POINTER

private function remap_bounds_3r(lb1, lb2, lb3, array) result(ptr)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: lb1
integer, intent(in) :: lb2
integer, intent(in) :: lb3
real, intent(in), DIMENSION(lb1:,lb2:,lb3:), TARGET :: array

Return Value real, DIMENSION(:,:,:), POINTER


Subroutines

public subroutine shm_init(wcomm, split_)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: wcomm
logical, intent(in), optional :: split_

private subroutine shm_alloc_c1(a, lubd, tag, label, ierror)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(inout), pointer :: a(:)
integer, intent(in) :: lubd(:)
integer, intent(out), optional :: tag
character(len=maxlen), intent(in), optional :: label
integer, intent(out), optional :: ierror

private subroutine shm_alloc_c2(a, lubd, tag, label, ierror)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(inout), pointer :: a(:,:)
integer, intent(in) :: lubd(:)
integer, intent(out), optional :: tag
character(len=maxlen), intent(in), optional :: label
integer, intent(out), optional :: ierror

private subroutine shm_alloc_c3(a, lubd, tag, label, ierror)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(inout), pointer :: a(:,:,:)
integer, intent(in) :: lubd(:)
integer, intent(out), optional :: tag
character(len=maxlen), intent(in), optional :: label
integer, intent(out), optional :: ierror

private subroutine shm_alloc_c(ndim, lubd, a1, a2, a3, tag, label, ierror)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: ndim
integer, intent(in) :: lubd(2*ndim)
complex, intent(inout), optional, pointer :: a1(:)
complex, intent(inout), optional, pointer :: a2(:,:)
complex, intent(inout), optional, pointer :: a3(:,:,:)
integer, intent(out), optional :: tag
character(len=maxlen), intent(in), optional :: label
integer, intent(out), optional :: ierror

private subroutine shm_alloc_r1(a, lubd, tag, label, ierror)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(inout), pointer :: a(:)
integer, intent(in) :: lubd(:)
integer, intent(out), optional :: tag
character(len=maxlen), intent(in), optional :: label
integer, intent(out), optional :: ierror

private subroutine shm_alloc_r2(a, lubd, tag, label, ierror)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(inout), pointer :: a(:,:)
integer, intent(in) :: lubd(:)
integer, intent(out), optional :: tag
character(len=maxlen), intent(in), optional :: label
integer, intent(out), optional :: ierror

private subroutine shm_alloc_r3(a, lubd, tag, label, ierror)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(inout), pointer :: a(:,:,:)
integer, intent(in) :: lubd(:)
integer, intent(out), optional :: tag
character(len=maxlen), intent(in), optional :: label
integer, intent(out), optional :: ierror

private subroutine shm_alloc_r(ndim, lubd, a1, a2, a3, tag, label, ierror)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: ndim
integer, intent(in) :: lubd(2*ndim)
real, intent(inout), optional, pointer :: a1(:)
real, intent(inout), optional, pointer :: a2(:,:)
real, intent(inout), optional, pointer :: a3(:,:,:)
integer, intent(out), optional :: tag
character(len=maxlen), intent(in), optional :: label
integer, intent(out), optional :: ierror

private subroutine shm_free_c1(a)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(inout) :: a(:)

private subroutine shm_free_c2(a)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(inout) :: a(:,:)

private subroutine shm_free_c3(a)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(inout) :: a(:,:,:)

private subroutine shm_free_c(a)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(inout), target :: a(*)

private subroutine shm_free_r1(a)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(inout) :: a(:)

private subroutine shm_free_r2(a)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(inout) :: a(:,:)

private subroutine shm_free_r3(a)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(inout) :: a(:,:,:)

private subroutine shm_free_r(a)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(inout), target :: a(*)

public subroutine shm_node_barrier()

FIXME : Add documentation
ifdef 1 endif

Arguments

None

private subroutine shm_fence_r(a)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
real, intent(in), target :: a

private subroutine shm_fence_c(a)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
complex, intent(in), target :: a

private subroutine shm_get_node_pointer_c(pin, id, a1, a2, a3, tag)

FIXME : Add documentation
$ pointer_array: do j = 1, size(shm_info%g_lo_ptr) $ do i = 0, shm_info%size -1 $ s = shm_info%g_lo_se(1, i) $ e = shm_info%g_lo_se(2, i) $ aux => shm_info%g_lo_ptr(j)%p(:,:, s:e) $ !print*,'get_node_pointer', iproc, i,j,s,e $ if ( associated(aux, pin)) then $ get_node_pointer => shm_info%g_lo_ptr(j)%p $ !print'(a,7(i5,x))','get_node_pointer', iproc, lbound(get_node_pointer), ubound(get_node_pointer) $ exit pointer_array $ endif $ end do $ enddo pointer_array

Arguments

Type IntentOptional Attributes Name
complex, intent(in), target :: pin(*)
integer, intent(in) :: id
complex, intent(out), optional, pointer :: a1(:)
complex, intent(out), optional, pointer :: a2(:,:)
complex, intent(out), optional, pointer :: a3(:,:,:)
integer, intent(in), optional :: tag

private subroutine shm_get_node_pointer_r(pin, id, a1, a2, a3, tag)

FIXME : Add documentation
$ pointer_array: do j = 1, size(shm_info%g_lo_ptr) $ do i = 0, shm_info%size -1 $ s = shm_info%g_lo_se(1, i) $ e = shm_info%g_lo_se(2, i) $ aux => shm_info%g_lo_ptr(j)%p(:,:, s:e) $ !print*,'get_node_pointer', iproc, i,j,s,e $ if ( associated(aux, pin)) then $ get_node_pointer => shm_info%g_lo_ptr(j)%p $ !print'(a,7(i5,x))','get_node_pointer', iproc, lbound(get_node_pointer), ubound(get_node_pointer) $ exit pointer_array $ endif $ end do $ enddo pointer_array

Arguments

Type IntentOptional Attributes Name
real, intent(in), target :: pin(*)
integer, intent(in) :: id
real, intent(out), optional, pointer :: a1(:)
real, intent(out), optional, pointer :: a2(:,:)
real, intent(out), optional, pointer :: a3(:,:,:)
integer, intent(in), optional :: tag

public subroutine shm_clean()

FIXME : Add documentation

Arguments

None

private subroutine error_abort(s)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: s