next up previous contents
Next: 6 The Navigator Up: 1 Basic API's and Previous: 4 The Router   Contents

Subsections

5 The General Grid

5.1 Module m_GeneralGrid - Physical Coordinate Grid Information Storage (Source File: m_GeneralGrid.F90)

The GeneralGrid data type is a flexible, generic structure for storing physical coordinate grid information. The GeneralGrid may be employed to store coordinate grids of arbitrary dimension, and is also capable of supporting unstructured grids such as meteorological observation data streams. The grid is representated by a literal listing of the gridpoint coordinates, along with other integer and real attributes associated with each location. Examples of real non-coordinate attributes are grid cell length, cross-sectional area, and volume elements, projections of local directional unit vectors onto et cetera A GeneralGrid as at minimum one integer attribute--the global grid point number, or GlobGridNum, which serves as a unique identifier for each physical grid location.

The real attributes of of the GeneralGrid are grouped as List components:

This module contains the definition of the GeneralGrid datatype, various methods for creating and destroying it, query methods, and tools for multiple-key sorting of gridpoints.


INTERFACE:

 
  module m_GeneralGrid
USES:
       use m_List, only : List   ! Support for List components.
 
       use m_AttrVect, only : AttrVect ! Support for AttrVect component.
 
       implicit none
 
       private   ! except
PUBLIC TYPES:
 
       public :: GeneralGrid      ! The class data structure
 
     Type GeneralGrid
 #ifdef SEQUENCE
       sequence
 #endif
       type(List)                     :: coordinate_list
       type(List)                     :: coordinate_sort_order
       logical, dimension(:), pointer :: descend
       type(List)                     :: weight_list
       type(List)                     :: other_list
       type(List)                     :: index_list
       type(AttrVect)                 :: data
     End Type GeneralGrid
PUBLIC MEMBER FUNCTIONS:
 
       public :: init             ! Create a GeneralGrid
       public :: initCartesian    !
       public :: initUnstructured !
       public :: clean            ! Destroy a GeneralGrid
       public :: zero             ! Zero data in a GeneralGrid
 
                              ! Query functions-----------------
       public :: dims         ! Return dimensionality of the GeneralGrid
       public :: indexIA      ! Index integer attribute (indices)
       public :: indexRA      ! Index integer attribute (coords/weights)
       public :: lsize        ! Return local number of points
       public :: exportIAttr  ! Return INTEGER attribute as a vector
       public :: exportRAttr  ! Return REAL attribute as a vector
 
                              ! Manipulation--------------------
       public :: importIAttr  ! Insert INTEGER vector as attribute
       public :: importRAttr  ! Insert REAL vector as attribute
       public :: Sort         ! Sort point data by coordinates -> permutation
       public :: Permute      ! Rearrange point data using input permutation
       public :: SortPermute  ! Sort and Permute point data
 
     interface init  ; module procedure &
         init_, &
         initl_, &
         initgg_
     end interface
     interface initCartesian ; module procedure &
         initCartesianSP_, &
 	initCartesianDP_
     end interface
     interface initUnstructured ; module procedure &
         initUnstructuredSP_, &
 	initUnstructuredDP_
     end interface
     interface clean ; module procedure clean_ ; end interface
     interface zero ; module procedure zero_ ; end interface
 
     interface dims ; module procedure dims_ ; end interface
     interface indexIA ; module procedure indexIA_ ; end interface
     interface indexRA ; module procedure indexRA_ ; end interface
     interface lsize   ; module procedure lsize_   ; end interface
 
     interface exportIAttr ; module procedure exportIAttr_ ; end interface
     interface exportRAttr ; module procedure &
        exportRAttrSP_, &
        exportRAttrDP_
     end interface
     interface importIAttr ; module procedure importIAttr_ ; end interface
     interface importRAttr ; module procedure &
        importRAttrSP_, &
        importRAttrDP_
     end interface
 
     interface Sort    ; module procedure Sort_    ; end interface
     interface Permute ; module procedure Permute_ ; end interface
     interface SortPermute ; module procedure SortPermute_ ; end interface
PUBLIC DATA MEMBERS:
 
   CHARACTER Tag for GeneralGrid Global Grid Point Identification Number
 
   character(len=*), parameter :: GlobGridNum='GlobGridNum'
SEE ALSO:
   The MCT module m_AttrVect and the mpeu module m_List.
REVISION HISTORY:
   25Sep00 - J.W. Larson <[email protected]> - initial prototype
   31Oct00 - J.W. Larson <[email protected]> - modified the
             GeneralGrid type to allow inclusion of grid cell
             dimensions (lengths) and area/volume weights.
   15Jan01 - J.W. Larson implemented new GeneralGrid type 
             definition and added numerous APIs.
   17Jan01 - J.W. Larson fixed minor bug in module header use
             statement.
   19Jan01 - J.W. Larson added other_list and coordinate_sort_order
             components to the GeneralGrid type.
   21Mar01 - J.W. Larson - deleted the initv_ API (more study
             needed before implementation.
    2May01 - J.W. Larson - added initgg_ API (replaces old initv_).
   13Dec01 - J.W. Larson - added import and export methods.
   27Mar02 - J.W. Larson <[email protected]> - Corrected usage of
             m_die routines throughout this module.
    5Aug02 - E. Ong <[email protected]> - Modified GeneralGrid usage 
             to allow user-defined grid numbering schemes.

5.1.1 init_ - Create an Empty GeneralGrid

The routine init_() creates the storage space for grid point coordinates, area/volume weights, and other coordinate data (e.g., local cell dimensions). These data are referenced by List components that are also created by this routine (see the documentation of the declaration section of this module for more details about setting list information). Each of the input CHARACTER arguments is a colon-delimited string of attribute names, each corrsponding to a List element of the output GeneralGrid argument GGrid, and are summarized in the table below:


Argument Component of GGrid Significance Required?
CoordChars GGrid%coordinate_list Dimension Names Yes
CoordSortOrder GGrid%coordinate_sort_order Grid Point No
    Sorting Keys  
WeightChars GGrid%weight_list Grid Cell No
    Length, Area, and  
    Volume Weights  
OtherChars GGrid%other_list All Other No
    Real Attributes  
IndexChars GGrid%index_list All Other No
    Integer Attributes  

The input INTEGER argument lsize defines the number of grid points to be stored in GGrid.

If a set of sorting keys is supplied in the argument CoordSortOrder, the user can control whether the sorting by each key is in descending or ascending order by supplying the input LOGICAL array descend(:). By default, all sorting is in ascending order for each key if the argument descend is not provided.

N.B.: The output GeneralGrid GGrid is dynamically allocated memory. When one no longer needs GGrid, one should release this space by invoking clean() for the GeneralGrid.


INTERFACE:

 
  subroutine init_(GGrid, CoordChars, CoordSortOrder, descend, WeightChars, &
                   OtherChars, IndexChars, lsize )
USES:
       use m_stdio
       use m_die
 
       use m_List,     only : List
       use m_List,     only : List_init => init
       use m_List,     only : List_nitem => nitem
       use m_List,     only : List_shared => GetSharedListIndices
       use m_List,     only : List_append => append
       use m_List,     only : List_copy => copy
       use m_List,     only : List_nullify => nullify
       use m_List,     only : List_clean => clean
 
       use m_AttrVect, only : AttrVect
       use m_AttrVect, only : AttrVect_init => init
 
       implicit none
INPUT PARAMETERS:
       character(len=*),                intent(in) :: CoordChars
       character(len=*),      optional, intent(in) :: CoordSortOrder
       character(len=*),      optional, intent(in) :: WeightChars
       logical, dimension(:), optional, pointer    :: descend
       character(len=*),      optional, intent(in) :: OtherChars
       character(len=*),      optional, intent(in) :: IndexChars
       integer,               optional, intent(in) :: lsize
OUTPUT PARAMETERS:
       type(GeneralGrid), intent(out)   :: GGrid
REVISION HISTORY:
   25Sep00 - Jay Larson <[email protected]> - initial prototype
   15Jan01 - Jay Larson <[email protected]> - modified to fit
             new GeneralGrid definition.  
   19Mar01 - Jay Larson <[email protected]> - added OtherChars
   25Apr01 - Jay Larson <[email protected]> - added GlobGridNum
             as a mandatory integer attribute.
   13Jun01 - Jay Larson <[email protected]> - No longer define 
             blank List attributes of the GeneralGrid.  Previous
             versions of this routine had this feature, and this
             caused problems with the GeneralGrid Send and Receive
             operations on the AIX platform.
   13Jun01 - R. Jacob <[email protected]> - nullify any pointers
             for lists not declared.
   15Feb02 - Jay Larson <[email protected]> - made the input 
             argument CoordSortOrder mandatory (rather than
             optional).
   18Jul02 - E. Ong <[email protected]> - replaced this version of 
             init with one that calls initl_. 
    5Aug02 - E. Ong <[email protected]> - made the input argument
             CoordSortOrder optional to allow user-defined grid
             numbering schemes.

5.1.2 initl_ - Create an Empty GeneralGrid from Lists

The routine initl_() creates the storage space for grid point coordinates, area/volume weights, and other coordinate data (e.g., local cell dimensions). These data are referenced by List components that are also created by this routine (see the documentation of the declaration section of this module for more details about setting list information). Each of the input List arguments is used directly to create the corresponding List element of the output GeneralGrid argument GGrid, and are summarized in the table below:


Argument Component of GGrid Significance Required?
CoordList GGrid%coordinate_list Dimension Names Yes
CoordSortOrder GGrid%coordinate_sort_order Grid Point No
    Sorting Keys  
WeightList GGrid%weight_list Grid Cell No
    Length, Area, and  
    Volume Weights  
OtherList GGrid%other_list All Other No
    Real Attributes  
IndexList GGrid%index_list All Other No
    Integer Attributes  

The input INTEGER argument lsize defines the number of grid points to be stored in GGrid.

If a set of sorting keys is supplied in the argument CoordSortOrder, the user can control whether the sorting by each key is in descending or ascending order by supplying the input LOGICAL array descend(:). By default, all sorting is in ascending order for each key if the argument descend is not provided.

N.B.: The output GeneralGrid GGrid is dynamically allocated memory. When one no longer needs GGrid, one should release this space by invoking clean() for the GeneralGrid.


INTERFACE:

 
  subroutine initl_(GGrid, CoordList, CoordSortOrder, descend, WeightList, &
                    OtherList, IndexList, lsize )
USES:
 
       use m_stdio
       use m_die
 
       use m_List,     only : List
       use m_List,     only : List_init => init
       use m_List,     only : List_allocated => allocated
       use m_List,     only : List_nitem => nitem
       use m_List,     only : List_shared => GetSharedListIndices
       use m_List,     only : List_append => append
       use m_List,     only : List_copy => copy
       use m_List,     only : List_nullify => nullify
       use m_List,     only : List_clean => clean
 
       use m_AttrVect, only : AttrVect
       use m_AttrVect, only : AttrVect_init => init
 
       implicit none
INPUT PARAMETERS:
       Type(List),                      intent(in)  :: CoordList
       Type(List),            optional, intent(in)  :: CoordSortOrder
       Type(List),            optional, intent(in)  :: WeightList
       logical, dimension(:), optional, pointer     :: descend
       Type(List),            optional, intent(in)  :: OtherList
       Type(List),            optional, intent(in)  :: IndexList
       integer,               optional, intent(in)  :: lsize
OUTPUT PARAMETERS:
       type(GeneralGrid),               intent(out) :: GGrid
REVISION HISTORY:
   10May01 - Jay Larson <[email protected]> - initial version
    8Aug01 - E.T. Ong <[email protected]> - changed list assignment(=)
             to list copy to avoid compiler bugs with pgf90
   17Jul02 - E. Ong <[email protected]> - general revision; 
             added error checks
    5Aug02 - E. Ong <[email protected]> - made input argument
             CoordSortOrder optional to allow for user-defined
             grid numbering schemes

5.1.3 initgg_ - Create a GeneralGrid from Another

The routine initgg_() creates the storage space for grid point coordinates, area/volume weights, and other coordinate data (e.g., nearest-neighbor coordinates). These data are all copied from the already initialized input GeneralGrid argument iGGrid. This routine initializes the output GeneralGrid argument oGGrid with the same List data as iGGrid, but with storage space for lsize gridpoints.

N.B.: Though the attribute lists and gridpoint sorting strategy of iGGrid is copied to oGGrid, the actual values of the attributes are not.

N.B.: It is assumed that iGGrid has been initialized.

N.B.: The output GeneralGrid oGGrid is dynamically allocated memory. When one no longer needs oGGrid, one should release this space by invoking GeneralGrid_clean().


INTERFACE:

 
  subroutine initgg_(oGGrid, iGGrid, lsize)
USES:
       use m_stdio
       use m_die
 
       use m_List, only : List
       use m_List, only : List_allocated => allocated
       use m_List, only : List_copy => copy
       use m_List, only : List_nitems => nitem
       use m_List, only : List_nullify => nullify
 
       use m_AttrVect, only:  AttrVect
       use m_AttrVect, only:  AttrVect_init => init
 
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid), intent(in)  :: iGGrid
       integer, optional, intent(in)  :: lsize
OUTPUT PARAMETERS:
       type(GeneralGrid), intent(out) :: oGGrid
REVISION HISTORY:
    2May01 - Jay Larson <[email protected]> - Initial version.
   13Jun01 - Jay Larson <[email protected]> - Now, undefined List
             components of the GeneralGrid iGGrid are no longer 
             copied to oGGrid.
    8Aug01 - E.T. Ong <[email protected]> - changed list assignment(=)
             to list copy to avoid compiler bugs with pgf90
   24Jul02 - E.T. Ong <[email protected]> - updated this init version
             to correspond with initl_
    5Aug02 - E. Ong <[email protected]> - made input argument
             CoordSortOrder optional to allow for user-defined
             grid numbering schemes

5.1.4 initCartesianSP_ - Initialize a Cartesian GeneralGrid

The routine initCartesian_() creates the storage space for grid point coordinates, area and volume weights, and other coordinate data (e.g., cell area and volume weights). The names of the Cartesian axes are supplied by the user as a colon-delimitted string in the input CHARACTER argument CoordChars. For example, a Cartesian grid for Euclidian 3-space would have ${\tt CoordChars} = {\tt 'x:y:z'}$. The user can define named real attributes for spatial weighting data in the input CHARACTER argument WeightChars. For example, one could define attributes for Euclidean 3-space length elements by setting ${\tt WeightChars} = {\tt 'dx:dy:dz'}$. The input CHARCTER argument OtherChars provides space for defining other real attributes (again as a colon-delimited string of attribute names). One can define integer attributes by supplying a colon-delimitted string of names in the input CHARACTER argument IndexChars. For example, on could set aside storage space for the x-, y-, and z-indices by setting ${\tt IndexChars} = {\tt 'xIndex:yIndex:zIndex'}$.

Once the storage space in GGrid is initialized, The gridpoint coordinates are evaluated using the input arguments Dims (the number of points on each coordinate axis) and AxisData (the coordinate values on all of the points of all of the axes). The user presents the axes with each axis stored in a column of AxisData, and the axes are laid out in the same order as the ordering of the axis names in CoordChars. The number of points on each axis is defined by the entries of the input INTEGER array Dims(:). Continuing with the Euclidean 3-space example given above, setting ${\tt Dims(1:3)} = {\tt (256, 256, 128)}$ will result in a Cartesian grid with 256 points in the x- and y-directions, and 128 points in the z-direction. Thus the appropriate dimensions of AxisData are 256 rows (the maximum number of axis points among all the axes) by 3 columns (the number of physical dimensions). The x-axis points are stored in AxisData(1:256,1), the y-axis points are stored in AxisData(1:256,2), and the z-axis points are stored in AxisData(1:128,3).

The sorting order of the gridpoints can be either user-defined, or set automatically by MCT. If the latter is desired, the user must supply the argument CoordSortOrder, which defines the lexicographic ordering (by coordinate). The entries optional input LOGICAL array descend(:) stipulates whether the ordering with respect to the corresponding key in CoordChars is to be descending. If CoordChars is supplied, but descend(:) is not, the gridpoint information is placed in ascending order for each key. Returning to our Euclidian 3-space example, a choice of ${\tt CoordSortOrder} = {\tt y:x:z}$ and ${\tt descend(1:3)} =
({\tt .TRUE.}, {\tt .FALSE.}, {\tt .FALSE.})$ will result in the entries of GGrid being orderd lexicographically by y (in descending order), x (in ascending order), and z (in ascending order). Regardless of the gridpoint sorting strategy, MCT will number each of the gridpoints in GGrid, storing this information in the integer attribute named 'GlobGridNum'.


INTERFACE:

 
  subroutine initCartesianSP_(GGrid, CoordChars, CoordSortOrder, descend, &
                            WeightChars, OtherChars, IndexChars, Dims, &
                            AxisData)
USES:
       use m_stdio
       use m_die
       use m_realkinds,  only : SP
 
       use m_String,     only : String
       use m_String,     only : String_ToChar => ToChar
       use m_String,     only : String_clean => clean
 
       use m_List,     only : List
       use m_List,     only : List_init => init
       use m_List,     only : List_clean => clean
       use m_List,     only : List_nullify => nullify
       use m_List,     only : List_append => append
       use m_List,     only : List_nitem => nitem
       use m_List,     only : List_get => get
       use m_List,     only : List_shared => GetSharedListIndices
 
       use m_AttrVect, only : AttrVect
       use m_AttrVect, only : AttrVect_init => init
       use m_AttrVect, only : AttrVect_zero => zero
 
       implicit none
INPUT PARAMETERS:
       character(len=*),                  intent(in)  :: CoordChars
       character(len=*),        optional, intent(in)  :: CoordSortOrder
       character(len=*),        optional, intent(in)  :: WeightChars
       logical, dimension(:),   optional, pointer     :: descend
       character(len=*),        optional, intent(in)  :: OtherChars
       character(len=*),        optional, intent(in)  :: IndexChars
       integer, dimension(:),             pointer     :: Dims
       real(SP), dimension(:,:),          pointer     :: AxisData
OUTPUT PARAMETERS:
       type(GeneralGrid),                 intent(out) :: GGrid
REVISION HISTORY:
    7Jun01 - Jay Larson <[email protected]> - API Specification.
   12Aug02 - Jay Larson <[email protected]> - Implementation.

5.1.5 initUnstructuredSP_ - Initialize an Unstructured GeneralGrid

This routine creates the storage space for grid point coordinates, area/volume weights, and other coordinate data (e.g., local cell dimensions), and fills in user-supplied values for the grid point coordinates. These data are referenced by List components that are also created by this routine (see the documentation of the declaration section of this module for more details about setting list information). Each of the input CHARACTER arguments is a colon-delimited string of attribute names, each corrsponding to a List element of the output GeneralGrid argument GGrid, and are summarized in the table below:


Argument Component of GGrid Significance Required?
CoordChars GGrid%coordinate_list Dimension Names Yes
CoordSortOrder GGrid%coordinate_sort_order Grid Point No
    Sorting Keys  
WeightChars GGrid%weight_list Grid Cell No
    Length, Area, and  
    Volume Weights  
OtherChars GGrid%other_list All Other No
    Real Attributes  
IndexChars GGrid%index_list All Other No
    Integer Attributes  

The number of physical dimensions of the grid is set by the user in the input INTEGER argument nDims, and the number of grid points stored in GGrid is set using the input INTEGER argument nPoints. The grid point coordinates are input via the REAL array PointData(:). The number of entries in PointData must equal the product of nDims and nPoints. The grid points are grouped in nPoints consecutive groups of nDims entries, with the coordinate values for each point set in the same order as the dimensions are named in the list CoordChars.

If a set of sorting keys is supplied in the argument CoordSortOrder, the user can control whether the sorting by each key is in descending or ascending order by supplying the input LOGICAL array descend(:). By default, all sorting is in ascending order for each key if the argument descend is not provided.

N.B.: The output GeneralGrid GGrid is dynamically allocated memory. When one no longer needs GGrid, one should release this space by invoking clean() for the GeneralGrid.


INTERFACE:

 
  subroutine initUnstructuredSP_(GGrid, CoordChars, CoordSortOrder, descend, &
                               WeightChars, OtherChars, IndexChars, nDims, &
                               nPoints, PointData)
USES:
       use m_stdio
       use m_die
       use m_realkinds,only : SP
 
       use m_String,   only : String, char
       use m_List,     only : List
       use m_List,     only : List_init => init
       use m_List,     only : List_clean => clean
       use m_List,     only : List_nitem => nitem
       use m_List,     only : List_nullify => nullify
       use m_List,     only : List_copy => copy
       use m_List,     only : List_append => append
       use m_List,     only : List_shared => GetSharedListIndices
       use m_AttrVect, only : AttrVect
       use m_AttrVect, only : AttrVect_init => init
       use m_AttrVect, only : AttrVect_zero => zero
 
       implicit none
INPUT PARAMETERS:
       character(len=*),             intent(in) :: CoordChars
       character(len=*), optional,   intent(in) :: CoordSortOrder
       character(len=*), optional,   intent(in) :: WeightChars
       logical, dimension(:), optional, pointer :: descend
       character(len=*), optional,   intent(in) :: OtherChars
       character(len=*), optional,   intent(in) :: IndexChars
       integer,                      intent(in) :: nDims
       integer,                      intent(in) :: nPoints
       real(SP), dimension(:),       pointer    :: PointData
OUTPUT PARAMETERS:
       type(GeneralGrid), intent(out)   :: GGrid
REVISION HISTORY:
    7Jun01 - Jay Larson <[email protected]> - API specification.
   22Aug02 - J. Larson <[email protected]> - Implementation.

5.1.6 clean_ - Destroy a GeneralGrid

This routine deallocates all attribute storage space for the input/output GeneralGrid argument GGrid, and destroys all of its List components and sorting flags. The success (failure) of this operation is signified by the zero (non-zero) value of the optional INTEGER output argument stat.


INTERFACE:

 
     subroutine clean_(GGrid, stat)
USES:
       use m_stdio
       use m_die
 
       use m_List,     only : List_clean => clean
       use m_List,     only : List_allocated => allocated
       use m_AttrVect, only : AttrVect_clean => clean
 
       implicit none
INPUT/OUTPUT PARAMETERS:
       type(GeneralGrid), intent(inout) :: GGrid
       integer, optional, intent(out)   :: stat
REVISION HISTORY:
   25Sep00 - J.W. Larson <[email protected]> - initial prototype
   20Mar01 - J.W. Larson <[email protected]> - complete version.
    1Mar01 - E.T. Ong <[email protected]> - removed dies to prevent
             crashes when cleaning uninitialized attrvects. Added
             optional stat argument.
    5Aug02 - E. Ong <[email protected]> - a more rigorous revision

5.1.7 zero_ - Set GeneralGrid Data to Zero

This routine sets all of the point values of the integer and real attributes of an the input/output GeneralGrid argument GGrid to zero. The default action is to set the values of all the real and integer attributes to zero.


INTERFACE:

 
  subroutine zero_(GGrid, zeroReals, zeroInts)
USES:
 
 
      use m_die,only     : die
      use m_stdio,only   : stderr
 
      use m_AttrVect, only : AttrVect_zero => zero
 
      implicit none
INPUT/OUTPUT PARAMETERS:
      type(GeneralGrid),    intent(INOUT) :: GGrid
INPUT PARAMETERS:
 
      logical, optional, intent(IN)    :: zeroReals
      logical, optional, intent(IN)    :: zeroInts
REVISION HISTORY:
   11May08 - R. Jacob <[email protected]> - initial prototype/code

5.1.8 dims_ - Return the Dimensionality of a GeneralGrid

This INTEGER function returns the number of physical dimensions of the input GeneralGrid argument GGrid.


INTERFACE:

 
  integer function dims_(GGrid)
USES:
       use m_stdio
       use m_die
 
       use m_List,     only : List_nitem => nitem
 
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid), intent(in)  :: GGrid
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - initial version

5.1.9 indexIA - Index an Integer Attribute

This function returns an INTEGER, corresponding to the location of an integer attribute within the input GeneralGrid argument GGrid. For example, every GGrid has at least one integer attribute (namely the global gridpoint index 'GlobGridNum'). The array of integer values for the attribute 'GlobGridNum' is stored in

   {\tt GGrid%data%iAttr(indexIA_(GGrid,'GlobGridNum'),:)}.
   
If indexIA_() is unable to match item to any of the integer attributes present in GGrid, the resulting value is zero which is equivalent to an error. The optional input CHARACTER arguments perrWith and dieWith control how such errors are handled. Below are the rules how error handling is controlled by using perrWith and dieWith:
  1. if neither perrWith nor dieWith are present, indexIA_() terminates execution with an internally generated error message;
  2. if perrWith is present, but dieWith is not, an error message is written to stderr incorporating user-supplied traceback information stored in the argument perrWith;
  3. if dieWith is present, execution terminates with an error message written to stderr that incorporates user-supplied traceback information stored in the argument dieWith; and
  4. if both perrWith and dieWith are present, execution terminates with an error message using dieWith, and the argument perrWith is ignored.


INTERFACE:

 
  integer function indexIA_(GGrid, item, perrWith, dieWith)
USES:
       use m_die
       use m_stdio
 
       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(GeneralGrid),          intent(in) :: GGrid
       character(len=*),           intent(in) :: item
       character(len=*), optional, intent(in) :: perrWith
       character(len=*), optional, intent(in) :: dieWith
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - Initial version.
   27Mar02 - Jay Larson <[email protected]> - Cleaned up error
             handling logic.
    2Aug02 - Jay Larson <[email protected]> - Further refinement
             of error handling.

5.1.10 indexRA - Index a Real Attribute

This function returns an INTEGER, corresponding to the location of an integer attribute within the input GeneralGrid argument GGrid. For example, every GGrid has at least one integer attribute (namely the global gridpoint index 'GlobGridNum'). The array of integer values for the attribute 'GlobGridNum' is stored in

   {\tt GGrid%data%iAttr(indexRA_(GGrid,'GlobGridNum'),:)}.
   
If indexRA_() is unable to match item to any of the integer attributes present in GGrid, the resulting value is zero which is equivalent to an error. The optional input CHARACTER arguments perrWith and dieWith control how such errors are handled. Below are the rules how error handling is controlled by using perrWith and dieWith:
  1. if neither perrWith nor dieWith are present, indexRA_() terminates execution with an internally generated error message;
  2. if perrWith is present, but dieWith is not, an error message is written to stderr incorporating user-supplied traceback information stored in the argument perrWith;
  3. if dieWith is present, execution terminates with an error message written to stderr that incorporates user-supplied traceback information stored in the argument dieWith; and
  4. if both perrWith and dieWith are present, execution terminates with an error message using dieWith, and the argument perrWith is ignored.


INTERFACE:

 
  integer function indexRA_(GGrid, item, perrWith, dieWith)
USES:
       use m_stdio
       use m_die
 
       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(GeneralGrid),          intent(in)  :: GGrid
       character(len=*),           intent(in)  :: item
       character(len=*), optional, intent(in) :: perrWith
       character(len=*), optional, intent(in) :: dieWith
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - Initial version.
   27Mar02 - Jay Larson <[email protected]> - Cleaned up error
             handling logic.

5.1.11 lsize - Number of Grid Points

This INTEGER function returns the number of grid points stored in the input GeneralGrid argument GGrid. Note that the value returned will be the number of points stored on a local process in the case of a distributed GeneralGrid.


INTERFACE:

 
  integer function lsize_(GGrid)
USES:
       use m_List,     only : List
       use m_List,     only : List_allocated => allocated
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_die,      only : die    
       
 
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid), intent(in)  :: GGrid
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - Initial version.
   27Mar02 - Jay Larson <[email protected]> - slight logic change.
   27Mar02 - Jay Larson <[email protected]> - Bug fix and use of
             List_allocated() function to check for existence of 
             attributes.
    5Aug02 - E. Ong <[email protected]> - more rigorous revision

5.1.12 exportIAttr_ - Return GeneralGrid INTEGER Attribute as a Vector

This routine extracts from the input GeneralGrid argument GGrid the integer attribute corresponding to the tag defined in the input CHARACTER argument AttrTag, and returns it in the INTEGER output array outVect, and its length in the output INTEGER argument lsize.

N.B.: This routine will fail if the AttrTag is not in the GeneralGrid List component GGrid%data%iList.

N.B.: The flexibility of this routine regarding the pointer association status of the output argument outVect 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 outVect, then the user must ensure this pointer is not allocated (i.e. the user must nullify this pointer) before this routine is invoked.

N.B.: If the user has relied on this routine to allocate memory associated with the pointer outVect, 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 exportIAttr_(GGrid, AttrTag, outVect, lsize)
USES:
       use m_die 
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_exportIAttr => exportIAttr
 
       implicit none
INPUT PARAMETERS:
 
       type(GeneralGrid),      intent(in)  :: GGrid
       character(len=*),       intent(in)  :: AttrTag
OUTPUT PARAMETERS:
 
       integer,  dimension(:), pointer     :: outVect
       integer,  optional,     intent(out) :: lsize
REVISION HISTORY:
   13Dec01 - J.W. Larson <[email protected]> - initial prototype.

5.1.13 exportRAttrSP_ - Return GeneralGrid REAL Attribute as a Vector

This routine extracts from the input GeneralGrid argument GGrid the real attribute corresponding to the tag defined in the input CHARACTER argument AttrTag, and returns it in the REAL output array outVect, and its length in the output INTEGER argument lsize.

N.B.: This routine will fail if the AttrTag is not in the GeneralGrid List component GGrid%data%rList.

N.B.: The flexibility of this routine regarding the pointer association status of the output argument outVect 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 outVect, then the user must ensure this pointer is not allocated (i.e. the user must nullify this pointer) before this routine is invoked.

N.B.: If the user has relied on this routine to allocate memory associated with the pointer outVect, 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 exportRAttrSP_(GGrid, AttrTag, outVect, lsize)
USES:
       use m_die
       use m_stdio
 
       use m_realkinds,  only : SP
 
       use m_AttrVect,   only : AttrVect_exportRAttr => exportRAttr
 
       implicit none
INPUT PARAMETERS:
 
       type(GeneralGrid),          intent(in)  :: GGrid
       character(len=*),           intent(in)  :: AttrTag
OUTPUT PARAMETERS:
 
       real(SP),  dimension(:),    pointer     :: outVect
       integer,   optional,        intent(out) :: lsize
REVISION HISTORY:
   13Dec01 - J.W. Larson <[email protected]> - initial prototype.

5.1.14 importIAttr_ - Import GeneralGrid INTEGER Attribute

This routine imports data provided in the input INTEGER vector inVect into the GeneralGrid argument GGrid, storing it as the integer attribute corresponding to the tag defined in the input CHARACTER argument AttrTag. The input INTEGER argument lsize is used to ensure there is sufficient space in the GeneralGrid to store the data.

N.B.: This routine will fail if the AttrTag is not in the GeneralGrid List component GGrid%data%iList.


INTERFACE:

 
  subroutine importIAttr_(GGrid, AttrTag, inVect, lsize)
USES:
       use m_die
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_importIAttr => importIAttr
 
       implicit none
INPUT PARAMETERS:
 
       character(len=*),       intent(in)    :: AttrTag
       integer,  dimension(:), pointer       :: inVect
       integer,                intent(in)    :: lsize
INPUT/OUTPUT PARAMETERS:
 
       type(GeneralGrid),      intent(inout) :: GGrid
REVISION HISTORY:
   13Dec01 - J.W. Larson <[email protected]> - initial prototype.
   27Mar02 - Jay Larson <[email protected]> - improved error handling.

5.1.15 importRAttrSP_ - Import GeneralGrid REAL Attribute

This routine imports data provided in the input REAL vector inVect into the GeneralGrid argument GGrid, storing it as the real attribute corresponding to the tag defined in the input CHARACTER argument AttrTag. The input INTEGER argument lsize is used to ensure there is sufficient space in the GeneralGrid to store the data.

N.B.: This routine will fail if the AttrTag is not in the GeneralGrid List component GGrid%data%rList.


INTERFACE:

 
  subroutine importRAttrSP_(GGrid, AttrTag, inVect, lsize)
USES:
       use m_die ,          only : die
       use m_die ,          only : MP_perr_die
       use m_stdio ,        only : stderr
 
       use m_realkinds,     only : SP
 
       use m_AttrVect,      only : AttrVect_importRAttr => importRAttr
 
       implicit none
INPUT PARAMETERS:
 
       character(len=*),           intent(in)    :: AttrTag
       real(SP), dimension(:),     pointer       :: inVect
       integer,                    intent(in)    :: lsize
INPUT/OUTPUT PARAMETERS:
 
       type(GeneralGrid),          intent(inout) :: GGrid
REVISION HISTORY:
   13Dec01 - J.W. Larson <[email protected]> - initial prototype.
   27Mar02 - Jay Larson <[email protected]> - improved error handling.

5.1.16 Sort_ - Generate Sort Permutation Defined by Arbitrary Keys.

The subroutine Sort_() uses the list of keys present in the input List variable key_List. This list of keys is checked to ensure that only coordinate attributes are present in the sorting keys, and that there are no redundant keys. Once checked, this list is used to find the appropriate real attributes referenced by the items in key_list ( that is, it identifies the appropriate entries in GGrid%data%rList), and then uses these keys to generate a an output permutation perm that will put the entries of the attribute vector GGrid%data in lexicographic order as defined by key_list (the ordering in key_list being from left to right.


INTERFACE:

 
  subroutine Sort_(GGrid, key_List, perm, descend)
USES:
       use m_stdio
       use m_die
 
       use m_AttrVect,     only : AttrVect_Sort => Sort
       use m_List,        only : List_nitem => nitem
 
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid),               intent(in) :: GGrid
       type(List),                      intent(in) :: key_list
       logical, dimension(:), optional, intent(in) :: descend
OUTPUT PARAMETERS:
       integer, dimension(:), pointer              :: perm
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - Initial version.
   20Mar01 - Jay Larson <[email protected]> - Final working version.

5.1.17 Sortg_ - Generate Sort Permutation Based on GeneralGrid Keys.

The subroutine Sortg_() uses the list of sorting keys present in the input GeneralGrid variable GGrid%coordinate_sort_order to create a sort permutation perm(:). Sorting is either in ascending or descending order based on the entries of GGrid%descend(:). The output index permutation is stored in the array perm(:) that will put the entries of the attribute vector GGrid%data in lexicographic order as defined by GGrid%coordinate_sort_order. The ordering in GGrid%coordinate_sort_order being from left to right.

N.B.: This routine returnss an allocatable array perm(:). This allocated array must be deallocated when the user no longer needs it. Failure to do so will cause a memory leak.

N.B.: This routine will fail if GGrid has not been initialized with sort keys in the List component GGrid%coordinate_sort_order.


INTERFACE:

 
  subroutine Sortg_(GGrid, perm)
USES:
       use m_List, only : List_allocated => allocated
       use m_die,  only : die
    
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid),     intent(in) :: GGrid
OUTPUT PARAMETERS:
       integer, dimension(:), pointer    :: perm
REVISION HISTORY:
   22Mar01 - Jay Larson <[email protected]> - Initial version.
    5Aug02 - E. Ong <[email protected]> - revise with more error checking.

5.1.18 Permute_ - Permute GeneralGrid Attributes Using Supplied Index Permutation

The subroutine Permute_() uses an input index permutation perm to re-order the coordinate data stored in the GeneralGrid argument GGrid. This permutation can be generated by either of the routines Sort_() or Sortg_() contained in this module.


INTERFACE:

 
  subroutine Permute_(GGrid, perm)
USES:
 
       use m_stdio
       use m_die
 
       use m_AttrVect,     only : AttrVect
       use m_AttrVect, only : AttrVect_Permute => Permute
 
       implicit none
INPUT PARAMETERS:
       integer, dimension(:), intent(in)    :: perm
INPUT/OUTPUT PARAMETERS:
       type(GeneralGrid),     intent(inout) :: GGrid
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - API specification.
   10Apr01 - Jay Larson <[email protected]> - API modified, working
             code.

5.1.19 SortPermute_ - Sort and Permute GeneralGrid Attributes

The subroutine SortPermute_() uses the list of keys defined in GGrid%coordinate_sort_order to create an index permutation perm, which is then applied to re-order the coordinate data stored in the GeneralGrid argument GGrid (more specifically, the gridpoint data stored in GGrid%data. This permutation is generated by the routine Sortg_() contained in this module. The permutation is carried out by the routine Permute_() contained in this module.

N.B.: This routine will fail if GGrid has not been initialized with sort keys in the List component GGrid%coordinate_sort_order.


INTERFACE:

 
  subroutine SortPermute_(GGrid)
USES:
       use m_stdio
       use m_die
 
       implicit none
INPUT/OUTPUT PARAMETERS:
       type(GeneralGrid),     intent(inout)   :: GGrid
REVISION HISTORY:
   15Jan01 - Jay Larson <[email protected]> - API specification.
   10Apr01 - Jay Larson <[email protected]> - API modified, working
             code.
   13Apr01 - Jay Larson <[email protected]> - Simplified API and
             code (Thanks to Tony Craig of NCAR for detecting the
             bug that inspired these changes).


5.2 Module m_GeneralGridComms - Communications for the GeneralGrid type. (Source File: m_GeneralGridComms.F90)

In this module, we define communications methods specific to the GeneralGrid class (see the module m_GeneralGrid for more information about this class and its methods).


INTERFACE:

  module m_GeneralGridComms
USES:
       use m_GeneralGrid ! GeneralGrid class and its methods
 
 
       implicit none
 
       private   ! except
 
       public :: gather          ! gather all local vectors to the root
       public :: scatter         ! scatter from the root to all PEs
       public :: bcast           ! bcast from root to all PEs
       public :: send            ! Blocking SEND
       public :: recv            ! Blocking RECEIVE
 
     interface gather ; module procedure &
               GM_gather_, &
               GSM_gather_ 
     end interface
     interface scatter ; module procedure &
               GM_scatter_, &
               GSM_scatter_ 
     end interface
     interface bcast ; module procedure bcast_ ; end interface
     interface send  ; module procedure send_  ; end interface
     interface recv  ; module procedure recv_  ; end interface
REVISION HISTORY:
         27Apr01 - J.W. Larson <[email protected]> - Initial module/APIs
         07Jun01 - J.W. Larson <[email protected]> - Added point-to-point
         27Mar02 - J.W. Larson <[email protected]> - Overhaul of error
                   handling calls throughout this module.
         05Aug02 - E. Ong <[email protected]> - Added buffer association 
                   error checks to avoid making bad MPI calls

5.2.1 send_ - Point-to-point blocking send for the GeneralGrid.

The point-to-point send routine send_() sends the input GeneralGrid argument iGGrid to component comp_id. The message is identified by the tag defined by the INTEGER argument TagBase. The value of TagBase must match the value used in the call to recv_() on process dest. The success (failure) of this operation corresponds to a zero (nonzero) value for the output INTEGER flag status. The argument will be sent to the local root of the component.

N.B.: One must avoid assigning elsewhere the MPI tag values between TagBase and TagBase+20, inclusive. This is because send_() performs one send operation set up the header transfer, up to five List_send operations (two MPI_SEND calls in each), two send operations to transfer iGGrid%descend(:), and finally the send of the AttrVect component iGGrid%data (which comprises eight MPI_SEND operations).


INTERFACE:

 
  subroutine send_(iGGrid, comp_id, TagBase, status)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_init => init
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
 
       use m_MCTWorld, only : ComponentToWorldRank
       use m_MCTWorld, only : ThisMCTWorld
 
       use m_AttrVectComms,only : AttrVect_send => send
 
       use m_List, only : List_send => send
       use m_List, only : List_allocated => allocated
 
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid), intent(in) :: iGGrid
       integer,           intent(in) :: comp_id
       integer,           intent(in) :: TagBase
OUTPUT PARAMETERS:
       integer, optional, intent(out) :: status
REVISION HISTORY:
         04Jun01 - J.W. Larson <[email protected]> - API Specification.
         07Jun01 - J.W. Larson <[email protected]> - Initial version.
         10Jun01 - J.W. Larson <[email protected]> - Bug fixes--now works.
         11Jun01 - R. Jacob <[email protected]> use component id as input
                   argument.
         13Jun01 - J.W. Larson <[email protected]> - Initialize status
                   (if present).
         15Feb02 - J.W. Larson <[email protected]> - Made input argument
                   comm optional.
         13Jun02 - J.W. Larson <[email protected]> - Removed the argument
                   comm.  This routine is now explicitly for intercomponent
                   communications only.

5.2.2 recv_ - Point-to-point blocking recv for the GeneralGrid.

The point-to-point receive routine recv_() receives the output GeneralGrid argument oGGrid from component comp_id. The message is identified by the tag defined by the INTEGER argument TagBase. The value of TagBase must match the value used in the call to send_() on the other component. The success (failure) of this operation corresponds to a zero (nonzero) value for the output INTEGER flag status.

N.B.: This routine assumes that the GeneralGrid argument oGGrid is uninitialized on input; that is, all the List components are blank, the LOGICAL array oGGrid%descend is unallocated, and the AttrVect component oGGrid%data is uninitialized. The GeneralGrid oGGrid represents allocated memory. When the user no longer needs oGGrid, it should be deallocated by invoking GeneralGrid_clean() (see m_GeneralGrid for further details).

N.B.: One must avoid assigning elsewhere the MPI tag values between TagBase and TagBase+20, inclusive. This is because recv_() performs one receive operation set up the header transfer, up to five List_recv operations (two MPI_RECV calls in each), two receive operations to transfer iGGrid%descend(:), and finally the receive of the AttrVect component iGGrid%data (which comprises eight MPI_RECV operations).


INTERFACE:

 
  subroutine recv_(oGGrid, comp_id, TagBase, status)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_init => init
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
 
       use m_MCTWorld, only : ComponentToWorldRank
       use m_MCTWorld, only : ThisMCTWorld
 
       use m_AttrVectComms,only : AttrVect_recv => recv
 
       use m_List,only : List_recv => recv
       use m_List,only : List_nullify => nullify
 
       implicit none
INPUT PARAMETERS:
       integer,           intent(in) :: comp_id
       integer,           intent(in) :: TagBase
OUTPUT PARAMETERS:
       type(GeneralGrid), intent(out) :: oGGrid
       integer, optional, intent(out) :: status
REVISION HISTORY:
         04Jun01 - J.W. Larson <[email protected]> - API Specification.
         07Jun01 - J.W. Larson <[email protected]> - Initial version.
         10Jun01 - J.W. Larson <[email protected]> - Bug fixes--now works.
         11Jun01 - R. Jacob <[email protected]> use component id as input
                   argument.
         13Jun01 - J.W. Larson <[email protected]> - Initialize status
                   (if present).
         13Jun02 - J.W. Larson <[email protected]> - Removed the argument
                   comm.  This routine is now explicitly for intercomponent
                   communications only.

5.2.3 GM_gather_ - gather a GeneralGrid using input GlobalMap.

GM_gather_() takes an input GeneralGrid argument iG whose decomposition on the communicator associated with the F90 handle comm is described by the GlobalMap argument GMap, and gathers it to the GeneralGrid output argument oG on the root. The success (failure) of this operation is reported as a zero (nonzero) value in the optional INTEGER output argument stat.

N.B.: An important assumption made here is that the distributed GeneralGrid iG has been initialized with the same coordinate system, sort order, other real attributes, and the same indexing attributes for all processes on comm.

N.B.: Once the gridpoint data of the GeneralGrid are assembled on the root, they are stored in the order determined by the input GlobalMap GMap. The user may need to sorted these gathered data to order them in accordance with the coordinate_sort_order attribute of iG.

N.B.: The output GeneralGrid oG represents allocated memory on the root. When the user no longer needs oG it should be deallocated using GeneralGrid_clean() to avoid a memory leak


INTERFACE:

  subroutine GM_gather_(iG, oG, GMap, root, comm, stat)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GlobalMap, only : GlobalMap
       use m_GlobalMap, only : GlobalMap_gsize => gsize
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_init => init
 
       use m_AttrVectComms,only : AttrVect_Gather => gather
 
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid), intent(in)  :: iG
       type(GlobalMap),   intent(in)  :: GMap
       integer,           intent(in)  :: root
       integer,           intent(in)  :: comm
OUTPUT PARAMETERS:
       type(GeneralGrid), intent(out) :: oG
       integer, optional, intent(out) :: stat
REVISION HISTORY:
         27Apr01 - J.W. Larson <[email protected]> - API Specification.
         02May01 - J.W. Larson <[email protected]> - Initial code.
         13Jun01 - J.W. Larson <[email protected]> - Initialize stat
                   (if present).

5.2.4 GSM_gather_ - gather a GeneralGrid using input GlobalSegMap.

GMS_gather_() takes an input GeneralGrid argument iG whose decomposition on the communicator associated with the F90 handle comm is described by the GlobalSegMap argument GSMap, and gathers it to the GeneralGrid output argument oG on the root. The success (failure) of this operation is reported as a zero (nonzero) value in the optional INTEGER output argument stat.

N.B.: An important assumption made here is that the distributed GeneralGrid iG has been initialized with the same coordinate system, sort order, other real attributes, and the same indexing attributes for all processes on comm.

N.B.: Once the gridpoint data of the GeneralGrid are assembled on the root, they are stored in the order determined by the input GlobalSegMap GSMap. The user may need to sorted these gathered data to order them in accordance with the coordinate_sort_order attribute of iG.

N.B.: The output GeneralGrid oG represents allocated memory on the root. When the user no longer needs oG it should be deallocated using GeneralGrid_clean() to avoid a memory leak


INTERFACE:

 
  subroutine GSM_gather_(iG, oG, GSMap, root, comm, stat)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GlobalSegMap, only : GlobalSegMap
       use m_GlobalSegMap, only : GlobalSegMap_lsize => lsize
       use m_GlobalSegMap, only : GlobalSegMap_gsize => gsize
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_init => init
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
 
       use m_AttrVectComms,only : AttrVect_Gather => gather
 
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid),  intent(in)  :: iG
       type(GlobalSegMap), intent(in)  :: GSMap
       integer,            intent(in)  :: root
       integer,            intent(in)  :: comm
OUTPUT PARAMETERS:
       type(GeneralGrid),  intent(out) :: oG
       integer, optional,  intent(out) :: stat
REVISION HISTORY:
         27Apr01 - J.W. Larson <[email protected]> - API Specification.
         01May01 - J.W. Larson <[email protected]> - Working Version.
         13Jun01 - J.W. Larson <[email protected]> - Initialize stat
                   (if present).

5.2.5 GM_scatter_ - scatter a GeneralGrid using input GlobalMap.

GM_scatter_() takes an input GeneralGrid argument iG (valid only on the root process), and scatters it to the distributed GeneralGrid variable oG. The GeneralGrid oG is distributed on the communicator associated with the F90 handle comm using the domain decomposition described by the GlobalMap argument GMap. The success (failure) of this operation is reported as a zero (nonzero) value in the optional INTEGER output argument stat.

N.B.: The output GeneralGrid oG represents allocated memory on the root. When the user no longer needs oG it should be deallocated using GeneralGrid_clean() to avoid a memory leak.


INTERFACE:

 
  subroutine GM_scatter_(iG, oG, GMap, root, comm, stat)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GlobalMap, only : GlobalMap
       use m_GlobalMap, only : GlobalMap_lsize => lsize
       use m_GlobalMap, only : GlobalMap_gsize => gsize
 
       use m_AttrVectComms, only : AttrVect_scatter => scatter
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_init => init
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
 
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid), intent(in)  :: iG
       type(GlobalMap),   intent(in)  :: GMap
       integer,           intent(in)  :: root
       integer,           intent(in)  :: comm
OUTPUT PARAMETERS:
       type(GeneralGrid), intent(out) :: oG
       integer, optional, intent(out) :: stat
REVISION HISTORY:
         27Apr01 - J.W. Larson <[email protected]> - API Specification.
         04Jun01 - J.W. Larson <[email protected]> - Changed comms model
                   to MPI-style (i.e. iG valid on root only).
         13Jun01 - J.W. Larson <[email protected]> - Initialize stat
                   (if present).

5.2.6 GSM_scatter_ - scatter a GeneralGrid using input GlobalSegMap.

GM_scatter_() takes an input GeneralGrid argument iG (valid only on the root process), and scatters it to the distributed GeneralGrid variable oG. The GeneralGrid oG is distributed on the communicator associated with the F90 handle comm using the domain decomposition described by the GlobalSegMap argument GSMap. The success (failure) of this operation is reported as a zero (nonzero) value in the optional INTEGER output argument stat.

N.B.: The output GeneralGrid oG represents allocated memory on the root. When the user no longer needs oG it should be deallocated using GeneralGrid_clean() to avoid a memory leak.


INTERFACE:

 
  subroutine GSM_scatter_(iG, oG, GSMap, root, comm, stat)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GlobalSegMap, only : GlobalSegMap
       use m_GlobalSegMap, only : GlobalSegMap_lsize => lsize
       use m_GlobalSegMap, only : GlobalSegMap_gsize => gsize
 
       use m_AttrVectComms, only : AttrVect_scatter => scatter
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_init => init
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
 
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid),  intent(in)  :: iG
       type(GlobalSegMap), intent(in)  :: GSMap
       integer,            intent(in)  :: root
       integer,            intent(in)  :: comm
OUTPUT PARAMETERS:
       type(GeneralGrid),  intent(out) :: oG
       integer, optional,  intent(out) :: stat
REVISION HISTORY:
         27Apr01 - J.W. Larson <[email protected]> - API Specification.
         04Jun01 - J.W. Larson <[email protected]> - Initial code.
         13Jun01 - J.W. Larson <[email protected]> - Initialize stat
                   (if present).

5.2.7 bcast_ - Broadcast a GeneralGrid.

bcast_() takes an input GeneralGrid argument ioG (valid only on the root process), and broadcasts it to all processes on the communicator associated with the F90 handle comm. The success (failure) of this operation is reported as a zero (nonzero) value in the optional INTEGER output argument stat.

N.B.: On the non-root processes, the output GeneralGrid ioG represents allocated memory. When the user no longer needs ioG it should be deallocated by invoking GeneralGrid_clean(). Failure to do so risks a memory leak.


INTERFACE:

 
  subroutine bcast_(ioG, root, comm, stat)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GlobalSegMap, only : GlobalSegMap
       use m_GlobalSegMap, only : GlobalSegMap_lsize => lsize
       use m_GlobalSegMap, only : GlobalSegMap_gsize => gsize
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_init => init
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
 
       use m_AttrVectComms,only : AttrVect_bcast => bcast
 
       implicit none
INPUT PARAMETERS:
       integer,           intent(in)    :: root
       integer,           intent(in)    :: comm
INPUT/OUTPUT PARAMETERS:
       type(GeneralGrid), intent(inout) :: ioG
OUTPUT PARAMETERS:
       integer, optional, intent(out)   :: stat
REVISION HISTORY:
         27Apr01 - J.W. Larson <[email protected]> - API Specification.
         02May01 - J.W. Larson <[email protected]> - Initial version.
         13Jun01 - J.W. Larson <[email protected]> - Initialize stat
                   (if present).

5.2.8 bcastGeneralGridHeader_ - Broadcast the GeneralGrid Header.

This routine broadcasts the header information from the input GeneralGrid argument ioGGrid (on input valid on the root only). This broadcast is from the root to all processes on the communicator associated with the fortran 90 INTEGER handle comm. The success (failure) of this operation corresponds to a zero (nonzero) value for the output INTEGER flag stat.

The header information in a GeneralGrid variable comprises all the non-AttrVect components of the GeneralGrid; that is, everything except the gridpoint coordinate, geometry, and index data stored in iGGrid%data. This information includes:

  1. The coordinates in iGGrid%coordinate_list
  2. The coordinate sort order in iGGrid%coordinate_sort_order
  3. The area/volume weights in iGGrid%weight_list
  4. Other REAL geometric information in iGGrid%other_list
  5. Indexing information in iGGrid%index_list
  6. The LOGICAL descending/ascending order sort flags in iGGrid%descend(:).


INTERFACE:

 
  subroutine bcastGeneralGridHeader_(ioGGrid, root, comm, stat)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GlobalSegMap, only : GlobalSegMap
       use m_GlobalSegMap, only : GlobalSegMap_lsize => lsize
       use m_GlobalSegMap, only : GlobalSegMap_gsize => gsize
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_init => init
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
 
       use m_List, only : List
       use m_List, only : List_allocated => allocated
       use m_List, only : List_nullify => nullify
       use m_List, only : List_bcast => bcast
 
       implicit none
INPUT PARAMETERS:
       integer,           intent(in)    :: root
       integer,           intent(in)    :: comm
INPUT/OUTPUT PARAMETERS:
       type(GeneralGrid), intent(inout) :: ioGGrid
OUTPUT PARAMETERS:
       integer, optional, intent(out)   :: stat
REVISION HISTORY:
         05Jun01 - J.W. Larson <[email protected]> - Initial code.
         13Jun01 - J.W. Larson <[email protected]> - Initialize stat
                   (if present).
         05Aug02 - E. Ong <[email protected]> - added association checking

5.2.9 copyGeneralGridHeader_ - Copy the GeneralGrid Header.

This routine copies the header information from the input GeneralGrid argument iGGrid to the output GeneralGrid argument oGGrid. The header information in a GeneralGrid variable comprises all the non-AttrVect components of the GeneralGrid; that is, everything except the gridpoint coordinate, geometry, and index data stored in iGGrid%data. This information includes:

  1. The coordinates in iGGrid%coordinate_list
  2. The coordinate sort order in iGGrid%coordinate_sort_order
  3. The area/volume weights in iGGrid%weight_list
  4. Other REAL geometric information in iGGrid%other_list
  5. Indexing information in iGGrid%index_list
  6. The LOGICAL descending/ascending order sort flags in iGGrid%descend(:).


INTERFACE:

 
  subroutine copyGeneralGridHeader_(iGGrid, oGGrid)
USES:
       use m_stdio
       use m_die
 
       use m_List, only : List
       use m_List, only : List_copy => copy
       use m_List, only : List_allocated => allocated
       use m_List, only : List_nullify => nullify
 
       use m_GeneralGrid, only : GeneralGrid
 
       implicit none
INPUT PARAMETERS:
       type(GeneralGrid), intent(in)  :: iGGrid
OUTPUT PARAMETERS:
       type(GeneralGrid), intent(out) :: oGGrid
REVISION HISTORY:
         05Jun01 - J.W. Larson <[email protected]> - Initial code.
         08Aug01 - E.T. Ong <[email protected]> - changed list assignments(=)
                   to list copy.
         05Aug02 - E. Ong <[email protected]> - added association checking



next up previous contents
Next: 6 The Navigator Up: 1 Basic API's and Previous: 4 The Router   Contents
[email protected]