next up previous contents
Next: 11 Matrix Vector Multiplication Up: 2 High Level API's Previous: 9 Rearranging Attribute Vectors   Contents

Subsections

10 Sprase Matrix Support

10.1 Module m_SparseMatrix - Sparse Matrix Object (Source File: m_SparseMatrix.F90)

The SparseMatrix data type is MCT's object for storing sparse matrices. In MCT, intergrid interpolation is implemented as a sparse matrix-vector multiplication, with the AttrVect type playing the roles of the input and output vectors. The interpolation matrices tend to be extremely sparse. For ${\bf x} \in \Re^{N_x}$, and ${\bf y} \in \Re^{N_y}$, the interpolation matrix M used to effect ${\bf y} = {\bf M} {\bf x}$ will typically have ${\cal O}({N_y})$ non-zero elements. For that reason, the SparseMatrix type stores only information about non-zero matrix elements, along with the number of rows and columns in the full matrix. The nonzero matrix elements are stored in AttrVect form (see the module m_AttrVect for more details), and the set of attributes are listed below:


Attribute Name Significance Type
grow Global Row Index INTEGER
gcol Global Column Index INTEGER
lrow Local Row Index INTEGER
lcol Local Column Index INTEGER
weight Matrix Element ${M_{ij}}$ REAL

The provision of both local and global column and row indices is made because this datatype can be used in either shared-memory or distributed-memory parallel matrix-vector products.

This module contains the definition of the SparseMatrix type, creation and destruction methods, a variety of accessor methods, routines for testing the suitability of the matrix for interpolation (i.e. the sum of each row is either zero or unity), and methods for sorting and permuting matrix entries.

For better performance of the Matrix-Vector multiply on vector architectures, the SparseMatrix object also contains arrays for holding the sparse matrix data in a more vector-friendly form.


INTERFACE:

 
  module m_SparseMatrix
USES:
       use m_realkinds, only : FP
       use m_AttrVect, only : AttrVect
 
 
       private   ! except
PUBLIC TYPES:
 
       public :: SparseMatrix      ! The class data structure
 
       Type SparseMatrix
 #ifdef SEQUENCE
      sequence
 #endif
      integer :: nrows
 	 integer :: ncols
 	 type(AttrVect) :: data
          logical :: vecinit       ! additional data for the vectorized sMat
          integer,dimension(:),pointer :: row_s, row_e
          integer, dimension(:,:), pointer :: tcol
          real(FP), dimension(:,:), pointer :: twgt
          integer :: row_max, row_min
          integer :: tbl_end
       End Type SparseMatrix
PUBLIC MEMBER FUNCTIONS:
 
       public :: init              ! Create a SparseMatrix
       public :: vecinit           ! Initialize the vector parts
       public :: clean             ! Destroy a SparseMatrix
       public :: lsize             ! Local number of elements
       public :: indexIA           ! Index integer attribute
       public :: indexRA           ! Index real attribute
       public :: nRows             ! Total number of rows
       public :: nCols             ! Total number of columns
 
       public :: exportGlobalRowIndices    ! Return global row indices 
                                           ! for matrix elements
       public :: exportGlobalColumnIndices ! Return global column indices 
                                           ! for matrix elements
       public :: exportLocalRowIndices     ! Return local row indices 
                                           ! for matrix elements
       public :: exportLocalColumnIndices  ! Return local column indices 
                                           ! for matrix elements
       public :: exportMatrixElements      ! Return matrix elements
 
       public :: importGlobalRowIndices    ! Set global row indices 
                                           ! using 
       public :: importGlobalColumnIndices ! Return global column indices 
                                           ! for matrix elements
       public :: importLocalRowIndices     ! Return local row indices 
                                           ! for matrix elements
       public :: importLocalColumnIndices  ! Return local column indices 
                                           ! for matrix elements
       public :: importMatrixElements      ! Return matrix elements
       public :: Copy                      ! Copy a SparseMatrix
 
       public :: GlobalNumElements ! Total number of nonzero elements
       public :: ComputeSparsity   ! Fraction of matrix that is nonzero
       public :: local_row_range   ! Local (on-process) row range
       public :: global_row_range  ! Local (on-process) row range
       public :: local_col_range   ! Local (on-process) column range
       public :: global_col_range  ! Local (on-process) column range
       public :: CheckBounds       ! Check row and column values
                                   ! for out-of-bounds values
       public :: row_sum           ! Return SparseMatrix row sums
       public :: row_sum_check     ! Check SparseMatrix row sums against
                                   ! input "valid" values
       public :: Sort              ! Sort matrix entries to generate an
                                   ! index permutation (to be used by
                                   ! Permute()
       public :: Permute           ! Permute matrix entries using index
                                   ! permutation gernerated by Sort()
       public :: SortPermute       ! Sort/Permute matrix entries
 
     interface init  ; module procedure init_  ; end interface
     interface vecinit  ; module procedure vecinit_  ; end interface
     interface clean ; module procedure clean_ ; end interface
     interface lsize ; module procedure lsize_ ; end interface
     interface indexIA ; module procedure indexIA_ ; end interface
     interface indexRA ; module procedure indexRA_ ; end interface
     interface nRows ; module procedure nRows_ ; end interface
     interface nCols ; module procedure nCols_ ; end interface
 
     interface exportGlobalRowIndices ; module procedure &
 	 exportGlobalRowIndices_ 
     end interface
 
     interface exportGlobalColumnIndices ; module procedure &
 	 exportGlobalColumnIndices_ 
     end interface
 
     interface exportLocalRowIndices ; module procedure &
 	 exportLocalRowIndices_ 
     end interface
 
     interface exportLocalColumnIndices ; module procedure &
 	 exportLocalColumnIndices_ 
     end interface
 
     interface exportMatrixElements ; module procedure &
 	 exportMatrixElementsSP_, &
 	 exportMatrixElementsDP_
     end interface
 
     interface importGlobalRowIndices ; module procedure &
 	 importGlobalRowIndices_ 
     end interface
 
     interface importGlobalColumnIndices ; module procedure &
 	 importGlobalColumnIndices_ 
     end interface
 
     interface importLocalRowIndices ; module procedure &
 	 importLocalRowIndices_ 
     end interface
 
     interface importLocalColumnIndices ; module procedure &
 	 importLocalColumnIndices_ 
     end interface
 
     interface importMatrixElements ; module procedure &
 	 importMatrixElementsSP_, & 
 	 importMatrixElementsDP_
     end interface
 
     interface Copy ; module procedure Copy_ ; end interface
 
     interface GlobalNumElements ; module procedure &
 	 GlobalNumElements_ 
     end interface
 
     interface ComputeSparsity ; module procedure &
 	 ComputeSparsitySP_,  &
 	 ComputeSparsityDP_ 
     end interface
 
     interface local_row_range ; module procedure &
 	 local_row_range_ 
     end interface
 
     interface global_row_range ; module procedure &
 	 global_row_range_ 
     end interface
 
     interface local_col_range ; module procedure &
 	 local_col_range_ 
     end interface
 
     interface global_col_range ; module procedure &
 	 global_col_range_ 
     end interface
 
     interface CheckBounds; module procedure &
 	 CheckBounds_ 
     end interface
 
     interface row_sum ; module procedure &
 	 row_sumSP_, &
 	 row_sumDP_
     end interface
 
     interface row_sum_check ; module procedure &
 	 row_sum_checkSP_, & 
 	 row_sum_checkDP_
     end interface
 
     interface Sort ; module procedure Sort_ ; end interface
     interface Permute ; module procedure Permute_ ; end interface
     interface SortPermute ; module procedure SortPermute_ ; end interface
REVISION HISTORY:
   19Sep00 - J.W. Larson <[email protected]> - initial prototype
   15Jan01 - J.W. Larson <[email protected]> - added numerous APIs
   25Feb01 - J.W. Larson <[email protected]> - changed from row/column
             attributes to global and local row and column attributes
   23Apr01 - J.W. Larson <[email protected]> - added number of rows
             and columns to the SparseMatrix type.  This means the
             SparseMatrix is no longer a straight AttrVect type.  This
             also made necessary the addition of lsize(), indexIA(),
             and indexRA().
   29Oct03 - R. Jacob <[email protected]> - extend the SparseMatrix type
             to include mods from Fujitsu for a vector-friendly MatVecMul

10.1.1 init_ - Initialize an Empty SparseMatrix

This routine creates the storage space for the entries of a SparseMatrix, and sets the number of rows and columns in it. The input INTEGER arguments nrows and ncols specify the number of rows and columns respectively. The optional input argument lsize specifies the number of nonzero entries in the SparseMatrix. The initialized SparseMatrix is returned in the output argument sMat.

N.B.: This routine is allocating dynamical memory in the form of a SparseMatrix. The user must deallocate this space when the SparseMatrix is no longer needed by invoking the routine clean_().


INTERFACE:

 
  subroutine init_(sMat, nrows, ncols, lsize)
USES:
       use m_AttrVect, only : AttrVect_init => init
       use m_die
 
       implicit none
INPUT PARAMETERS:
 
       integer,            intent(in)   :: nrows
       integer,            intent(in)   :: ncols
       integer, optional,  intent(in)   :: lsize
OUTPUT PARAMETERS:
 
       type(SparseMatrix), intent(out)  :: sMat
REVISION HISTORY:
   19Sep00 - Jay Larson <[email protected]> - initial prototype
   23Apr01 - Jay Larson <[email protected]> - added arguments
             nrows and ncols--number of rows and columns in the
             SparseMatrix

10.1.2 vecinit_ - Initialize vector parts of a SparseMatrix

This routine creates the storage space for and intializes the vector parts of a SparseMatrix.

N.B.: This routine assumes the locally indexed parts of a SparseMatrix have been initialized. This is accomplished by either importing the values directly with importLocalRowIndices and importLocalColIndices or by importing the Global Row and Col Indices and making two calls to GlobalToLocalMatrix.

N.B.: The vector portion can use a large amount of memory so it is highly recommended that this routine only be called on a SparseMatrix that has been scattered or otherwise sized locally.


INTERFACE:

 
  subroutine vecinit_(sMat)
USES:
       use m_die
       use m_stdio
 
       implicit none
INPUT/OUTPUT PARAMETERS:
 
       type(SparseMatrix), intent(inout)  :: sMat
REVISION HISTORY:
   27Oct03 - R. Jacob <[email protected]> - initial version
             using code provided by Yoshi et. al.

10.1.3 clean_ - Destroy a SparseMatrix.

This routine deallocates dynamical memory held by the input SparseMatrix argument sMat. It also sets the number of rows and columns in the SparseMatrix to zero.


INTERFACE:

 
     subroutine clean_(sMat,stat)
USES:
       use m_AttrVect,only : AttrVect_clean => clean
       use m_die
 
       implicit none
 
   !INPUT/OUTPTU PARAMETERS:
 
       type(SparseMatrix), intent(inout) :: sMat
OUTPUT PARAMETERS:
 
       integer, optional,  intent(out)   :: stat
REVISION HISTORY:
   19Sep00 - J.W. Larson <[email protected]> - initial prototype
   23Apr00 - J.W. Larson <[email protected]> - added changes to
             accomodate clearing nrows and ncols.
   01Mar02 - E.T. Ong <[email protected]> Added stat argument.
   03Oct03 - R. Jacob <[email protected]> - clean vector parts

10.1.4 lsize_ - Local Number Non-zero Elements

This INTEGER function reports on-processor storage of the number of nonzero elements in the input SparseMatrix argument sMat.


INTERFACE:

 
     integer function lsize_(sMat)
USES:
       use m_AttrVect,only : AttrVect_lsize => lsize
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in) :: sMat
REVISION HISTORY:
   23Apr00 - J.W. Larson <[email protected]> - initial version.

10.1.5 GlobalNumElements_ - Global Number of Non-zero Elements

This routine computes the number of nonzero elements in a distributed SparseMatrix variable sMat. The input SparseMatrix argument sMat is examined on each process to determine the number of nonzero elements it holds, and this value is summed across the communicator associated with the input INTEGER handle comm, with the total returned on each process on the communicator.


INTERFACE:

 
  integer function GlobalNumElements_(sMat, comm)
USES:
       use m_die
       use m_mpif90
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in)  :: sMat
       integer, optional,  intent(in)  :: comm
REVISION HISTORY:
   24Apr01 - Jay Larson <[email protected]> - New routine.

10.1.6 indexIA_ - Index an Integer Attribute

This INTEGER function reports the row index for a given INTEGER attribute of the input SparseMatrix argument sMat. The attribute requested is represented by the input CHARACTER variable attribute. The list of integer attributes one can request is defined in the description block of the header of this module (m_SparseMatrix).

Here is how indexIA_ provides access to integer attribute data in a SparseMatrix variable sMat. Suppose we wish to access global row information. This attribute has associated with it the string tag grow. The corresponding index returned (igrow) is determined by invoking indexIA_:

   igrow = indexIA_(sMat, 'grow')

Access to the global row index data in sMat is thus obtained by referencing sMat%data%iAttr(igrow,:).


INTERFACE:

 
     integer function indexIA_(sMat, item, perrWith, dieWith)
USES:
       use m_String, only : String
       use m_String, only : String_init => init
       use m_String, only : String_clean => clean
       use m_String, only : String_ToChar => ToChar
 
       use m_TraceBack, only : GenTraceBackString
 
       use m_AttrVect,only : AttrVect_indexIA => indexIA
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix),         intent(in) :: sMat
       character(len=*),           intent(in) :: item
       character(len=*), optional, intent(in) :: perrWith
       character(len=*), optional, intent(in) :: dieWith
REVISION HISTORY:
         23Apr00 - J.W. Larson <[email protected]> - initial version.

10.1.7 indexRA_ - Index a Real Attribute

This INTEGER function reports the row index for a given REAL attribute of the input SparseMatrix argument sMat. The attribute requested is represented by the input CHARACTER variable attribute. The list of real attributes one can request is defined in the description block of the header of this module (m_SparseMatrix).

Here is how indexRA_ provides access to integer attribute data in a SparseMatrix variable sMat. Suppose we wish to access matrix element values. This attribute has associated with it the string tag weight. The corresponding index returned (iweight) is determined by invoking indexRA_:

   iweight = indexRA_(sMat, 'weight')

Access to the matrix element data in sMat is thus obtained by referencing sMat%data%rAttr(iweight,:).


INTERFACE:

 
     integer function indexRA_(sMat, item, perrWith, dieWith)
USES:
       use m_String, only : String
       use m_String, only : String_init => init
       use m_String, only : String_clean => clean
       use m_String, only : String_ToChar => ToChar
 
       use m_TraceBack, only : GenTraceBackString
 
       use m_AttrVect,only : AttrVect_indexRA => indexRA
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix),         intent(in) :: sMat
       character(len=*),           intent(in) :: item
       character(len=*), optional, intent(in) :: perrWith
       character(len=*), optional, intent(in) :: dieWith
REVISION HISTORY:
   24Apr00 - J.W. Larson <[email protected]> - initial version.

10.1.8 nRows_ - Return the Number of Rows

This routine returns the total number of rows in the input SparseMatrix argument sMat. This number of rows is a constant, and not dependent on the decomposition of the SparseMatrix.


INTERFACE:

 
     integer function nRows_(sMat)
USES:
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in) :: sMat
REVISION HISTORY:
   19Apr01 - J.W. Larson <[email protected]> - initial prototype

10.1.9 nCols_ - Return the Number of Columns

This routine returns the total number of columns in the input SparseMatrix argument sMat. This number of columns is a constant, and not dependent on the decomposition of the SparseMatrix.


INTERFACE:

 
     integer function nCols_(sMat)
USES:
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in) :: sMat
REVISION HISTORY:
   19Apr01 - J.W. Larson <[email protected]> - initial prototype

10.1.10 exportGlobalRowIndices_ - Return Global Row Indices

This routine extracts from the input SparseMatrix argument sMat its global row indices, and returns them in the INTEGER output array GlobalRows, and its length in the output INTEGER argument length.

N.B.: The flexibility of this routine regarding the pointer association status of the output argument GlobalRows means the user must invoke this routine with care. If the user wishes this routine to fill a pre-allocated array, then obviously this array must be allocated prior to calling this routine. If the user wishes that the routine create the output argument array GlobalRows, then the user must ensure this pointer is not allocated (i.e. the user must nullify this pointer) at the time this routine is invoked.

N.B.: If the user has relied on this routine to allocate memory associated with the pointer GlobalRows, then the user is responsible for deallocating this array once it is no longer needed. Failure to do so will result in a memory leak.


INTERFACE:

 
  subroutine exportGlobalRowIndices_(sMat, GlobalRows, length)
USES:
       use m_die 
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_exportIAttr => exportIAttr
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix),     intent(in)  :: sMat
OUTPUT PARAMETERS:
 
       integer,  dimension(:), pointer     :: GlobalRows
       integer,  optional,     intent(out) :: length
REVISION HISTORY:
    7May02 - J.W. Larson <[email protected]> - initial version.

10.1.11 exportGlobalColumnIndices_ - Return Global Column Indices

This routine extracts from the input SparseMatrix argument sMat its global column indices, and returns them in the INTEGER output array GlobalColumns, and its length in the output INTEGER argument length.

N.B.: The flexibility of this routine regarding the pointer association status of the output argument GlobalColumns means the user must invoke this routine with care. If the user wishes this routine to fill a pre-allocated array, then obviously this array must be allocated prior to calling this routine. If the user wishes that the routine create the output argument array GlobalColumns, then the user must ensure this pointer is not allocated (i.e. the user must nullify this pointer) at the time this routine is invoked.

N.B.: If the user has relied on this routine to allocate memory associated with the pointer GlobalColumns, then the user is responsible for deallocating this array once it is no longer needed. Failure to do so will result in a memory leak.


INTERFACE:

 
  subroutine exportGlobalColumnIndices_(sMat, GlobalColumns, length)
USES:
       use m_die 
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_exportIAttr => exportIAttr
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix),     intent(in)  :: sMat
OUTPUT PARAMETERS:
 
       integer,  dimension(:), pointer     :: GlobalColumns
       integer,  optional,     intent(out) :: length
REVISION HISTORY:
    7May02 - J.W. Larson <[email protected]> - initial version.

10.1.12 exportLocalRowIndices_ - Return Local Row Indices

This routine extracts from the input SparseMatrix argument sMat its local row indices, and returns them in the INTEGER output array LocalRows, and its length in the output INTEGER argument length.

N.B.: The flexibility of this routine regarding the pointer association status of the output argument LocalRows means the user must invoke this routine with care. If the user wishes this routine to fill a pre-allocated array, then obviously this array must be allocated prior to calling this routine. If the user wishes that the routine create the output argument array LocalRows, then the user must ensure this pointer is not allocated (i.e. the user must nullify this pointer) at the time this routine is invoked.

N.B.: If the user has relied on this routine to allocate memory associated with the pointer LocalRows, then the user is responsible for deallocating this array once it is no longer needed. Failure to do so will result in a memory leak.


INTERFACE:

 
  subroutine exportLocalRowIndices_(sMat, LocalRows, length)
USES:
       use m_die 
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_exportIAttr => exportIAttr
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix),     intent(in)  :: sMat
OUTPUT PARAMETERS:
 
       integer,  dimension(:), pointer     :: LocalRows
       integer,  optional,     intent(out) :: length
REVISION HISTORY:
    7May02 - J.W. Larson <[email protected]> - initial version.

10.1.13 exportLocalColumnIndices_ - Return Local Column Indices

This routine extracts from the input SparseMatrix argument sMat its local column indices, and returns them in the INTEGER output array LocalColumns, and its length in the output INTEGER argument length.

N.B.: The flexibility of this routine regarding the pointer association status of the output argument LocalColumns means the user must invoke this routine with care. If the user wishes this routine to fill a pre-allocated array, then obviously this array must be allocated prior to calling this routine. If the user wishes that the routine create the output argument array LocalColumns, then the user must ensure this pointer is not allocated (i.e. the user must nullify this pointer) at the time this routine is invoked.

N.B.: If the user has relied on this routine to allocate memory associated with the pointer LocalColumns, then the user is responsible for deallocating this array once it is no longer needed. Failure to do so will result in a memory leak.


INTERFACE:

 
  subroutine exportLocalColumnIndices_(sMat, LocalColumns, length)
USES:
       use m_die 
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_exportIAttr => exportIAttr
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix),     intent(in)  :: sMat
OUTPUT PARAMETERS:
 
       integer,  dimension(:), pointer     :: LocalColumns
       integer,  optional,     intent(out) :: length
REVISION HISTORY:
    7May02 - J.W. Larson <[email protected]> - initial version.

10.1.14 exportMatrixElementsSP_ - Return Matrix Elements as Array

This routine extracts the matrix elements from the input SparseMatrix argument sMat, and returns them in the REAL output array MatrixElements, and its length in the output INTEGER argument length.

N.B.: The flexibility of this routine regarding the pointer association status of the output argument MatrixElements means the user must invoke this routine with care. If the user wishes this routine to fill a pre-allocated array, then obviously this array must be allocated prior to calling this routine. If the user wishes that the routine create the output argument array MatrixElements, then the user must ensure this pointer is not allocated (i.e. the user must nullify this pointer) at the time this routine is invoked.

N.B.: If the user has relied on this routine to allocate memory associated with the pointer MatrixElements, then the user is responsible for deallocating this array once it is no longer needed. Failure to do so will result in a memory leak.

The native precision version is described here. A double precision version is also available.


INTERFACE:

 
  subroutine exportMatrixelementsSP_(sMat, MatrixElements, length)
USES:
       use m_die 
       use m_stdio
       use m_realkinds, only : SP
 
       use m_AttrVect,      only : AttrVect_exportRAttr => exportRAttr
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix),     intent(in)  :: sMat
OUTPUT PARAMETERS:
 
       real(SP),  dimension(:),    pointer     :: MatrixElements
       integer,   optional,        intent(out) :: length
REVISION HISTORY:
    7May02 - J.W. Larson <[email protected]> - initial version.
    6Jan04 - R. Jacob <[email protected]> - SP and DP versions

10.1.15 importGlobalRowIndices_ - Set Global Row Indices of Elements

This routine imports global row index data into the SparseMatrix argument sMat. The user provides the index data in the input INTEGER vector inVect. The input INTEGER argument lsize is used as a consistencey check to ensure the user is sufficient space in the SparseMatrix to store the data.


INTERFACE:

 
  subroutine importGlobalRowIndices_(sMat, inVect, lsize)
USES:
       use m_die
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_importIAttr => importIAttr
 
       implicit none
INPUT PARAMETERS:
 
       integer,  dimension(:), pointer       :: inVect
       integer,                intent(in)    :: lsize
INPUT/OUTPUT PARAMETERS:
 
       type(SparseMatrix),     intent(inout) :: sMat
REVISION HISTORY:
    7May02 - J.W. Larson <[email protected]> - initial prototype.

10.1.16 importGlobalColumnIndices_ - Set Global Column Indices of Elements

This routine imports global column index data into the SparseMatrix argument sMat. The user provides the index data in the input INTEGER vector inVect. The input INTEGER argument lsize is used as a consistencey check to ensure the user is sufficient space in the SparseMatrix to store the data.


INTERFACE:

 
  subroutine importGlobalColumnIndices_(sMat, inVect, lsize)
USES:
       use m_die
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_importIAttr => importIAttr
 
       implicit none
INPUT PARAMETERS:
 
       integer,  dimension(:), pointer       :: inVect
       integer,                intent(in)    :: lsize
INPUT/OUTPUT PARAMETERS:
 
       type(SparseMatrix),     intent(inout) :: sMat
REVISION HISTORY:
    7May02 - J.W. Larson <[email protected]> - initial prototype.

10.1.17 importLocalRowIndices_ - Set Local Row Indices of Elements

This routine imports local row index data into the SparseMatrix argument sMat. The user provides the index data in the input INTEGER vector inVect. The input INTEGER argument lsize is used as a consistencey check to ensure the user is sufficient space in the SparseMatrix to store the data.


INTERFACE:

 
  subroutine importLocalRowIndices_(sMat, inVect, lsize)
USES:
       use m_die
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_importIAttr => importIAttr
 
       implicit none
INPUT PARAMETERS:
 
       integer,  dimension(:), pointer       :: inVect
       integer,                intent(in)    :: lsize
INPUT/OUTPUT PARAMETERS:
 
       type(SparseMatrix),     intent(inout) :: sMat
REVISION HISTORY:
    7May02 - J.W. Larson <[email protected]> - initial prototype.

10.1.18 importLocalColumnIndices_ - Set Local Column Indices of Elements

This routine imports local column index data into the SparseMatrix argument sMat. The user provides the index data in the input INTEGER vector inVect. The input INTEGER argument lsize is used as a consistencey check to ensure the user is sufficient space in the SparseMatrix to store the data.


INTERFACE:

 
  subroutine importLocalColumnIndices_(sMat, inVect, lsize)
USES:
       use m_die
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_importIAttr => importIAttr
 
       implicit none
INPUT PARAMETERS:
 
       integer,  dimension(:), pointer       :: inVect
       integer,                intent(in)    :: lsize
INPUT/OUTPUT PARAMETERS:
 
       type(SparseMatrix),     intent(inout) :: sMat
REVISION HISTORY:
    7May02 - J.W. Larson <[email protected]> - initial prototype.

10.1.19 importMatrixElementsSP_ - Import Non-zero Matrix Elements

This routine imports matrix elements index data into the SparseMatrix argument sMat. The user provides the index data in the input REAL vector inVect. The input INTEGER argument lsize is used as a consistencey check to ensure the user is sufficient space in the SparseMatrix to store the data.


INTERFACE:

 
  subroutine importMatrixElementsSP_(sMat, inVect, lsize)
USES:
       use m_die
       use m_stdio
       use m_realkinds, only : SP
 
       use m_AttrVect,      only : AttrVect_importRAttr => importRAttr
 
       implicit none
INPUT PARAMETERS:
 
       real(SP),  dimension(:),    pointer       :: inVect
       integer,                intent(in)    :: lsize
INPUT/OUTPUT PARAMETERS:
 
       type(SparseMatrix),     intent(inout) :: sMat
REVISION HISTORY:
    7May02 - J.W. Larson <[email protected]> - initial prototype.
    6Jan04 - R. Jacob <[email protected]> - Make SP and DP versions.

10.1.20 Copy_ - Create a Copy of an Input SparseMatrix

This routine creates a copy of the input SparseMatrix argument sMat, returning it as the output SparseMatrix argument sMatCopy.

N.B.: The output argument sMatCopy represents allocated memory the user must deallocate when it is no longer needed. The MCT routine to use for this purpose is clean() from this module.


INTERFACE:

 
  subroutine Copy_(sMat, sMatCopy)
USES:
       use m_die
       use m_stdio
 
       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
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in) :: sMat
OUTPUT PARAMETERS:
 
       type(SparseMatrix), intent(out) :: sMatCopy
REVISION HISTORY:
   27Sep02 - J.W. Larson <[email protected]> - initial prototype.

10.1.21 local_row_range_ - Local Row Extent of Non-zero Elements

This routine examines the input distributed SparseMatrix variable sMat, and returns the range of local row values having nonzero elements. The first local row with nonzero elements is returned in the INTEGER argument start_row, the last row in end_row.


INTERFACE:

 
  subroutine local_row_range_(sMat, start_row, end_row)
USES:
       use m_die
 
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_indexIA => indexIA
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in)  :: sMat
OUTPUT PARAMETERS:
 
       integer,            intent(out) :: start_row
       integer,            intent(out) :: end_row
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - API specification.
   25Feb01 - Jay Larson <[email protected]> - Initial prototype.
   23Apr01 - Jay Larson <[email protected]> - Modified to accomodate
             changes to the SparseMatrix type.

10.1.22 global_row_range_ - Global Row Extent of Non-zero Elements

This routine examines the input distributed SparseMatrix variable sMat, and returns the range of global row values having nonzero elements. The first local row with nonzero elements is returned in the INTEGER argument start_row, the last row in end_row.


INTERFACE:

 
  subroutine global_row_range_(sMat, comm, start_row, end_row)
USES:
       use m_die
 
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_indexIA => indexIA
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in)  :: sMat
       integer,            intent(in)  :: comm
OUTPUT PARAMETERS:
 
       integer,            intent(out) :: start_row
       integer,            intent(out) :: end_row
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - API specification.
   25Feb01 - Jay Larson <[email protected]> - Initial prototype.
   23Apr01 - Jay Larson <[email protected]> - Modified to accomodate
             changes to the SparseMatrix type.

10.1.23 local_col_range_ - Local Column Extent of Non-zero Elements

This routine examines the input distributed SparseMatrix variable sMat, and returns the range of local column values having nonzero elements. The first local column with nonzero elements is returned in the INTEGER argument start_col, the last column in end_col.


INTERFACE:

 
  subroutine local_col_range_(sMat, start_col, end_col)
USES:
       use m_die
 
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_indexIA => indexIA
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in)  :: sMat
OUTPUT PARAMETERS:
 
       integer,            intent(out) :: start_col
       integer,            intent(out) :: end_col
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - API specification.
   25Feb01 - Jay Larson <[email protected]> - Initial prototype.
   23Apr01 - Jay Larson <[email protected]> - Modified to accomodate
             changes to the SparseMatrix type.

10.1.24 global_col_range_ - Global Column Extent of Non-zero Elements

This routine examines the input distributed SparseMatrix variable sMat, and returns the range of global column values having nonzero elements. The first global column with nonzero elements is returned in the INTEGER argument start_col, the last column in end_col.


INTERFACE:

 
  subroutine global_col_range_(sMat, comm, start_col, end_col)
USES:
       use m_die
 
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_indexIA => indexIA
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in)  :: sMat
       integer,            intent(in)  :: comm
OUTPUT PARAMETERS:
 
       integer,            intent(out) :: start_col
       integer,            intent(out) :: end_col
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - API specification.
   25Feb01 - Jay Larson <[email protected]> - Initial prototype.
   23Apr01 - Jay Larson <[email protected]> - Modified to accomodate
             changes to the SparseMatrix type.

10.1.25 ComputeSparsitySP_ - Compute Matrix Sparsity

This routine computes the sparsity of a consolidated (all on one process) or distributed SparseMatrix. The input SparseMatrix argument sMat is examined to determine the number of nonzero elements it holds, and this value is divided by the product of the number of rows and columns in sMat. If the optional input argument comm is given, then the distributed elements are counted and the sparsity computed accordingly, and the resulting value of sparsity is returned to all processes.

Given the inherent problems with multiplying and dividing large integers, the work in this routine is performed using floating point arithmetic on the logarithms of the number of rows, columns, and nonzero elements.


INTERFACE:

 
  subroutine ComputeSparsitySP_(sMat, sparsity, comm)
USES:
       use m_die
       use m_mpif90
       use m_realkinds, only : SP, FP
 
       use m_AttrVect, only : AttrVect_lsize => lsize
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in)  :: sMat
       integer, optional,  intent(in)  :: comm
OUTPUT PARAMETERS:
 
       real(SP),           intent(out) :: sparsity
REVISION HISTORY:
   23Apr01 - Jay Larson <[email protected]> - New routine.

10.1.26 CheckBounds_ - Check for Out-of-Bounds Row/Column Values

This routine examines the input distributed SparseMatrix variable sMat, and examines the global row and column index for each element, comparing them with the known maximum values for each (as returned by the routines nRows_() and nCols_(), respectively). If global row or column entries are non-positive, or greater than the defined maximum values, this routine stops execution with an error message. If no out-of-bounds values are detected, the output INTEGER status ierror is set to zero.


INTERFACE:

 
  subroutine CheckBounds_(sMat, ierror)
USES:
       use m_die
 
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_indexIA => indexIA
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in)  :: sMat
OUTPUT PARAMETERS:
 
       integer,            intent(out) :: ierror
REVISION HISTORY:
   24Apr01 - Jay Larson <[email protected]> - Initial prototype.

10.1.27 row_sumSP_ - Sum Elements in Each Row

Given an input SparseMatrix argument sMat, row_sum_() returns the number of the rows num_rows in the sparse matrix and the sum of the elements in each row in the array sums. The input argument comm is the Fortran 90 MPI communicator handle used to determine the number of rows and perform the sums. The output arguments num_rows and sums are valid on all processes.

N.B.: This routine allocates an array sums. The user is responsible for deallocating this array when it is no longer needed. Failure to do so will cause a memory leak.


INTERFACE:

 
  subroutine row_sumSP_(sMat, num_rows, sums, comm)
USES:
       use m_die
       use m_mpif90
       use m_realkinds, only : SP, FP
 
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_indexIA => indexIA
       use m_AttrVect, only : AttrVect_indexRA => indexRA
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in)  :: sMat
       integer,            intent(in)  :: comm
OUTPUT PARAMETERS:
 
       integer,            intent(out) :: num_rows
       real(SP), dimension(:), pointer :: sums
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - API specification.
   25Jan01 - Jay Larson <[email protected]> - Prototype code.
   23Apr01 - Jay Larson <[email protected]> - Modified to accomodate
             changes to the SparseMatrix type.
   18May01 - R. Jacob <[email protected]> - Use MP_TYPE function
             to set type in the mpi_allreduce

10.1.28 row_sum_checkSP_ - Check Row Sums vs. Valid Values

The routine row_sum_check() sums the rows of the input distributed (across the communicator identified by comm) SparseMatrix variable sMat. It then compares these sums with the num_valid input "valid" values stored in the array valid_sums. If all of the sums are within the absolute tolerence specified by the input argument abs_tol of any of the valid values, the output LOGICAL flag valid is set to .TRUE. Otherwise, this flag is returned with value .FALSE.


INTERFACE:

 
  subroutine row_sum_checkSP_(sMat, comm, num_valid, valid_sums, abs_tol, valid)
USES:
       use m_die
       use m_realkinds, only : SP, FP
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix), intent(in)  :: sMat
       integer,            intent(in)  :: comm
       integer,            intent(in)  :: num_valid
       real(SP),           intent(in)  :: valid_sums(num_valid)
       real(SP),           intent(in)  :: abs_tol
OUTPUT PARAMETERS:
 
       logical,            intent(out) :: valid
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - API specification.
   25Feb01 - Jay Larson <[email protected]> - Prototype code.
   06Jan03 - R. Jacob <[email protected]> - create DP and SP versions

10.1.29 Sort_ - Generate Index Permutation

The subroutine Sort_() uses a list of sorting keys defined by the input List argument key_list, searches for the appropriate integer or real attributes referenced by the items in key_list ( that is, it identifies the appropriate entries in sMat%data%iList and sMat%data%rList), and then uses these keys to generate an index permutation perm that will put the nonzero matrix entries of stored in sMat%data in lexicographic order as defined by key_ist (the ordering in key_list being from left to right. The optional LOGICAL array input argument descend specifies whether or not to sort by each key in descending order or ascending order. Entries in descend that have value .TRUE. correspond to a sort by the corresponding key in descending order. If the argument descend is not present, the sort is performed for all keys in ascending order.


INTERFACE:

 
  subroutine Sort_(sMat, key_list, perm, descend)
USES:
       use m_die ,          only : die
       use m_stdio ,        only : stderr
 
       use m_List ,         only : List
 
       use m_AttrVect, only: AttrVect_Sort => Sort
 
       implicit none
INPUT PARAMETERS:
 
       type(SparseMatrix),              intent(in) :: sMat
       type(List),                      intent(in) :: key_list
       logical, dimension(:), optional, intent(in) :: descend
OUTPUT PARAMETERS:
 
       integer, dimension(:), pointer              :: perm
REVISION HISTORY:
   24Apr01 - J.W. Larson <[email protected]> - initial prototype

10.1.30 Permute_ - Permute Matrix Elements using Supplied Index Permutation

The subroutine Permute_() uses an input index permutation perm to re-order the entries of the SparseMatrix argument sMat. The index permutation perm is generated using the routine Sort_() (in this module).


INTERFACE:

 
  subroutine Permute_(sMat, perm)
USES:
       use m_die ,          only : die
       use m_stdio ,        only : stderr
 
       use m_AttrVect, only: AttrVect_Permute => Permute
 
       implicit none
INPUT PARAMETERS:
 
 
       integer, dimension(:), pointer               :: perm
INPUT/OUTPUT PARAMETERS:
 
       type(SparseMatrix),            intent(inout) :: sMat
REVISION HISTORY:
   24Apr01 - J.W. Larson <[email protected]> - initial prototype

10.1.31 SortPermute_ - Sort and Permute Matrix Elements

The subroutine SortPermute_() uses a list of sorting keys defined by the input List argument key_list, searches for the appropriate integer or real attributes referenced by the items in key_ist ( that is, it identifies the appropriate entries in sMat%data%iList and sMat%data%rList), and then uses these keys to generate an index permutation that will put the nonzero matrix entries of stored in sMat%data in lexicographic order as defined by key_list (the ordering in key_list being from left to right. The optional LOGICAL array input argument descend specifies whether or not to sort by each key in descending order or ascending order. Entries in descend that have value .TRUE. correspond to a sort by the corresponding key in descending order. If the argument descend is not present, the sort is performed for all keys in ascending order.

Once this index permutation is created, it is applied to re-order the entries of the SparseMatrix argument sMat accordingly.


INTERFACE:

 
  subroutine SortPermute_(sMat, key_list, descend)
USES:
       use m_die ,          only : die
       use m_stdio ,        only : stderr
 
       use m_List ,         only : List
 
       implicit none
INPUT PARAMETERS:
 
       type(List),                      intent(in)    :: key_list
       logical, dimension(:), optional, intent(in)    :: descend
INPUT/OUTPUT PARAMETERS:
 
       type(SparseMatrix),              intent(inout) :: sMat
REVISION HISTORY:
   24Apr01 - J.W. Larson <[email protected]> - initial prototype


10.2 Module m_SparseMatrixComms - sparse matrix communications methods. (Source File: m_SparseMatrixComms.F90)

The SparseMatrix datatype provides sparse matrix storage for the parallel matrix-vector multiplication ${\bf y} = {\bf M} {\bf x}$. This module provides communications services for the SparseMatrix type. These services include scattering matrix elements based on row or column decompositions, gathering of matrix elements to the root, and broadcasting from the root.

N.B.: These routines will not communicate the vector portion of a SparseMatrix, if it has been initialized. A WARNING will be issued in most cases. In general, do communication first, then call vecinit.


INTERFACE:

 
  module m_SparseMatrixComms
 
       private   ! except
PUBLIC MEMBER FUNCTIONS:
       public :: ScatterByColumn
       public :: ScatterByRow
       public :: Gather
       public :: Bcast
 
     interface ScatterByColumn ; module procedure &
          ScatterByColumnGSMap_
     end interface
 
     interface ScatterByRow ; module procedure &
          ScatterByRowGSMap_
     end interface
 
     interface Gather ; module procedure &
 	 GM_gather_, &
 	 GSM_gather_
     end interface
 
     interface Bcast ; module procedure Bcast_ ; end interface
REVISION HISTORY:
   13Apr01 - J.W. Larson <[email protected]> - initial prototype
             and API specifications.
   10May01 - J.W. Larson <[email protected]> - added GM_gather_
             and cleaned up prologues.

10.2.1 ScatterByColumnGSMap_ - Column-based scatter for SparseMatrix.

This routine scatters the input SparseMatrix argument GsMat (valid only on the root) to a distributed SparseMatrix variable LsMat across all the processes present on the communicator associated with the integer handle comm. The decomposition defining the scatter is supplied by the input GlobalSegMap argument columnGSMap. The optional output INTEGER flag stat signifies a successful (failed) operation if it is returned with value zero (nonzero).

N.B.: This routine returns an allocated SparseMatrix variable LsMat. The user must destroy this variable when it is no longer needed by invoking SparseMatrix_Clean().


INTERFACE:

 
  subroutine ScatterByColumnGSMap_(columnGSMap, GsMat, LsMat, root, comm, stat)
USES:
 
    use m_die, only : MP_perr_die,die
    use m_stdio
    use m_mpif90
 
    use m_List, only: List
    use m_List, only: List_init => init
    use m_List, only: List_clean => clean
 
    use m_GlobalSegMap, only : GlobalSegMap
    use m_GlobalSegMap, only : GlobalSegMap_clean => clean
 
    use m_SparseMatrix, only : SparseMatrix
    use m_SparseMatrix, only : SparseMatrix_nRows => nRows
    use m_SparseMatrix, only : SparseMatrix_nCols => nCols
    use m_SparseMatrix, only : SparseMatrix_SortPermute => SortPermute
 
    use m_SparseMatrixDecomp, only : SparseMatrixDecompByColumn => ByColumn
 
    use m_AttrVectComms, only : AttrVect_Scatter => scatter
 
    implicit none
INPUT PARAMETERS:
    type(GlobalSegMap), intent(in)    :: columnGSMap
    integer,            intent(in)    :: root
    integer,            intent(in)    :: comm
INPUT/OUTPUT PARAMETERS:
    type(SparseMatrix), intent(inout) :: GsMat
OUTPUT PARAMETERS:
    type(SparseMatrix), intent(out) :: LsMat
    integer, optional,  intent(out) :: stat
REVISION HISTORY:
   13Apr01 - J.W. Larson <[email protected]> - initial API spec.
   10May01 - J.W. Larson <[email protected]> - cleaned up prologue.
   13Jun01 - J.W. Larson <[email protected]> - Made status flag stat
             optional, and ititilaze it to zero if it is present.
   09Jul03 - E.T. Ong <[email protected]> - added sorting to distributed
             matrix elements

10.2.2 ScatterByRowGSMap_ -Row-based scatter for SparseMatrix.

This routine scatters the input SparseMatrix argument GsMat (valid only on the root) to a distributed SparseMatrix variable LsMat across all the processes present on the communicator associated with the integer handle comm. The decomposition defining the scatter is supplied by the input GlobalSegMap argument rowGSMap. The output integer flag stat signifies a successful (failed) operation if it is returned with value zero (nonzero).

N.B.: This routine returns an allocated SparseMatrix variable LsMat. The user must destroy this variable when it is no longer needed by invoking SparseMatrix_Clean().


INTERFACE:

 
  subroutine ScatterByRowGSMap_(rowGSMap, GsMat, LsMat, root, comm, stat)
USES:
    use m_die, only : MP_perr_die,die
    use m_stdio
    use m_mpif90
 
    use m_List, only: List
    use m_List, only: List_init => init
    use m_List, only: List_clean => clean
 
    use m_GlobalSegMap, only : GlobalSegMap
    use m_GlobalSegMap, only : GlobalSegMap_clean => clean
 
    use m_SparseMatrix, only : SparseMatrix
    use m_SparseMatrix, only : SparseMatrix_nRows => nRows
    use m_SparseMatrix, only : SparseMatrix_nCols => nCols
    use m_SparseMatrix, only : SparseMatrix_SortPermute => SortPermute
 
    use m_SparseMatrixDecomp, only : SparseMatrixDecompByRow => ByRow
 
    use m_AttrVectComms, only : AttrVect_Scatter => scatter
 
    implicit none
INPUT PARAMETERS:
    type(GlobalSegMap), intent(in)    :: rowGSMap
    integer,            intent(in)    :: root
    integer,            intent(in)    :: comm
INPUT/OUTPUT PARAMETERS:
    type(SparseMatrix), intent(inout) :: GsMat
OUTPUT PARAMETERS:
    type(SparseMatrix), intent(out) :: LsMat
    integer, optional,  intent(out) :: stat
REVISION HISTORY:
   13Apr01 - J.W. Larson <[email protected]> - initial API spec.
   26Apr01 - R.L. Jacob  <[email protected]> - fix use statement
             from SMDecomp so it points to ByRow
   13Jun01 - J.W. Larson <[email protected]> - Made status flag stat
             optional, and initialize it to zero if it is present.
   09Jul03 - E.T. Ong <[email protected]> - Added sorting to distributed
             matrix elements.

10.2.3 GM_gather_ - Gather a distributed SparseMatrix to the root.

This routine gathers the input distributed SparseMatrix argument LsMat to the SparseMatrix variable GsMat on the root. The decomposition defining the gather is supplied by the input GlobalMap argument GMap. The status flag stat has value zero (nonzero) if the operation has succeeded (failed).

N.B.: This routine returns an allocated SparseMatrix variable GsMat. The user must destroy this variable when it is no longer needed by invoking SparseMatrix_Clean().


INTERFACE:

 
  subroutine GM_gather_(LsMat, GsMat, GMap, root, comm, stat)
USES:
    use m_stdio
    use m_die, only : die
 
    use m_GlobalMap, only: GlobalMap
 
    use m_SparseMatrix, only: SparseMatrix
    use m_SparseMatrix, only: SparseMatrix_nRows => nRows
    use m_SparseMatrix, only: SparseMatrix_nCols => nCols
 
    use m_AttrVectComms, only : AttrVect_gather => gather
 
    implicit none
INPUT PARAMETERS:
    type(SparseMatrix), intent(in) :: LsMat
    type(GlobalMap),    intent(in) :: GMap
    integer,            intent(in) :: root
    integer,            intent(in) :: comm
OUTPUT PARAMETERS:
    type(SparseMatrix), intent(out) :: GsMat
    integer, optional,  intent(out) :: stat
REVISION HISTORY:
   13Apr01 - J.W. Larson <[email protected]> - initial API spec.
   10May01 - J.W. Larson <[email protected]> - initial routine and
             prologue
   13Jun01 - J.W. Larson <[email protected]> - Made status flag stat
             optional, and ititilaze it to zero if it is present.

10.2.4 GSM_gather_ - Gather a distributed SparseMatrix to the root.

This routine gathers the input distributed SparseMatrix argument LsMat to the SparseMatrix variable GsMat on the root. The decomposition defining the gather is supplied by the input GlobalSegMap argument GSMap. The status flag stat has value zero (nonzero) if the operation has succeeded (failed).

N.B.: This routine returns an allocated SparseMatrix variable GsMat. The user must destroy this variable when it is no longer needed by invoking SparseMatrix_Clean().


INTERFACE:

 
  subroutine GSM_gather_(LsMat, GsMat, GSMap, root, comm, stat)
USES:
    use m_stdio
    use m_die, only : die
 
    use m_GlobalSegMap, only: GlobalSegMap
 
    use m_SparseMatrix, only: SparseMatrix
    use m_SparseMatrix, only: SparseMatrix_nRows => nRows
    use m_SparseMatrix, only: SparseMatrix_nCols => nCols
 
    use m_AttrVectComms, only : AttrVect_gather => gather
 
    implicit none
INPUT PARAMETERS:
    type(SparseMatrix), intent(in) :: LsMat
    type(GlobalSegMap), intent(in) :: GSMap
    integer,            intent(in) :: root
    integer,            intent(in) :: comm
OUTPUT PARAMETERS:
    type(SparseMatrix), intent(out) :: GsMat
    integer, optional,  intent(out) :: stat
REVISION HISTORY:
   13Apr01 - J.W. Larson <[email protected]> - initial API spec.
   13Jun01 - J.W. Larson <[email protected]> - Made status flag stat
             optional, and ititilaze it to zero if it is present.

10.2.5 Bcast_ - Broadcast a SparseMatrix.

This routine broadcasts the SparseMatrix argument sMat from the root to all processes on the communicator associated with the communicator handle comm. The status flag stat has value zero if the operation has succeeded.

N.B.: This routine returns an allocated SparseMatrix variable sMat. The user must destroy this variable when it is no longer needed by invoking SparseMatrix_Clean().

N.B.: This routine will exit with an error if the vector portion of sMat has been initialized prior to broadcast.


INTERFACE:

 
  subroutine Bcast_(sMat, root, comm, stat)
USES:
 
    use m_die, only : MP_perr_die,die
    use m_stdio
    use m_mpif90
 
    use m_GlobalSegMap, only: GlobalSegMap
 
    use m_AttrVectComms, only : AttrVect_bcast => bcast
 
    use m_SparseMatrix, only: SparseMatrix
    use m_SparseMatrix, only: SparseMatrix_nRows => nRows
    use m_SparseMatrix, only: SparseMatrix_nCols => nCols
 
    implicit none
INPUT PARAMETERS:
    integer,            intent(in) :: root
    integer,            intent(in) :: comm
INPUT/OUTPUT PARAMETERS:
    type(SparseMatrix), intent(inout) :: sMat
OUTPUT PARAMETERS:
    integer, optional,  intent(out) :: stat
REVISION HISTORY:
   13Apr01 - J.W. Larson <[email protected]> - initial API spec/code
   13Jun01 - J.W. Larson <[email protected]> - Made status flag stat
             optional, and ititilaze it to zero if it is present.
   17Jul02 - J.W. Larson <[email protected]> - Bug fix--local 
             process ID myID was uninitialized.


10.3 Module m_SparseMatrixDecomp - Parallel sparse matrix decomposition. (Source File: m_SparseMatrixDecomp.F90)

The SparseMatrix datatype provides sparse matrix storage for the parallel matrix-vector multiplication ${\bf y} = {\bf M} {\bf x}$. This module provides services to create decompositions for the SparseMatrix. The matrix decompositions available are row and column decompositions. They are generated by invoking the appropriate routine in this module, and passing the corresponding vector decomposition. For a row (column) decomposition, one invokes the routine ByRow() (ByColumn()), passing the domain decomposition for the vector y (x).


INTERFACE:

 
  module m_SparseMatrixDecomp
 
       private   ! except
PUBLIC MEMBER FUNCTIONS:
       public :: ByColumn
       public :: ByRow
 
 
     interface ByColumn ; module procedure &
          ByColumnGSMap_
     end interface
 
     interface ByRow ; module procedure &
          ByRowGSMap_
     end interface
REVISION HISTORY:
   13Apr01 - J.W. Larson <[email protected]> - initial prototype
             and API specifications.
   03Aug01 - E. Ong <[email protected]> - in ByRowGSMap and ByColumnGSMap,
             call GlobalSegMap_init on non-root processes with actual 
             shaped arguments to satisfy Fortran 90 standard. See
             comments in ByRowGSMap/ByColumnGSMap.

10.3.1 ByColumnGSMap_ - Generate Row-based GlobalSegMap for SparseMatrix


INTERFACE:

 
  subroutine ByColumnGSMap_(xGSMap, sMat, sMGSMap, root, comm)
USES:
    use m_die,  only: MP_perr_die,die
 
    use m_List, only: List
    use m_List, only: List_init => init
    use m_List, only: List_clean => clean
 
    use m_AttrVect, only: AttrVect
    use m_AttrVect, only: AttrVect_init => init
    use m_AttrVect, only: AttrVect_zero => zero
    use m_AttrVect, only: AttrVect_lsize => lsize
    use m_AttrVect, only: AttrVect_indexIA => indexIA
    use m_AttrVect, only: AttrVect_copy => copy
    use m_AttrVect, only: AttrVect_clean => clean
    
    use m_AttrVectComms, only: AttrVect_scatter => scatter
    use m_AttrVectComms, only: AttrVect_gather => gather
 
    use m_GlobalMap, only : GlobalMap
    use m_GlobalMap, only : GlobalMap_init => init
    use m_GlobalMap, only : GlobalMap_clean => clean
 
    use m_GlobalSegMap, only: GlobalSegMap
    use m_GlobalSegMap, only: GlobalSegMap_init => init
    use m_GlobalSegMap, only: GlobalSegMap_peLocs => peLocs
    use m_GlobalSegMap, only: GlobalSegMap_comp_id => comp_id
 
    use m_SparseMatrix, only: SparseMatrix
    use m_SparseMatrix, only: SparseMatrix_lsize => lsize
    use m_SparseMatrix, only: SparseMatrix_SortPermute => SortPermute
 
    implicit none
INPUT PARAMETERS:
    type(GlobalSegMap), intent(in)    :: xGSMap
    integer,            intent(in)    :: root
    integer,            intent(in)    :: comm
INPUT/OUTPUT PARAMETERS:
    type(SparseMatrix), intent(inout) :: sMat
OUTPUT PARAMETERS:
    type(GlobalSegMap), intent(out) :: sMGSMap
DESCRIPTION:

This routine is invoked from all processes on the communicator comm to create from an input SparseMatrix sMat (valid only on the root process) and an input x-vector decomposition described by the GlobalSegMap argument xGSMap (valid at least on the root) to create an output GlobalSegMap decomposition of the matrix elements sMGSMap, which is valid on all processes on the communicator. This matrix GlobalSegMap describes the corresponding column decomposition of sMat.

N.B.: The argument sMat is returned sorted in lexicographic order by column and row.


REVISION HISTORY:

   13Apr01 - J.W. Larson <[email protected]> - initial API spec.
   26Apr01 - R.L. Jacob <[email protected]> - add use statements for
             GlobalSegMap_init and GSMap_peLocs.
             Add gsize argument required to GSMap_peLocs.
             Add underscore to ComputeSegments call so it matches
             the subroutine decleration.
             change attribute on starts,lengths, and pe_locs to
             pointer to match GSMap_init.
             add use m_die statement
   26Apr01 - J.W. Larson <[email protected]> - fixed major logic bug
             that had all processes executing some operations that 
             should only occur on the root.
   09Jul03 - E.T. Ong <[email protected]> - call pe_locs in parallel. 
             reduce the serial sort from gcol:grow to just gcol.

10.3.2 ByRowGSMap_ - Generate Row-based GlobalSegMap for SparseMatrix


INTERFACE:

 
  subroutine ByRowGSMap_(yGSMap, sMat, sMGSMap, root, comm)
USES:
 
    use m_die,  only: MP_perr_die,die
 
    use m_List, only: List
    use m_List, only: List_init => init
    use m_List, only: List_clean => clean
 
    use m_AttrVect, only: AttrVect
    use m_AttrVect, only: AttrVect_init => init
    use m_AttrVect, only: AttrVect_lsize => lsize
    use m_AttrVect, only: AttrVect_indexIA => indexIA
    use m_AttrVect, only: AttrVect_copy => copy
    use m_AttrVect, only: AttrVect_clean => clean
    use m_AttrVect, only: AttrVect_zero => zero
    
    use m_AttrVectComms, only: AttrVect_scatter => scatter
    use m_AttrVectComms, only: AttrVect_gather => gather
 
    use m_GlobalMap, only : GlobalMap
    use m_GlobalMap, only : GlobalMap_init => init
    use m_GlobalMap, only : GlobalMap_clean => clean
 
    use m_GlobalSegMap, only: GlobalSegMap
    use m_GlobalSegMap, only: GlobalSegMap_init => init
    use m_GlobalSegMap, only: GlobalSegMap_peLocs => peLocs
    use m_GlobalSegMap, only: GlobalSegMap_comp_id => comp_id
 
    use m_SparseMatrix, only: SparseMatrix
    use m_SparseMatrix, only: SparseMatrix_lsize => lsize
    use m_SparseMatrix, only: SparseMatrix_SortPermute => SortPermute
 
    implicit none
INPUT PARAMETERS:
    type(GlobalSegMap), intent(in)    :: yGSMap
    integer,            intent(in)    :: root
    integer,            intent(in)    :: comm
INPUT/OUTPUT PARAMETERS:
    type(SparseMatrix), intent(inout) :: sMat
OUTPUT PARAMETERS:
    type(GlobalSegMap), intent(out) :: sMGSMap
DESCRIPTION:

This routine is invoked from all processes on the communicator comm to create from an input SparseMatrix sMat (valid only on the root process) and an input y-vector decomposition described by the GlobalSegMap argument yGSMap (valid at least on the root) to create an output GlobalSegMap decomposition of the matrix elements sMGSMap, which is valid on all processes on the communicator. This matrix GlobalSegMap describes the corresponding row decomposition of sMat.

N.B.: The argument sMat is returned sorted in lexicographic order by row and column.


REVISION HISTORY:

   13Apr01 - J.W. Larson <[email protected]> - initial API spec.
   26Apr01 - R.L. Jacob <[email protected]> - add use statements for
             GlobalSegMap_init and GSMap_peLocs.
             Add gsize argument required to GSMap_peLocs.
             Add underscore to ComputeSegments call so it matches
             the subroutine decleration.
             change attribute on starts,lengths, and pe_locs to
              pointer to match GSMap_init.
   26Apr01 - J.W. Larson <[email protected]> - fixed major logic bug
             that had all processes executing some operations that 
             should only occur on the root.
   09Jun03 - E.T. Ong <[email protected]> - call peLocs in parallel.
             reduce the serial sort from grow:gcol to just grow.

10.3.3 ComputeSegments_ - Create segments from list data.


INTERFACE:

 
  subroutine ComputeSegments_(element_pe_locs, elements, num_elements, &
                              nsegs, seg_starts, seg_lengths, seg_pe_locs)
USES:
 
    use m_die,  only: die
 
    implicit none
INPUT PARAMETERS:
    integer, dimension(:), intent(in)  :: element_pe_locs
    integer, dimension(:), intent(in)  :: elements
    integer,               intent(in)  :: num_elements
OUTPUT PARAMETERS:
    integer,               intent(out) :: nsegs
    integer, dimension(:), pointer     :: seg_starts
    integer, dimension(:), pointer     :: seg_lengths
    integer, dimension(:), pointer     :: seg_pe_locs
DESCRIPTION:

This routine examins an input list of num_elements process ID locations stored in the array element_pe_locs, counts the number of contiguous segments nsegs, and returns the segment start index, length, and process ID location in the arrays seg_starts(:), seg_lengths(:), and seg_pe_locs(:), respectively.

N.B.: The argument sMat is returned sorted in lexicographic order by row and column.


REVISION HISTORY:

   18Apr01 - J.W. Larson <[email protected]> - initial version.
   28Aug01 - M.J. Zavislak <[email protected]>
                 Changed first sanity check to get size(element_pe_locs)
                 instead of size(elements)


10.4 Module m_SparseMatrixToMaps - Maps from the Sparse Matrix (Source File: m_SparseMatrixToMaps.F90)

The SparseMatrix provides consolidated (on one process) or distributed sparse matrix storage for the operation ${\bf y} = {\bf M} {\bf x}$, where x and y are vectors, and M is a matrix. In performing parallel matrix-vector multiplication, one has numerous options regarding the decomposition of the matrix M, and the vectors y and x. This module provides services to generate mct mapping components--the GlobalMap and GlobalSegMap for the vectors y and/or x based on the decomposition of the sparse matrix M.


INTERFACE:

 
  module m_SparseMatrixToMaps
USES:
       use m_SparseMatrix, only : SparseMatrix
 
       implicit none
 
       private   ! except
 
       public :: SparseMatrixToXGlobalSegMap
       public :: SparseMatrixToYGlobalSegMap
 
     interface SparseMatrixToXGlobalSegMap ; module procedure &
 	 SparseMatrixToXGlobalSegMap_
     end interface
 
     interface SparseMatrixToYGlobalSegMap ; module procedure &
 	 SparseMatrixToYGlobalSegMap_
     end interface
REVISION HISTORY:
   13Apr01 - J.W. Larson <[email protected]> - initial prototype
             and API specifications.

10.4.1 SparseMatrixToXGlobalSegMap_ - Generate X GlobalSegmap.

Given an input SparseMatrix argument sMat, this routine generates an output GlobalSegMap variable xGSMap, which describes the domain decomposition of the vector x in the distributed matrix-vector multiplication

\begin{displaymath}{\bf y} = {\bf M} {\bf x}.\end{displaymath}


INTERFACE:

 
  subroutine SparseMatrixToXGlobalSegMap_(sMat, xGSMap, root, comm, comp_id)
USES:
       use m_stdio, only : stderr
       use m_die,   only : die
       use m_mpif90
 
       use m_List, only : List
       use m_List, only : List_init => init
       use m_List, only : List_clean => clean
 
       use m_SparseMatrix, only : SparseMatrix
       use m_SparseMatrix, only : SparseMatrix_nCols => nCols
       use m_SparseMatrix, only : SparseMatrix_lsize => lsize
       use m_SparseMatrix, only : SparseMatrix_indexIA => indexIA
       use m_SparseMatrix, only : SparseMatrix_SortPermute => SortPermute
 
       use m_GlobalSegMap, only : GlobalSegMap
       use m_GlobalSegMap, only : GlobalSegMap_init => init
 
       implicit none
INPUT PARAMETERS:
       integer,            intent(in)    :: root    ! communicator root
       integer,            intent(in)    :: comm    ! communicator handle
       integer,            intent(in)    :: comp_id ! component id
INPUT/OUTPUT PARAMETERS:
       type(SparseMatrix), intent(inout) :: sMat    ! input SparseMatrix
OUTPUT PARAMETERS:
       type(GlobalSegMap), intent(out)   :: xGSMap  ! segmented decomposition
                                                    ! for x
REVISION HISTORY:
   13Apr01 - J.W. Larson <[email protected]> - API specification.
   25Apr01 - J.W. Larson <[email protected]> - First version.
   27Apr01 - J.W. Larson <[email protected]> - Bug fix--intent of
             argument sMat changed from (IN) to (INOUT)
   27Apr01 - R.L. Jacob <[email protected]> - bug fix-- add use 
             statement for SortPermute
   01May01 - R.L. Jacob <[email protected]> - make comp_id an
             input argument

10.4.2 SparseMatrixToYGlobalSegMap_ - Generate Y GlobalSegmap.

Given an input SparseMatrix argument sMat, this routine generates an output GlobalSegMap variable yGSMap, which describes the domain decomposition of the vector y in the distributed matrix-vector multiplication ${\bf y} = {\bf M} {\bf x}$.


INTERFACE:

 
  subroutine SparseMatrixToYGlobalSegMap_(sMat, yGSMap, root, comm, comp_id)
USES:
       use m_stdio, only : stderr
       use m_die,   only : die
 
       use m_List, only : List
       use m_List, only : List_init => init
       use m_List, only : List_clean => clean
 
       use m_SparseMatrix, only : SparseMatrix
       use m_SparseMatrix, only : SparseMatrix_nRows => nRows
       use m_SparseMatrix, only : SparseMatrix_lsize => lsize
       use m_SparseMatrix, only : SparseMatrix_indexIA => indexIA
       use m_SparseMatrix, only : SparseMatrix_SortPermute => SortPermute
 
       use m_GlobalSegMap, only : GlobalSegMap
       use m_GlobalSegMap, only : GlobalSegMap_init => init
 
       implicit none
INPUT PARAMETERS:
       integer,            intent(in)    :: root    ! communicator root
       integer,            intent(in)    :: comm    ! communicator handle
       integer,            intent(in)    :: comp_id ! component id
INPUT/OUTPUT PARAMETERS:
       type(SparseMatrix), intent(inout) :: sMat    ! input SparseMatrix
OUTPUT PARAMETERS:
       type(GlobalSegMap), intent(out)   :: yGSMap  ! segmented decomposition
                                                    ! for y
REVISION HISTORY:
   13Apr01 - J.W. Larson <[email protected]> - API specification.
   25Apr01 - J.W. Larson <[email protected]> - initial code.
   27Apr01 - J.W. Larson <[email protected]> - Bug fix--intent of
             argument sMat changed from (IN) to (INOUT)
   27Apr01 - R.L. Jacob <[email protected]> - bug fix-- add use 
             statement for SortPermute
   01May01 - R.L. Jacob <[email protected]> - make comp_id an
             input argument
   07May02 - J.W. Larson <[email protected]> - Changed interface to
             make it consistent with SparseMatrixToXGlobalSegMap_().

10.4.3 CreateSegments_ - Generate segment information.

This routine examines an input INTEGER list of numbers indices (of length num_indices), determines the number of segments of consecutive numbers (or runs) nsegs. The starting indices for each run, and their lengths are returned in the INTEGER arrays starts(:) and lengths(:), respectively.


INTERFACE:

 
  subroutine ComputeSegments_(indices, num_indices, nsegs, starts, lengths)
USES:
       use m_stdio, only : stderr
       use m_die,   only : die
 
       implicit none
INPUT PARAMETERS:
 
       integer, dimension(:), intent(in)  :: indices
       integer,               intent(in)  :: num_indices
OUTPUT PARAMETERS:
       integer,               intent(out) :: nsegs
       integer, dimension(:), pointer     :: starts
       integer, dimension(:), pointer     :: lengths
REVISION HISTORY:
   19Apr01 - J.W. Larson <[email protected]> - API specification.
   25Apr01 - J.W. Larson <[email protected]> - Initial code.
   27Apr01 - J.W. Larson <[email protected]> - Bug fix--error in
             computation of segment starts/lengths.
   27Nov01 - E.T. Ong <[email protected]> - Bug fix--initialize
             nsegs=0 in case num_indices=0.


10.5 Module m_SparseMatrixPlus - Class Parallel for Matrix-Vector Multiplication (Source File: m_SparseMatrixPlus.F90)

Matrix-vector multiplication is one of the MCT's core services, and is used primarily for the interpolation of data fields from one physical grid to another. Let ${\bf x} \in \Re^{N_x}$ and ${\bf y} \in \Re^{N_y}$ represent data fields on physical grids $A$ and $B$, respectively. Field data is interpolated from grid $A$ to grid $B$ by

\begin{displaymath}{\bf y} = {\bf M} {\bf x} , \end{displaymath}

where M is aa ${N_y} \times {N_x}$ matrix.

Within MCT, the SparseMatrix data type is MCT's object for storing sparse matrices such as M , and the AttrVect data type is MCT's field data storage object. That is, x and y are each stored in AttrVect form, and M is stored as a SparseMatrix.

For global address spaces (uniprocessor or shared-memory parallel), this picture of matrix-vector multiplication is sufficient. If one wishes to perform distributed-memory parallel matrix-vector multiplication, however, in addition to computation, one must consider communication.

There are three basic message-passing parallel strategies for computing ${\bf y} = {\bf M} {\bf x}$:

  1. Decompose M based on its rows, and corresponding to the decomposition for the vector y. That is, if a given process owns the $i^{\rm th}$ element of y, then all the elements of row $i$ of M also reside on this process. Then ${\bf y} = {\bf M} {\bf x}$ is implemented as follows:
    1. Create an intermediate vector x' that is the pre-image of the elements of y owned locally.
    2. Comunnicate with the appropriate processes on the local communicator to gather from x the elements of x'.
    3. Compute ${\bf y} = {\bf M} {\bf x'}$.
    4. Destroy the data structure holding x'.
  2. Decompose M based on its columns, and corresponding to the decomposition for the vector x. That is, if a given process owns the $j^{\rm th}$ element of x, then all the elements of column $j$ of M also reside on this process. Then ${\bf y} = {\bf M} {\bf x}$ is implemented as follows:
    1. Create an intermediate vector y' that holds partial sums of elements of y computed from x and M.
    2. Compute ${\bf y'} = {\bf M} {\bf x}$.
    3. Perform communications to route elements of y' to their eventual destinations in y, where they will be summed, resulting in the distributed vector y.
    4. Destroy the data structure holding y'.
  3. Decompose M based on some arbitrary, user-supplied scheme. This will necessitate two intermediate vectors x' and y'. Then ${\bf y} = {\bf M} {\bf x}$ is implemented as follows:
    1. Create intermediate vectors x' and y'. The numbers of elements in x' and y' are based M, specifically its numbers of distinct row and column index values, respectively.
    2. Comunnicate with the appropriate processes on the local communicator to gather from x the elements of x'.
    3. Compute ${\bf y'} = {\bf M} {\bf x'}$.
    4. Perform communications to route elements of y' to their eventual destinations in y, where they will be summed, resulting in the distributed vector y.
    5. Destroy the data structures holding x' and y'.

These operations require information about many aspects of the multiplication process. These data are:

In MCT, the above data are stored in a master class for SparseMatrix- AttrVect multiplication. This master class is called a SparseMatrixPlus.

This module contains the definition of the SparseMatrixPlus, and a variety of methods to support it. These include initialization, destruction, query, and data import/export.


INTERFACE:

 
  module m_SparseMatrixPlus
USES:
 
       use m_String, only : String
       use m_SparseMatrix, only : SparseMatrix
       use m_Rearranger, only : Rearranger
PUBLIC TYPES:
 
       public :: SparseMatrixPlus
 
       Type SparseMatrixPlus
 #ifdef SEQUENCE
         sequence
 #endif
         type(String) :: Strategy
         integer :: XPrimeLength
         type(Rearranger) :: XToXPrime
         integer :: YPrimeLength
         type(Rearranger) :: YPrimeToY
         type(SparseMatrix) :: Matrix
 	integer :: Tag
       End Type SparseMatrixPlus
PUBLIC MEMBER FUNCTIONS:
 
       public :: init
       public :: vecinit
       public :: clean
       public :: initialized
       public :: exportStrategyToChar
 
       interface init ; module procedure &
         initFromRoot_, &
         initDistributed_
       end interface
       interface vecinit ; module procedure vecinit_ ; end interface
       interface clean ; module procedure clean_ ; end interface
       interface initialized ; module procedure initialized_ ; end interface
       interface exportStrategyToChar ; module procedure &
         exportStrategyToChar_ 
       end interface
PUBLIC DATA MEMBERS:
 
       public :: Xonly ! Matrix decomposed only by ROW (i.e., based 
                       ! on the decomposition of y); comms x->x'
       public :: Yonly ! Matrix decomposed only by COLUMN (i.e., based 
                       ! on the decomposition of x); comms y'->y
       public :: XandY ! Matrix has complex ROW/COLUMN decomposed
DEFINED PARAMETERS:
 
       integer,parameter                    :: DefaultTag = 700
SEE ALSO:
   The MCT module m_SparseMatrix for more information about Sparse Matrices.
   The MCT module m_Rearranger for deatailed information about Communications 
   scheduling.
   The MCT module m_AttrVect for details regarding the Attribute Vector.
   The MCT module m_MatAttrVectMult for documentation of API's that use 
   the SparseMatrixPlus.
REVISION HISTORY:
   29August 2002 - J. Larson <[email protected]> - API specification.

10.5.1 initFromRoot_ - Creation and Initializtion from the Root

This routine creates an SparseMatrixPlus sMatPlus using the following elements:

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


INTERFACE:

 
  subroutine initFromRoot_(sMatPlus, sMat, xGSMap, yGSMap, strategy, &
                           root, comm, ComponentID, Tag)
USES:
 
       use m_die
       use m_stdio
       use m_mpif90
 
       use m_String, only : String
       use m_String, only : String_init => init
 
       use m_GlobalSegMap, only : GlobalSegMap
       use m_GlobalSegMap, only : GlobalSegMap_gsize => gsize
       use m_GlobalSegMap, only : GlobalSegMap_lsize => lsize
       use m_GlobalSegMap, only : GlobalSegMap_clean => clean
 
       use m_SparseMatrix, only : SparseMatrix
       use m_SparseMatrix, only : SparseMatrix_nRows => nRows
       use m_SparseMatrix, only : SparseMatrix_nCols => nCols
 
       use m_SparseMatrixComms, only : SparseMatrix_ScatterByRow => ScatterByRow
       use m_SparseMatrixComms, only : SparseMatrix_ScatterByColumn => &
                                                                 ScatterByColumn
 
       use m_SparseMatrixToMaps, only : SparseMatrixToXGlobalSegMap
       use m_SparseMatrixToMaps, only : SparseMatrixToYGlobalSegMap
 
       use m_GlobalToLocal, only : GlobalToLocalMatrix
 
       use m_Rearranger, only : Rearranger
       use m_Rearranger, only : Rearranger_init => init
 
       implicit none
INPUT PARAMETERS:
 
       type(GlobalSegMap),     intent(in)    :: xGSMap
       type(GlobalSegMap),     intent(in)    :: yGSMap
       character(len=*),       intent(in)    :: strategy
       integer,                intent(in)    :: root
       integer,                intent(in)    :: comm
       integer,                intent(in)    :: ComponentID
       integer,optional,       intent(in)    :: Tag
INPUT/OUTPUT PARAMETERS:
       
       type(SparseMatrix),     intent(inout) :: sMat
OUTPUT PARAMETERS:
 
       type(SparseMatrixPlus), intent(out)   :: SMatPlus
REVISION HISTORY:
   30Aug02 - Jay Larson <[email protected]> - API Specification

10.5.2 initDistributed_ - Distributed Creation and Initializtion

This routine creates an SparseMatrixPlus sMatPlus using the following elements:

The other input arguments required by this routine are the INTEGER arguments root and ComponentID, which define the communicator root ID and MCT component ID, respectively.


INTERFACE:

 
  subroutine initDistributed_(sMatPlus, sMat, xGSMap, yGSMap, root, comm, &
                              ComponentID, Tag)
USES:
 
       use m_die
       use m_stdio
       use m_mpif90
 
       use m_String, only : String
       use m_String, only : String_init => init
 
       use m_GlobalSegMap, only : GlobalSegMap
       use m_GlobalSegMap, only : GlobalSegMap_gsize => gsize
       use m_GlobalSegMap, only : GlobalSegMap_lsize => lsize
       use m_GlobalSegMap, only : GlobalSegMap_clean => clean
 
       use m_SparseMatrix, only : SparseMatrix
       use m_SparseMatrix, only : SparseMatrix_nRows => nRows
       use m_SparseMatrix, only : SparseMatrix_nCols => nCols
       use m_SparseMatrix, only : SparseMatrix_Copy => Copy
 
       use m_SparseMatrixComms, only : SparseMatrix_ScatterByRow => ScatterByRow
       use m_SparseMatrixComms, only : SparseMatrix_ScatterByColumn => &
                                                                 ScatterByColumn
 
       use m_SparseMatrixToMaps, only : SparseMatrixToXGlobalSegMap
       use m_SparseMatrixToMaps, only : SparseMatrixToYGlobalSegMap
 
       use m_GlobalToLocal, only : GlobalToLocalMatrix
 
       use m_Rearranger, only : Rearranger
       use m_Rearranger, only : Rearranger_init => init
 
       implicit none
INPUT PARAMETERS:
 
       type(GlobalSegMap),     intent(in)    :: xGSMap
       type(GlobalSegMap),     intent(in)    :: yGSMap
       integer,                intent(in)    :: root
       integer,                intent(in)    :: comm
       integer,                intent(in)    :: ComponentID
       integer,optional,       intent(in)    :: Tag
INPUT/OUTPUT PARAMETERS:
       
       type(SparseMatrix),     intent(inout) :: sMat
OUTPUT PARAMETERS:
 
       type(SparseMatrixPlus), intent(out)   :: SMatPlus
REVISION HISTORY:
   30Aug02 - Jay Larson <[email protected]> - API Specification

10.5.3 vecinit_ - Initialize vector parts of a SparseMatrixPlus

This routine will initialize the parts of the SparseMatrix in the SparseMatrixPlus object that are used in the vector-friendly version of the sparse matrix multiply.


INTERFACE:

 
  subroutine vecinit_(SMatP)
USES:
       use m_die
       use m_SparseMatrix, only : SparseMatrix_vecinit => vecinit
 
       implicit none
INPUT/OUTPUT PARAMETERS:
 
       type(SparseMatrixPlus), intent(inout)  :: SMatP
REVISION HISTORY:
   29Oct03 - R. Jacob <[email protected]> - initial prototype

10.5.4 clean_ - Destruction of a SparseMatrixPlus Object

This routine deallocates all allocated memory belonging to the input/output SparseMatrixPlus argument SMatP, and sets to zero its integer components describing intermediate vector length, and sets its LOGICAL flag signifying initialization to .FALSE. The success (failure) of this operation is signified by the zero (non-zero) value of the optional INTEGER output argument status. If the user does supply status when invoking this routine, failure of clean_() will lead to termination of execution with an error message.


INTERFACE:

 
  subroutine clean_(SMatP, status)
USES:
 
       use m_die
       use m_stdio
 
       use m_String, only : String
       use m_String, only : String_init => init
       use m_String, only : String_ToChar => toChar
       use m_String, only : String_clean => clean
 
       use m_SparseMatrix, only : SparseMatrix
       use m_SparseMatrix, only : SparseMatrix_clean => clean
 
       use m_Rearranger, only : Rearranger
       use m_Rearranger, only : Rearranger_clean => clean
 
       implicit none
INPUT/OUTPUT PARAMETERS:
 
       type(SparseMatrixPlus), intent(inout)  :: SMatP
OUTPUT PARAMETERS:
 
       integer, optional,  intent(out)   :: status
REVISION HISTORY:
   30Aug02 - Jay Larson <[email protected]> - API Specification

10.5.5 initialized_ - Confirmation of Initialization

This LOGICAL query function tells the user if the input SparseMatrixPlus argument sMatPlus has been initialized. The return value of initialized_ is .TRUE. if sMatPlus has been previously initialized, .FALSE. if it has not.


INTERFACE:

 
  logical function initialized_(sMatPlus)
USES:
   No external modules are used by this function.
       
       use m_String, only : String_len
       use m_List,   only : List
       use m_List,   only : List_init => init
       use m_List,   only : List_identical => identical
       use m_List,   only : List_clean => clean
 
       use m_die
 
       implicit none
INPUT PARAMETERS:
       type(SparseMatrixPlus), intent(in)  :: sMatPlus
REVISION HISTORY:
   26Sep02 - Jay Larson <[email protected]> - Implementation

10.5.6 exportStrategyToChar - Return Parallelization Strategy

This query subroutine returns the parallelization strategy set in the input SparseMatrixPlus argument sMatPlus. The result is returned in the output CHARACTER argument StratChars.


INTERFACE:

 
  function exportStrategyToChar_(sMatPlus)
USES:
    use m_stdio
    use m_die
 
    use m_String, only : String_ToChar => toChar
    use m_String, only : String_init => init
    use m_String, only : String_clean => clean
    use m_String, only : String
 
    implicit none
INPUT PARAMETERS:
       type(SparseMatrixPlus), intent(in)  :: sMatPlus
OUTPUT PARAMETERS:
       character(len=size(sMatPlus%Strategy%c)) :: exportStrategyToChar_
 
REVISION HISTORY:
   01Aug07 - Jay Larson <[email protected]> - Implementation



next up previous contents
Next: 11 Matrix Vector Multiplication Up: 2 High Level API's Previous: 9 Rearranging Attribute Vectors   Contents
[email protected]