next up previous contents
Next: 10 Sprase Matrix Support Up: 2 High Level API's Previous: 8 Sending and Receiving   Contents

Subsections

9 Rearranging Attribute Vectors

9.1 Module m_Rearranger - Remaps an AttrVect within a group of processes (Source File: m_Rearranger.F90)

This module provides routines and datatypes for rearranging data between two Attribute Vectors defined on the same grid but with two different GlobalSegMaps. ''Rearrange'' is a generalized form of a parallel matrix transpose. A parallel matrix transpose can take advantage of symmetry in the data movement algorithm. An MCT Rearranger makes no assumptions about symmetry.

When data needs to move between two components and the components share any processors, use m_Rearranger. If the components are on distinct sets of processors, use m_Transfer.


SEE ALSO:

    m_Transfer
INTERFACE:
 
  module m_Rearranger
USES:
 
       use m_Router, only : Router
 
       implicit none
 
       private	! except
PUBLIC DATA MEMBERS:
 
       public :: Rearranger  ! The class data structure
 
       type :: Rearranger
 #ifdef SEQUENCE
          sequence
 #endif
          private 
          type(Router) :: SendRouter
          type(Router) :: RecvRouter
          integer,dimension(:,:),pointer :: LocalPack
          integer :: LocalSize
       end type Rearranger
 
   !PRIVATE DATA MEMBERS:
       integer :: max_nprocs  ! size of MPI_COMM_WORLD used for generation of
                              ! local automatic arrays
PUBLIC MEMBER FUNCTIONS:
 
       public :: init         ! creation method
 
       public :: rearrange    ! the rearrange routine
 
       public :: clean        ! destruction method
       public :: print        ! print out comm info
 
       interface init      ; module procedure init_      ; end interface
       interface Rearrange ; module procedure Rearrange_ ; end interface
       interface clean     ; module procedure clean_     ; end interface
       interface print     ; module procedure print_     ; end interface
DEFINED PARAMETERS:
 
   integer,parameter                    :: DefaultTag = 500
REVISION HISTORY:
   31Jan02 - E.T. Ong <[email protected]> - initial prototype
   04Jun02 - E.T. Ong <[email protected]> - changed local copy structure to
             LocalSize. Made myPid a global process in MCTWorld.
   27Sep02 - R. Jacob <[email protected]> - Remove SrcAVsize and TrgAVsize
             and use Router%lAvsize instead for sanity check.
   25Jan08 - R. Jacob <[email protected]> - Add ability to handle unordered
             gsmaps.

9.1.1 Init_ - Initialize a Rearranger

This routine takes two GlobalSegMap inputs, SourceGSMap and TargetGSMap and build a Rearranger OutRearranger between them. myComm is used for the internal communication.

N.B. The two GlolbalSegMap inputs must be initialized so that the index values on a processor are in ascending order.


INTERFACE:

 
  subroutine init_(SourceGSMap,TargetGSMap,myComm,OutRearranger)
USES:
 
    use m_MCTWorld,     only : ThisMCTWorld
    use m_GlobalSegMap, only : GlobalSegMap
    use m_GlobalSegMap, only : GSMap_lsize => lsize
    use m_GlobalSegMap, only : GSMap_increasing => increasing
    use m_Router,       only : Router     
    use m_Router,       only : Router_init => init
    use m_mpif90
    use m_die
    use m_stdio
 
    implicit none
INPUT PARAMETERS:
    type(GlobalSegMap), intent(in)            :: SourceGSMap, TargetGSMap
    integer,            intent(in)            :: myComm
OUTPUT PARAMETERS:
    type(Rearranger),   intent(out)           :: OutRearranger
REVISION HISTORY:
   31Jan02 - E.T. Ong <[email protected]> - initial prototype
   20Mar02 - E.T. Ong <[email protected]> - working code
   05Jun02 - E.T. Ong <[email protected]> - Use LocalPack
   30Mar06 - P. Worley <[email protected]> - added max_nprocs,
             used in communication optimizations in rearrange

9.1.2 clean_ - Clean a Rearranger

This routine deallocates allocated memory associated with the input/output Rearranger argument ReArr. The success (failure) of this operation is reported in the zero (nonzero) value of the optional output INTEGER argument status.


INTERFACE:

 
  subroutine clean_(ReArr, status)
USES:
    use m_Router,only : Router     
    use m_Router,only : Router_clean => clean
    use m_mpif90
    use m_die
    use m_stdio
 
    implicit none
INPUT/OUTPUT PARAMETERS:
    type(Rearranger),    intent(inout)           :: ReArr
OUTPUT PARAMETERS:
    integer, optional,   intent(out)             :: status
REVISION HISTORY:
   31Jan02 - E.T. Ong <[email protected]> - initial prototype
   20Mar02 - E.T. Ong <[email protected]> - working code

9.1.3 rearrange_ - Rearrange data between two Attribute Vectors

This subroutine will take data in the SourceAv Attribute Vector and rearrange it to match the GlobalSegMap used to define the TargetAv Attribute Vector using the Rearrnger InRearranger.

The optional argument Tag can be used to set the tag value used in the rearrangement. DefaultTag will be used otherwise.

If the optional argument Sum is present and true, data for the same physical point coming from two or more processes will be summed. Otherwise, data is overwritten.

If the optional argument Vector is present and true, vector architecture-friendly parts of this routine will be invoked.

If the optional argument AlltoAll is present and true, the communication will be done with an alltoall call instead of individual sends and receives.

The size of the SourceAv and TargetAv argument must match those stored in the InRearranger or and error will result.

N.B.: SourceAv and TargetAv are assumed to have exactly the same attributes in exactly the same order.


INTERFACE:

 
  subroutine rearrange_(SourceAVin,TargetAV,InRearranger,Tag,Sum,Vector,AlltoAll)
USES:
 
    use m_MCTWorld,only :MCTWorld
    use m_MCTWorld,only :ThisMCTWorld
    use m_AttrVect,  only : AttrVect
    use m_AttrVect,  only : AttrVect_init => init
    use m_AttrVect,  only : AttrVect_lsize => lsize
    use m_AttrVect,  only : AttrVect_copy => copy
    use m_AttrVect,  only : AttrVect_clean => clean
    use m_AttrVect,  only : AttrVect_zero => zero
    use m_AttrVect,  only : nIAttr,nRAttr
    use m_AttrVect,  only : Permute,Unpermute
    use m_Router,    only : Router     
    use m_realkinds, only : FP
    use m_mpif90
    use m_die
    use m_stdio
 
    implicit none
INPUT/OUTPUT PARAMETERS:
    type(AttrVect),             intent(inout)   :: TargetAV
INPUT PARAMETERS:
    type(AttrVect),   target,   intent(in)      :: SourceAVin
    type(Rearranger), target,   intent(in)      :: InRearranger
    integer,          optional, intent(in)      :: Tag
    logical,          optional, intent(in)      :: Sum
    logical,          optional, intent(in)      :: Vector
    logical,          optional, intent(in)      :: AlltoAll
REVISION HISTORY:
   31Jan02 - E.T. Ong <[email protected]> - initial prototype
   20Mar02 - E.T. Ong <[email protected]> - working code
   08Jul02 - E.T. Ong <[email protected]> - change intent of Target,Source
   29Oct03 - R. Jacob <[email protected]> - add optional argument vector
             to control use of vector-friendly mods provided by Fujitsu.
   30Mar06 - P. Worley <[email protected]> - added alltoall option and
             reordered send/receive order to improve communication 
             performance.  Also remove replace allocated arrays with
             automatic.
   14Oct06 - R. Jacob <[email protected]> - check value of Sum argument.
   25Jan08 - R. Jacob <[email protected]> - Permute/unpermute if the internal
             routers permarr is defined.

9.1.4 print_ - Print rearranger communication info

Print out communication info for both routers in a rearranger. Print out on unit number 'lun' e.g. (source,destination,length)


INTERFACE:

 
     subroutine print_(rearr,mycomm,lun)
USES:
       use m_die
       use m_Router, only: router_print => print
 
       implicit none
INPUT/OUTPUT PARAMETERS:
       type(Rearranger),      intent(in) :: rearr
       integer, intent(in)           :: mycomm
       integer, intent(in)           :: lun
REVISION HISTORY:
   27Jul07 - R. Loy <[email protected]>  initial version



next up previous contents
Next: 10 Sprase Matrix Support Up: 2 High Level API's Previous: 8 Sending and Receiving   Contents
[email protected]