next up previous contents
Next: 5 The General Grid Up: 1 Basic API's and Previous: 3 Global Segment Map   Contents

Subsections

4 The Router

4.1 Module m_Router - Router class (Source File: m_Router.F90)

The Router data type contains all the information needed to send an AttrVect between a component on M MPI-processes and a component on N MPI-processes. This module defines the Router datatype and provides methods to create and destroy one.


INTERFACE:

 
  module m_Router
 
       use m_realkinds, only : FP
       use m_zeit
 
       implicit none
 
       private   ! except
 
   !declare a private pointer structure for the real data
       type :: rptr
 #ifdef SEQUENCE
         sequence
 #endif
         real(FP),dimension(:),pointer :: pr
       end type
 
   !declare a private pointer structure for the integer data
       type :: iptr
 #ifdef SEQUENCE
         sequence
 #endif
         integer,dimension(:),pointer :: pi
       end type
PUBLIC TYPES:
       public :: Router	        ! The class data structure
 
       public :: rptr,iptr       ! pointer types used in Router
 
     type Router
 #ifdef SEQUENCE
       sequence
 #endif
       integer :: comp1id                           ! myid
       integer :: comp2id                           ! id of second component
       integer :: nprocs	                           ! number of procs to talk to
       integer :: maxsize                           ! maximum amount of data going to a processor
       integer :: lAvsize                           ! The local size of AttrVect which can be 
                                                    ! used with this Router in MCT_Send/MCT_Recv
       integer :: numiatt                           ! Number of integer attributes currently in use
       integer :: numratt                           ! Number of real attributes currently in use
       integer,dimension(:),pointer   :: pe_list    ! processor ranks of send/receive in MCT_comm
       integer,dimension(:),pointer   :: num_segs   ! number of segments to send/receive
       integer,dimension(:),pointer   :: locsize    ! total of seg_lengths for a proc
       integer,dimension(:),pointer   :: permarr    ! possible permutation array
       integer,dimension(:,:),pointer :: seg_starts ! starting index
       integer,dimension(:,:),pointer :: seg_lengths! total length
       type(rptr),dimension(:),pointer :: rp1       ! buffer to hold real data
       type(iptr),dimension(:),pointer :: ip1       ! buffer to hold integer data
       integer,dimension(:),pointer   :: ireqs,rreqs  ! buffer for MPI_Requests
       integer,dimension(:,:),pointer :: istatus,rstatus  ! buffer for MPI_Status
     end type Router
PUBLIC MEMBER FUNCTIONS:
       public :: init            ! Create a Router
       public :: clean           ! Destroy a Router
       public :: print           ! Print info about a Router
 
 
     interface init  ; module procedure  &
         initd_, &       ! initialize a Router between two seperate components
         initp_ 	        ! initialize a Router locally with two GSMaps
     end interface
     interface clean ; module procedure clean_ ; end interface
     interface print ; module procedure print_ ; end interface
REVISION HISTORY:
   15Jan01 - R. Jacob <[email protected]> - initial prototype
   08Feb01 - R. Jacob <[email protected]> add locsize and maxsize 
             to Router type
   25Sep02 - R. Jacob <[email protected]> Remove type string.  Add lAvsize
   23Jul03 - R. Jacob <[email protected]> Add status and reqs arrays used
             in send/recv to the Router datatype.
   24Jul03 - R. Jacob <[email protected]> Add real and integer buffers
             for send/recv to the Router datatype.
   22Jan08 - R. Jacob <[email protected]> Add ability to handle an unordered
             GSMap by creating a new, ordered one and building Router from
             that.  Save permutation info in Router datatype.

4.1.1 initd_ - initialize a Router between two seperate components

The routine initd_() exchanges the GSMap with the component identified by othercomp and then calls initp_() to build a Router Rout between them.

N.B. The GSMap argument must be declared so that the index values on a processor are in ascending order.


INTERFACE:

 
  subroutine initd_(othercomp,GSMap,mycomm,Rout,name )
USES:
       use m_GlobalSegMap, only :GlobalSegMap
       use m_ExchangeMaps,only: MCT_ExGSMap => ExchangeMap
       use m_mpif90
       use m_die
 
       implicit none
INPUT PARAMETERS:
       integer, intent(in)	       :: othercomp
       integer, intent(in)	       :: mycomm
       type(GlobalSegMap),intent(in)    :: GSMap     ! of the calling comp
       character(len=*), intent(in),optional     :: name
OUTPUT PARAMETERS:
       type(Router), intent(out)        :: Rout
REVISION HISTORY:
   15Jan01 - R. Jacob <[email protected]> - initial prototype
   06Feb01 - R. Jacob <[email protected]> - Finish initialization
             of the Router.  Router now works both ways.
   25Apr01 - R. Jacob <[email protected]> - Eliminate early 
             custom code to exchange GSMap components and instead
             the more general purpose routine in m_ExchangeMaps.
             Use new subroutine OrderedPoints in m_GlobalSegMap
             to construct the vector of local and remote GSMaps.
             Clean-up code a little.
   03May01 - R. Jacob <[email protected]> - rename to initd and
             move most of code to new initp routine

4.1.2 initp_ - initialize a Router from two GlobalSegMaps

Given two GlobalSegmentMaps GSMap and RGSMap, intialize a Router Rout between them. Use local communicator mycomm.

N.B. The two GSMap arguments must be declared so that the index values on a processor are in ascending order.


INTERFACE:

 
  subroutine initp_(inGSMap,inRGSMap,mycomm,Rout,name )
USES:
       use m_GlobalSegMap,  only :GlobalSegMap
       use m_GlobalSegMap,  only :ProcessStorage
       use m_GlobalSegMap,  only :GSMap_comp_id => comp_id
       use m_GlobalSegMap,  only :GSMap_increasing => increasing
       use m_GlobalSegMap,  only :GlobalSegMap_copy => copy
       use m_GlobalSegMap,  only :GlobalSegMap_init => init
       use m_GlobalSegMap,  only :GlobalSegMap_clean => clean
       use m_GlobalSegMap,  only :GlobalSegMap_OPoints => OrderedPoints
       use m_GlobalSegMap,  only :GlobalSegMap_ngseg => ngseg  ! rml
       use m_GlobalSegMap,  only :GlobalSegMap_nlseg => nlseg  ! rml
       use m_GlobalSegMap,  only :GlobalSegMap_max_nlseg => max_nlseg  ! rml
 
       use m_GlobalToLocal, only :GlobalToLocalIndex
       use m_MCTWorld,      only :MCTWorld
       use m_MCTWorld,      only :ThisMCTWorld
 
       use m_Permuter      ,only:Permute
       use m_MergeSorts    ,only:IndexSet
       use m_MergeSorts    ,only:IndexSort
 
       use m_mpif90
       use m_die
 
        use m_zeit
 
 
       use m_stdio    ! rml
        use shr_timer_mod        ! rml timers
 
       implicit none
INPUT PARAMETERS:
       type(GlobalSegMap), intent(in)	:: inGSMap
       type(GlobalSegMap), intent(in)	:: inRGSMap
       integer	     ,    intent(in)	:: mycomm
       character(len=*), intent(in),optional     :: name
OUTPUT PARAMETERS:
       type(Router),      intent(out)	:: Rout
REVISION HISTORY:
   03May01 - R.L. Jacob <[email protected]> - Initial code brought
             in from old init routine.
   31Jul01 - Jace A Mogill <[email protected]>
             Rewrote to reduce number of loops and temp storage
   26Apr06 - R. Loy <[email protected]> - recode the search through
             the remote GSMap to improve efficiency
   05Jan07 - R. Loy <[email protected]> - improved bound on size of 
             tmpsegcount and tmpsegstart
   15May07 - R. Loy <[email protected]> - improved bound on size of
             rgs_lb and rgs_ub
   25Jan08 - R. Jacob <[email protected]> - Dont die if GSMap is not
             increasing.  Instead, permute it to increasing and proceed.
   07Sep12 - T. Craig <[email protected]> - Replace a double loop with a single
             to improve speed for large proc and segment counts.

4.1.3 clean_ - Destroy a Router

Deallocate Router internal data structures and set integer parts to zero.


INTERFACE:

 
     subroutine clean_(Rout,stat)
USES:
       use m_die
 
       implicit none
INPUT/OUTPUT PARAMETERS:
       type(Router),      intent(inout) :: Rout
OUTPUT PARAMETERS:
       integer, optional, intent(out)   :: stat
REVISION HISTORY:
   15Jan01 - R. Jacob <[email protected]> - initial prototype
   08Feb01 - R. Jacob <[email protected]> - add code to clean
             the maxsize and locsize
   01Mar02 - E.T. Ong <[email protected]> removed the die to prevent
             crashes and added stat argument.

4.1.4 print_ - Print router info

Print out communication info about router on unit number 'lun' e.g. (source,destination,length)


INTERFACE:

 
     subroutine print_(rout,mycomm,lun)
USES:
       use m_die
       use m_mpif90
 
       implicit none
INPUT/OUTPUT PARAMETERS:
       type(Router),      intent(in) :: Rout
       integer, intent(in)           :: mycomm
       integer, intent(in)           :: lun
REVISION HISTORY:
   27Jul07 - R. Loy <[email protected]>  initial version



next up previous contents
Next: 5 The General Grid Up: 1 Basic API's and Previous: 3 Global Segment Map   Contents
[email protected]