next up previous contents
Next: 15 Global To Local Up: 2 High Level API's Previous: 13 Merging of Flux   Contents

Subsections

14 Time Averaging

14.1 Module m_Accumulator - Time Averaging/Accumlation Buffer (Source File: m_Accumulator.F90)

An accumulator is a data class used for computing running sums and/or time averages of AttrVect class data. The period of time over which data are accumulated/averaged is the accumulation cycle, which is defined by the total number of accumulation steps (the component Accumulator%num_steps). When the accumulation routine accumulate_ is invoked, the number of accumulation cycle steps (the component Accumulator%steps_done)is incremented, and compared with the number of steps in the accumulation cycle to determine if the accumulation cycle has been completed. The accumulation buffers of the Accumulator are stored in an AttrVect (namely the component Accumulator%data), which allows the user to define the number of variables and their names at run-time. Finally, one can define for each field being accumulated the specific accumulation action. Currently, there are two options: Time Averaging and Time Summation. The user chooses the specific action by setting an integer action flag for each attribute being accumulated. The supported options are defined by the public data member constants MCT_SUM and MCT_AVG.
This module also supports a simple usage of accumulator where all the actions are SUM (inits_ and initavs_) and the user must call average_ to calculate the average from the current value of Accumulator%steps_done. Accumulator%num_steps is ignored in this case.


INTERFACE:

 
  module m_Accumulator
USES:
       use m_List, only : List
       use m_AttrVect, only : AttrVect
       use m_realkinds,only : SP,DP,FP
 
       implicit none
 
       private	! except
PUBLIC TYPES:
 
       public :: Accumulator ! The class data structure
 
     Type Accumulator
 #ifdef SEQUENCE
       sequence
 #endif
       integer :: num_steps      ! total number of accumulation steps
       integer :: steps_done     ! number of accumulation steps performed
       integer, pointer, dimension(:) :: iAction ! index of integer actions
       integer, pointer, dimension(:) :: rAction ! index of real actions
       type(AttrVect) :: data    ! accumulated sum field storage
     End Type Accumulator
PUBLIC MEMBER FUNCTIONS:
       public :: init            ! creation method
       public :: initp           ! partial creation method (MCT USE ONLY)
       public :: clean		! destruction method
       public :: initialized     ! check if initialized
       public :: lsize		! local length of the data arrays
       public :: NumSteps        ! number of steps in a cycle
       public :: StepsDone       ! number of steps completed in the 
                                 ! current cycle
       public :: nIAttr		! number of integer fields
       public :: nRAttr		! number of real fields
       public :: indexIA		! index the integer fields
       public :: indexRA		! index the real fields
       public :: getIList	! Return tag from INTEGER 
                                 ! attribute list
       public :: getRList	! Return tag from REAL attribute
                                 ! list
       public :: exportIAttr  ! Return INTEGER attribute as a vector
       public :: exportRAttr  ! Return REAL attribute as a vector
       public :: importIAttr  ! Insert INTEGER vector as attribute
       public :: importRAttr  ! Insert REAL vector as attribute
       public :: zero         ! Clear an accumulator
       public :: SharedAttrIndexList ! Returns the number of shared
 				    ! attributes, and lists of the
 				    ! respective locations of these
 				    ! shared attributes
       public :: accumulate   ! Add AttrVect data into an Accumulator
       public :: average      ! Calculate an average in an Accumulator
 
   Definition of interfaces for the methods for the Accumulator:
 
     interface init   ; module procedure	&
        init_,	&
        inits_,	&
        initv_,  &
        initavs_
     end interface
     interface initp  ; module procedure	initp_ ; end interface
     interface clean  ; module procedure clean_  ; end interface
     interface initialized; module procedure initialized_ ; end interface
     interface lsize  ; module procedure lsize_  ; end interface
     interface NumSteps  ; module procedure NumSteps_  ; end interface
     interface StepsDone  ; module procedure StepsDone_  ; end interface
     interface nIAttr ; module procedure nIAttr_ ; end interface
     interface nRAttr ; module procedure nRAttr_ ; end interface
     interface indexIA; module procedure indexIA_; end interface
     interface indexRA; module procedure indexRA_; end interface
     interface getIList; module procedure getIList_; end interface
     interface getRList; module procedure getRList_; 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 zero ; module procedure zero_ ; end interface
     interface SharedAttrIndexList ; module procedure   &
        aCaCSharedAttrIndexList_,  &   
        aVaCSharedAttrIndexList_
     end interface
     interface accumulate ; module procedure accumulate_ ; end interface
     interface average ; module procedure average_ ; end interface
PUBLIC DATA MEMBERS:
       public :: MCT_SUM
       public :: MCT_AVG
 
     integer, parameter :: MCT_SUM = 1
     integer, parameter :: MCT_AVG = 2
REVISION HISTORY:
    7Sep00 - Jay Larson <[email protected]> - initial prototype
    7Feb01 - Jay Larson <[email protected]> - Public interfaces
             to getIList() and getRList().
    9Aug01 - E.T. Ong <[email protected]> - added initialized and
             initp_ routines. Added 'action' in Accumulator type.
    6May02 - Jay Larson <[email protected]> - added import/export
              routines.
    26Aug02 - E.T. Ong <[email protected]> - thourough code revision; 
              no added routines
    10Jan08 - R. Jacob <[email protected]> - add simple accumulator
              use support and check documentation.

14.1.1 init_ - Initialize an Accumulator and its Registers

This routine allocates space for the output Accumulator argument aC, and at a minimum sets the number of time steps in an accumulation cycle (defined by the input INTEGER argument num_steps), and the length of the Accumulator register buffer (defined by the input INTEGER argument lsize). If one wishes to accumulate integer fields, the list of these fields is defined by the input CHARACTER argument iList, which is specified as a colon-delimited set of substrings (further information regarding this is available in the routine init_() of the module m_AttrVect). If no value of iList is supplied, no integer attribute accumulation buffers will be allocated. The accumulation action on each of the integer attributes can be defined by supplying the input INTEGER array argument iAction(:) (whose length must correspond to the number of items in iList). The values of the elements of iAction(:) must be one of the values among the public data members defined in the declaration section of this module. If the integer attributes are to be accumulated (i.e. one supplies iList), but iAction(:) is not specified, the default action for all integer accumulation operations will be summation. The input arguments rList and rAction(:) define the names of the real variables to be accumulated and the accumulation action for each. The arguments rList and rAction(:) are related to each other the same way as iList and iAction(:). Finally, the user can manually set the number of completed steps in an accumulation cycle (e.g. for restart purposes) by supplying a value for the optional input INTEGER argument steps_done.


INTERFACE:

 
  subroutine init_(aC, iList, iAction, rList, rAction, lsize, &
                   num_steps,steps_done)
USES:
       use m_AttrVect, only : AttrVect_init => init
       use m_AttrVect, only : AttrVect_zero => zero
 
       use m_List, only: List
       use m_List, only: List_nullify => nullify
       use m_List, only: List_init => init
       use m_List, only: List_nitem => nitem
       use m_List, only: List_clean => clean
 
       use m_stdio
       use m_die
 
       implicit none
INPUT PARAMETERS:
       character(len=*),      optional, intent(in)  :: iList
       integer, dimension(:), optional, intent(in)  :: iAction
       character(len=*),      optional, intent(in)  :: rList
       integer, dimension(:), optional, intent(in)  :: rAction
       integer,                         intent(in)  :: lsize
       integer,                         intent(in)  :: num_steps
       integer,               optional, intent(in)  :: steps_done
OUTPUT PARAMETERS:
       type(Accumulator),               intent(out) :: aC
REVISION HISTORY:
   11Sep00 - Jay Larson <[email protected]> - initial prototype
   27JUL01 - E.T. Ong <[email protected]> - added iAction, rAction,
             niAction, and nrAction to accumulator type. Also defined
             MCT_SUM and MCT_AVG for accumulator module.

14.1.2 inits_ - Initialize a simple Accumulator and its Registers

This routine allocates space for the output simple Accumulator argument aC, and sets the length of the Accumulator register buffer (defined by the input INTEGER argument lsize). If one wishes to accumulate integer fields, the list of these fields is defined by the input CHARACTER argument iList, which is specified as a colon-delimited set of substrings (further information regarding this is available in the routine init_() of the module m_AttrVect). If no value of iList is supplied, no integer attribute accumulation buffers will be allocated. The input argument rList define the names of the real variables to be accumulated. Finally, the user can manually set the number of completed steps in an accumulation cycle (e.g. for restart purposes) by supplying a value for the optional input INTEGER argument steps_done. Its default value is zero.

In a simple accumulator, the action is always SUM.


INTERFACE:

 
  subroutine inits_(aC, iList, rList, lsize,steps_done)
USES:
       use m_List, only : List_init => init
       use m_List, only : List_clean => clean
       use m_List, only : List_nitem => nitem
       use m_AttrVect, only : AttrVect_init => init
       use m_AttrVect, only : AttrVect_zero => zero
       use m_die
 
       implicit none
INPUT PARAMETERS:
       character(len=*),      optional, intent(in)  :: iList
       character(len=*),      optional, intent(in)  :: rList
       integer,                         intent(in)  :: lsize
       integer,               optional, intent(in)  :: steps_done
OUTPUT PARAMETERS:
       type(Accumulator),               intent(out) :: aC
REVISION HISTORY:
   10Jan08 - R. Jacob <[email protected]> - initial version based on init_

14.1.3 initp_ - Initialize an Accumulator but not its Registers

This routine is an internal service routine for use by the other initialization routines in this module. It sets up some--but not all--of the components of the output Accumulator argument aC. This routine can set up the following components of aC:

  1. aC%iAction, the array of accumlation actions for the integer attributes of aC (if the input INTEGER array argument iAction(:) is supplied);
  2. aC%rAction, the array of accumlation actions for the real attributes of aC (if the input INTEGER array argument rAction(:) is supplied);
  3. aC%num_steps, the number of steps in an accumulation cycle (if the input INTEGER argument num_steps is supplied); and
  4. aC%steps_done, the number of steps completed so far in an accumulation cycle (if the input INTEGER argument steps_done is supplied).


INTERFACE:

 
  subroutine initp_(aC, iAction, rAction, num_steps, steps_done)
USES:
       use m_die
 
       implicit none
INPUT PARAMETERS:
       integer, dimension(:), optional, intent(in)  :: iAction
       integer, dimension(:), optional, intent(in)  :: rAction
       integer,                         intent(in)  :: num_steps
       integer,               optional, intent(in)  :: steps_done
OUTPUT PARAMETERS:
       type(Accumulator),               intent(out) :: aC
REVISION HISTORY:
   11Sep00 - Jay Larson <[email protected]> - initial prototype
   27JUL01 - E.T. Ong <[email protected]> - added iAction, rAction,
             niAction, and nrAction to accumulator type. Also defined
             MCT_SUM and MCT_AVG for accumulator module.

14.1.4 initv_ - Initialize One Accumulator using Another

This routine takes the integer and real attribute information (including accumulation action settings for each attribute) from a previously initialized Accumulator (the input argument bC), and uses it to create another Accumulator (the output argument aC). In the absence of the INTEGER input arguments lsize, num_steps, and steps_done, aC will inherit from bC its length, the number of steps in its accumulation cycle, and the number of steps completed in its present accumulation cycle, respectively.


INTERFACE:

 
  subroutine initv_(aC, bC, lsize, num_steps, steps_done)
USES:
       use m_List,   only : List
       use m_List,   only : ListExportToChar => exportToChar
       use m_List,   only : List_copy        => copy
       use m_List,   only : List_allocated   => allocated
       use m_List,   only : List_clean       => clean
       use m_die
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator),           intent(in)  :: bC
       integer,           optional, intent(in)  :: lsize
       integer,           optional, intent(in)  :: num_steps
       integer,           optional, intent(in)  :: steps_done
OUTPUT PARAMETERS:
       type(Accumulator),           intent(out) :: aC
REVISION HISTORY:
   11Sep00 - Jay Larson <[email protected]> - initial prototype
   17May01 - R. Jacob <[email protected]> - change string_get to
             list_get
   27JUL01 - E.T. Ong <[email protected]> - added iaction,raction 
             compatibility
    2Aug02 - J. Larson <[email protected]> made argument num_steps
             optional

14.1.5 initavs_ - Initialize a simple Accumulator from an AttributeVector

This routine takes the integer and real attribute information (including from a previously initialized AttributeVector (the input argument aV), and uses it to create a simple (sum only) Accumulator (the output argument aC). In the absence of the INTEGER input argument lsize, aC will inherit from Av its length. In the absence of the optional INTEGER argument, steps_done will be set to zero.


INTERFACE:

 
  subroutine initavs_(aC, aV, acsize, steps_done)
USES:
       use m_AttrVect, only: AttrVect_lsize => lsize
       use m_AttrVect, only: AttrVect_nIAttr => nIAttr
       use m_AttrVect, only: AttrVect_nRAttr => nRAttr
       use m_AttrVect, only: AttrVect_exIL2c => exportIListToChar
       use m_AttrVect, only: AttrVect_exRL2c => exportRListToChar
       use m_die
 
       implicit none
INPUT PARAMETERS:
       type(AttrVect),           intent(in)     :: aV
       integer,           optional, intent(in)  :: acsize
       integer,           optional, intent(in)  :: steps_done
OUTPUT PARAMETERS:
       type(Accumulator),           intent(out) :: aC
REVISION HISTORY:
   10Jan08 - R. Jacob <[email protected]> - initial version based on initv_

14.1.6 clean_ - Destroy an Accumulator

This routine deallocates all allocated memory structures associated with the input/output Accumulator argument aC. The success (failure) of this operation is signified by the zero (non-zero) value of the optional INTEGER output argument stat. If clean_() is invoked with stat present, it is the user's obligation to check this return code and act accordingly. If stat is not supplied and any of the deallocation operations fail, this routine will terminate execution with an error statement.


INTERFACE:

 
  subroutine clean_(aC, stat)
USES:
       use m_mall
       use m_stdio
       use m_die
       use m_AttrVect, only : AttrVect_clean => clean
 
       implicit none
INPUT/OUTPUT PARAMETERS:
       type(Accumulator), intent(inout) :: aC
OUTPUT PARAMETERS:
       integer, optional, intent(out)   :: stat
REVISION HISTORY:
   11Sep00 - Jay Larson <[email protected]> - initial prototype
   27JUL01 - E.T. Ong <[email protected]> - deallocate pointers iAction
             and rAction.
    1Mar02 - E.T. Ong <[email protected]> removed the die to prevent
             crashes and added stat argument.

14.1.7 initialized_ - Check if an Accumulator is Initialized

This logical function returns a value of .TRUE. if the input Accumulator argument aC is initialized correctly. The term "correctly initialized" means there is internal consistency between the number of integer and real attributes in aC, and their respective data structures for accumulation registers, and accumulation action flags. The optional LOGICAL input argument die_flag if present, can result in messages written to stderr:

Otherwise, inconsistencies in how aC is set up will result in termination with an error message. The optional CHARACTER input argument source_name allows the user to, in the event of error, generate traceback information (e.g., the name of the routine that invoked this one).


INTERFACE:

 
  logical function initialized_(aC, die_flag, source_name)
USES:
 
    use m_stdio
    use m_die
    use m_List, only : List
    use m_List, only : List_allocated => allocated
 
    use m_AttrVect, only : AttrVect
    use m_AttrVect, only : Attr_nIAttr => nIAttr
    use m_AttrVect, only : Attr_nRAttr => nRAttr
 
    implicit none
INPUT PARAMETERS:
    type(Accumulator),          intent(in) :: aC
    logical,          optional, intent(in) :: die_flag
    character(len=*), optional, intent(in) :: source_name
REVISION HISTORY:
    7AUG01 - E.T. Ong <[email protected]> - initital prototype

14.1.8 lsize_ - Length of an Accumulator

This INTEGER query function returns the number of data points for which the input Accumulator argument aC is performing accumulation. This value corresponds to the length of the AttrVect component aC%data that stores the accumulation registers.


INTERFACE:

 
  integer function lsize_(aC)
USES:
       use m_AttrVect, only : AttrVect_lsize => lsize
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator), intent(in) :: aC
REVISION HISTORY:
   12Sep00 - Jay Larson <[email protected]> - initial prototype

14.1.9 NumSteps_ - Number of Accumulation Cycle Time Steps

This INTEGER query function returns the number of time steps in an accumulation cycle for the input Accumulator argument aC.


INTERFACE:

 
  integer function NumSteps_(aC)
USES:
       use m_die,   only : die
       use m_stdio, only : stderr
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator), intent(in) :: aC
REVISION HISTORY:
    7Aug02 - Jay Larson <[email protected]> - initial prototype

14.1.10 StepsDone_ - Number of Completed Steps in the Current Cycle

This INTEGER query function returns the of time steps that have been completed in the current accumulation cycle for the input Accumulator argument aC.


INTERFACE:

 
  integer function StepsDone_(aC)
USES:
       use m_die,   only : die
       use m_stdio, only : stderr
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator), intent(in) :: aC
REVISION HISTORY:
    7Aug02 - Jay Larson <[email protected]> - initial prototype

14.1.11 nIAttr_ - Return the Number of INTEGER Attributes

This INTEGER query function returns the number of integer attributes that are stored in the input Accumulator argument aC. This value is equal to the number of integer attributes in the AttrVect component aC%data that stores the accumulation registers.


INTERFACE:

 
  integer function nIAttr_(aC)
USES:
       use m_AttrVect, only : AttrVect_nIAttr => nIAttr
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator),intent(in) :: aC
REVISION HISTORY:
   12Sep00 - Jay Larson <[email protected]> - initial prototype

14.1.12 nRAttr_ - number of REAL fields stored in the Accumulator.

This INTEGER query function returns the number of real attributes that are stored in the input Accumulator argument aC. This value is equal to the number of real attributes in the AttrVect component aC%data that stores the accumulation registers.


INTERFACE:

 
  integer function nRAttr_(aC)
USES:
       use m_AttrVect, only : AttrVect_nRAttr => nRAttr
  
       implicit none
INPUT PARAMETERS:
       type(Accumulator),intent(in) :: aC
REVISION HISTORY:
   12Sep00 - Jay Larson <[email protected]> - initial prototype

14.1.13 getIList_ - Retrieve a Numbered INTEGER Attribute Name

This routine returns as a String (see the mpeu module m_String for information) the name of the ith item in the integer registers of the Accumulator argument aC.


INTERFACE:

 
  subroutine getIList_(item, ith, aC)
USES:
       use m_AttrVect, only : AttrVect_getIList => getIList
       use m_String,   only : String
 
       implicit none
INPUT PARAMETERS:
       integer,           intent(in)  :: ith
       type(Accumulator), intent(in)  :: aC
OUTPUT PARAMETERS:
       type(String),      intent(out) :: item
REVISION HISTORY:
   12Sep00 - Jay Larson <[email protected]> - initial prototype

14.1.14 getRList_ - Retrieve a Numbered REAL Attribute Name

This routine returns as a String (see the mpeu module m_String for information) the name of the ith item in the real registers of the Accumulator argument aC.


INTERFACE:

 
  subroutine getRList_(item, ith, aC)
USES:
       use m_AttrVect, only : AttrVect_getRList => getRList
       use m_String,   only : String
 
       implicit none
INPUT PARAMETERS:
       integer,          intent(in)  :: ith
       type(Accumulator),intent(in)  :: aC
OUTPUT PARAMETERS:
       type(String),     intent(out) :: item
REVISION HISTORY:
   12Sep00 - Jay Larson <[email protected]> - initial prototype

14.1.15 indexIA_ - Index an INTEGER Attribute

This INTEGER query function returns the index in the integer accumulation register buffer of the Accumulator argument aC the attribute named by the CHARACTER argument item. That is, all the accumulator running tallies for the attribute named item reside in

   aC%data%iAttr(indexIA_(aC,item),:).
  
The user may request traceback information (e.g., the name of the routine from which this one is called) by providing values for either of the optional CHARACTER arguments perrWith or dieWith In the event indexIA_() can not find item in aC, the routine behaves as follows:
  1. if neither perrWith nor dieWith are present, indexIA_() returns a value of zero;
  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.


INTERFACE:

 
  integer function indexIA_(aC, item, perrWith, dieWith)
USES:
       use m_AttrVect, only : AttrVect_indexIA => indexIA
       use m_die,  only : die
       use m_stdio,only : stderr
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator),          intent(in) :: aC
       character(len=*),           intent(in) :: item
       character(len=*), optional, intent(in) :: perrWith
       character(len=*), optional, intent(in) :: dieWith
REVISION HISTORY:
   14Sep00 - Jay Larson <[email protected]> - initial prototype

14.1.16 indexRA_ - index the Accumulator real attribute list.

This INTEGER query function returns the index in the real accumulation register buffer of the Accumulator argument aC the attribute named by the CHARACTER argument item. That is, all the accumulator running tallies for the attribute named item reside in

   aC%data%rAttr(indexRA_(aC,item),:).
  
The user may request traceback information (e.g., the name of the routine from which this one is called) by providing values for either of the optional CHARACTER arguments perrWith or dieWith In the event indexRA_() can not find item in aC, the routine behaves as follows:
  1. if neither perrWith nor dieWith are present, indexRA_() returns a value of zero;
  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.


INTERFACE:

 
  integer function indexRA_(aC, item, perrWith, dieWith)
USES:
       use m_AttrVect, only : AttrVect_indexRA => indexRA
       use m_die,  only : die
       use m_stdio,only : stderr
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator),          intent(in) :: aC
       character(len=*),           intent(in) :: item
       character(len=*), optional, intent(in) :: perrWith
       character(len=*), optional, intent(in) :: dieWith
REVISION HISTORY:
   	14Sep00 - Jay Larson <[email protected]> - initial prototype

14.1.17 exportIAttr_ - Export INTEGER Attribute to a Vector

This routine extracts from the input Accumulator argument aC 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 Accumulator List component aC%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) at the time 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_(aC, AttrTag, outVect, lsize)
USES:
       use m_die 
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_exportIAttr => exportIAttr
 
       implicit none
INPUT PARAMETERS:
 
       type(Accumulator),      intent(in)  :: aC
       character(len=*),       intent(in)  :: AttrTag
OUTPUT PARAMETERS:
 
       integer,  dimension(:), pointer     :: outVect
       integer,  optional,     intent(out) :: lsize
REVISION HISTORY:
 
    6May02 - J.W. Larson <[email protected]> - initial prototype.

14.1.18 exportRAttrSP_ - Export REAL Attribute to a Vector

This routine extracts from the input Accumulator argument aC 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 Accumulator List component aC%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) at the time 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_(aC, AttrTag, outVect, lsize)
USES:
       use m_die 
       use m_stdio
 
       use m_AttrVect,      only : AttrVect_exportRAttr => exportRAttr
 
       implicit none
INPUT PARAMETERS:
 
       type(Accumulator),      intent(in)  :: aC
       character(len=*),       intent(in)  :: AttrTag
OUTPUT PARAMETERS:
 
       real(SP), dimension(:), pointer     :: outVect
       integer,  optional,     intent(out) :: lsize
REVISION HISTORY:
    6May02 - J.W. Larson <[email protected]> - initial prototype.

14.1.19 importIAttr_ - Import INTEGER Attribute from a Vector

This routine imports data provided in the input INTEGER vector inVect into the Accumulator argument aC, 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 Accumulator to store the data.

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


INTERFACE:

 
  subroutine importIAttr_(aC, AttrTag, inVect, lsize)
USES:
       use m_die
       use m_stdio ,        only : stderr
 
       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(Accumulator),      intent(inout) :: aC
REVISION HISTORY:
    6May02 - J.W. Larson <[email protected]> - initial prototype.

14.1.20 importRAttrSP_ - Import REAL Attribute from a Vector

This routine imports data provided in the input REAL vector inVect into the Accumulator argument aC, 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 Accumulator to store the data.

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


INTERFACE:

 
  subroutine importRAttrSP_(aC, AttrTag, inVect, lsize)
USES:
       use m_die 
       use m_stdio ,        only : stderr
 
       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(Accumulator),      intent(inout) :: aC
REVISION HISTORY:
    6May02 - J.W. Larson <[email protected]> - initial prototype.

14.1.21 zero_ - Zero an Accumulator

This subroutine clears the the Accumulator argument aC. This is accomplished by setting the number of completed steps in the accumulation cycle to zero, and zeroing out all of the accumlation registers.


INTERFACE:

 
  subroutine zero_(aC)
USES:
       use m_AttrVect, only : AttrVect_zero => zero
 
       implicit none
INPUT/OUTPUT PARAMETERS:
       type(Accumulator), intent(inout) :: aC
REVISION HISTORY:
    7Aug02 - Jay Larson <[email protected]> - initial prototype

14.1.22 aCaCSharedAttrIndexList_ - Cross-index Two Accumulators

aCaCSharedAttrIndexList_() takes a pair of user-supplied Accumulator variables aC1 and aC2, and for choice of either REAL or INTEGER attributes (as specified literally in the input CHARACTER argument attrib) returns the number of shared attributes NumShared, and arrays of indices Indices1 and Indices2 to their storage locations in aC1 and aC2, respectively.

N.B.: This routine returns two allocated arrays--Indices1(:) and Indices2(:)--which must be deallocated once the user no longer needs them. Failure to do this will create a memory leak.


INTERFACE:

 
  subroutine aCaCSharedAttrIndexList_(aC1, aC2, attrib, NumShared, &
                                      Indices1, Indices2)
USES:
       use m_stdio
       use m_die,         only : MP_perr_die, die, warn
 
       use m_List,     only : GetSharedListIndices
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator),    intent(in)  :: aC1   
       type(Accumulator),    intent(in)  :: aC2
       character*7,          intent(in)  :: attrib
OUTPUT PARAMETERS:
       integer,              intent(out) :: NumShared
       integer,dimension(:), pointer     :: Indices1
       integer,dimension(:), pointer     :: Indices2
REVISION HISTORY:
    7Feb01 - J.W. Larson <[email protected]> - initial version

14.1.23 aVaCSharedAttrIndexList_ - Cross-index with an AttrVect

aVaCSharedAttrIndexList_() a user-supplied AttrVect variable aV and an Accumulator variable aC, and for choice of either REAL or INTEGER attributes (as ! specified literally in the input CHARACTER argument attrib) returns the number of shared attributes NumShared, and arrays of indices Indices1 and Indices2 to their storage locations in aV and aC, respectively.

N.B.: This routine returns two allocated arrays--Indices1(:) and Indices2(:)--which must be deallocated once the user no longer needs them. Failure to do this will create a memory leak.


INTERFACE:

 
  subroutine aVaCSharedAttrIndexList_(aV, aC, attrib, NumShared, &
                                      Indices1, Indices2)
USES:
       use m_stdio
       use m_die,         only : MP_perr_die, die, warn
 
       use m_AttrVect,    only : AttrVect
 
       use m_List,     only : GetSharedListIndices
 
  
       implicit none
INPUT PARAMETERS:
       type(AttrVect),       intent(in)  :: aV   
       type(Accumulator),    intent(in)  :: aC
       character(len=*),     intent(in)  :: attrib
OUTPUT PARAMETERS:
       integer,              intent(out) :: NumShared
       integer,dimension(:), pointer     :: Indices1
       integer,dimension(:), pointer     :: Indices2
REVISION HISTORY:
    7Feb01 - J.W. Larson <[email protected]> - initial version

14.1.24 accumulate_-Acumulate from an AttrVect to an Accumulator.

This routine performs time accumlation of data present in an MCT field data AttrVect variable aV and combines it with the running tallies stored in the MCT Accumulator variable aC. This routine automatically identifies which fields are held in common by aV and aC and uses the accumulation action information stored in aC to decide how each field in aV is to be combined into its corresponding running tally in aC. The accumulation operations currently supported are:

This routine also automatically increments the counter in aC signifying the number of steps completed in the accumulation cycle.

NOTE: The user must reset (zero) the Accumulator after the average has been formed or the next call to accumulate will add to the average.


INTERFACE:

 
  subroutine accumulate_(aV, aC)
USES:
       use m_stdio, only : stdout,stderr
       use m_die,   only : die
 
       use m_AttrVect, only : AttrVect
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_nIAttr => nIAttr
       use m_AttrVect, only : AttrVect_nRAttr => nRAttr
       use m_AttrVect, only : AttrVect_indexRA => indexRA
       use m_AttrVect, only : AttrVect_indexIA => indexIA
 
       implicit none
INPUT PARAMETERS:
       type(AttrVect),     intent(in)    :: aV      ! Input AttrVect
INPUT/OUTPUT PARAMETERS:
       type(Accumulator),  intent(inout) :: aC      ! Output Accumulator
REVISION HISTORY:
   18Sep00 - J.W. Larson <[email protected]> -- initial version.
    7Feb01 - J.W. Larson <[email protected]> -- General version.
   10Jun01 - E.T. Ong -- fixed divide-by-zero problem in integer
             attribute accumulation.
   27Jul01 - E.T. Ong <[email protected]> -- removed action argument.
             Make compatible with new Accumulator type.

14.1.25 average_ - Force an average to be taken on an Accumulator

This routine will compute the average of the current values in an Accumulator using the current value of steps_done in the Accumulator


INTERFACE:

 
  subroutine average_(aC)
USES:
       use m_stdio, only : stdout,stderr
       use m_die,   only : die
 
       use m_AttrVect, only : AttrVect
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_nIAttr => nIAttr
       use m_AttrVect, only : AttrVect_nRAttr => nRAttr
       use m_AttrVect, only : AttrVect_indexRA => indexRA
       use m_AttrVect, only : AttrVect_indexIA => indexIA
 
       implicit none
INPUT/OUTPUT PARAMETERS:
       type(Accumulator),  intent(inout) :: aC      ! Output Accumulator
REVISION HISTORY:
   11Jan08 - R.Jacob <[email protected]> -- initial version based on accumulate_


14.2 Module m_AccumulatorComms - MPI Communication Methods for the Accumulator (Source File: m_AccumulatorComms.F90)

This module contains communications methods for the Accumulator datatype (see m_Accumulator for details). MCT's communications are implemented in terms of the Message Passing Interface (MPI) standard, and we have as best as possible, made the interfaces to these routines appear as similar as possible to the corresponding MPI routines. For the Accumulator, we currently support only the following collective operations: broadcast, gather, and scatter. The gather and scatter operations rely on domain decomposition descriptors that are defined elsewhere in MCT: the GlobalMap, which is a one-dimensional decomposition (see the MCT module m_GlobalMap for more details); and the GlobalSegMap, which is a segmented decomposition capable of supporting multidimensional domain decompositions (see the MCT module m_GlobalSegMap for more details).


INTERFACE:

 
  module m_AccumulatorComms
USES:
   No external modules are used in the declaration section of this module.
 
       implicit none
 
       private	! except
PUBLIC MEMBER FUNCTIONS:
   List of communications Methods for the Accumulator class
 
       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
 
   Definition of interfaces for the communication methods for 
   the Accumulator:
 
     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
REVISION HISTORY:
   31Oct00 - Jay Larson <[email protected]> - initial prototype--
             These routines were separated from the module m_Accumulator
   15Jan01 - Jay Larson <[email protected]> - Specification of 
             APIs for the routines GSM_gather_() and GSM_scatter_().
   10May01 - Jay Larson <[email protected]> - Changes in the
             comms routine to match the MPI model for collective
             communications, and general clean-up of prologues.
    9Aug01 - E.T. Ong <[email protected]> - Added private routine
             bcastp_. Used new Accumulator routines initp_ and 
             initialized_ to simplify the routines.
    26Aug02 - E.T. Ong <[email protected]> - thourough code revision; 
              no added routines

14.2.1 GM_gather_ - Gather Accumulator Distributed by a GlobalMap

GM_gather() takes a distributed (across the communicator associated with the handle comm) input Accumulator argument iC and gathers its data to the Accumulator oC on the root. The decomposition of iC is described by the input GlobalMap argument Gmap. The success (failure) of this operation is signified by the zero (nonzero) value of the optional output argument stat.


INTERFACE:

 
  subroutine GM_gather_(iC, oC, GMap, root, comm, stat)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GlobalMap, only : GlobalMap
       use m_AttrVect, only : AttrVect_clean => clean
       use m_Accumulator, only : Accumulator
       use m_Accumulator, only : Accumulator_initialized => initialized
       use m_Accumulator, only : Accumulator_initv => init
       use m_AttrVectComms, only : AttrVect_gather => gather
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator), intent(in)  :: iC
       type(GlobalMap) ,  intent(in)  :: GMap
       integer,           intent(in)  :: root
       integer,           intent(in)  :: comm
OUTPUT PARAMETERS:
       type(Accumulator), intent(out) :: oC
       integer, optional,intent(out)  :: stat
REVISION HISTORY:
   13Sep00 - Jay Larson <[email protected]> - initial prototype
   31Oct00 - Jay Larson <[email protected]> - relocated to the
             module m_AccumulatorComms
   15Jan01 - Jay Larson <[email protected]> - renamed GM_gather_
   10May01 - Jay Larson <[email protected]> - revamped comms 
             model to match MPI comms model, and cleaned up prologue
    9Aug01 - E.T. Ong <[email protected]> - 2nd prototype. Used the 
             intiialized_ and accumulator init routines.

14.2.2 GSM_gather_ - Gather Accumulator Distributed by a GlobalSegMap

This routine takes the distrubuted (on the communcator associated with the handle comm) input Accumulator argument iC gathers it to the the Accumulator argument oC (valid only on the root). The decompositon of iC is contained in the input GlobalSegMap argument GSMap. The success (failure) of this operation is signified by the zero (nonzero) returned value of the INTEGER flag stat.


INTERFACE:

 
  subroutine GSM_gather_(iC, oC, GSMap, root, comm, stat)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GlobalSegMap, only : GlobalSegMap
       use m_AttrVect, only : AttrVect_clean => clean
       use m_Accumulator, only : Accumulator
       use m_Accumulator, only : Accumulator_initv => init
       use m_Accumulator,   only : Accumulator_initialized => initialized
       use m_AttrVectComms, only : AttrVect_gather => gather
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator),  intent(in) :: iC
       type(GlobalSegMap), intent(in) :: GSMap
       integer,            intent(in) :: root
       integer,            intent(in) :: comm
OUTPUT PARAMETERS:
       type(Accumulator), intent(out) :: oC
       integer, optional, intent(out) :: stat
REVISION HISTORY:
   	15Jan01 - Jay Larson <[email protected]> - API specification.
   	10May01 - Jay Larson <[email protected]> - Initial code and
                   cleaned up prologue.
         09Aug01 - E.T. Ong <[email protected]> - 2nd prototype. Used the 
                   intiialized_ and accumulator init routines.

14.2.3 GM_scatter_ - Scatter an Accumulator using a GlobalMap

This routine takes the input Accumulator argument iC (valid only on the root), and scatters it to the distributed Accumulator argument oC on the processes associated with the communicator handle comm. The decompositon used to scatter the data is contained in the input GlobalMap argument GMap. The success (failure) of this operation is signified by the zero (nonzero) returned value of the INTEGER flag stat.


INTERFACE:

 
  subroutine GM_scatter_(iC, oC, GMap, root, comm, stat)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GlobalMap,   only : GlobalMap
       use m_Accumulator, only : Accumulator
       use m_Accumulator, only : Accumulator_initv => init
       use m_Accumulator, only : Accumulator_initialized => initialized
       use m_AttrVect, only : AttrVect_clean => clean
       use m_AttrVectComms, only : AttrVect_scatter => scatter
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator), intent(in)  :: iC
       type(GlobalMap),   intent(in)  :: GMap
       integer,           intent(in)  :: root
       integer,           intent(in)  :: comm
OUTPUT PARAMETERS:
       type(Accumulator), intent(out) :: oC
       integer, optional, intent(out) :: stat
REVISION HISTORY:
   	14Sep00 - Jay Larson <[email protected]> - initial prototype
   	31Oct00 - Jay Larson <[email protected]> - moved from the module
                   m_Accumulator to m_AccumulatorComms
   	15Jan01 - Jay Larson <[email protected]> - renamed GM_scatter_.
         10May01 - Jay Larson <[email protected]> - revamped code to fit
                   MPI-like comms model, and cleaned up prologue.
         09Aug01 - E.T. Ong <[email protected]> - 2nd prototype. Used the  
                   initialized_, Accumulator init_, and bcastp_ routines.

14.2.4 GSM_scatter_ - Scatter an Accumulator using a GlobalSegMap

This routine takes the input Accumulator argument iC (valid only on the root), and scatters it to the distributed Accumulator argument oC on the processes associated with the communicator handle comm. The decompositon used to scatter the data is contained in the input GlobalSegMap argument GSMap. The success (failure) of this operation is signified by the zero (nonzero) returned value of the INTEGER flag stat.


INTERFACE:

 
  subroutine GSM_scatter_(iC, oC, GSMap, root, comm, stat)
USES:
       use m_stdio
       use m_die
       use m_mpif90
 
       use m_GlobalSegMap, only : GlobalSegMap
       use m_Accumulator, only : Accumulator
       use m_Accumulator, only : Accumulator_initv => init
       use m_Accumulator, only : Accumulator_initialized => initialized
       use m_AttrVect, only : AttrVect_clean => clean
       use m_AttrVectComms, only : AttrVect_scatter => scatter
 
       implicit none
INPUT PARAMETERS:
       type(Accumulator),  intent(in)  :: iC
       type(GlobalSegMap), intent(in)  :: GSMap
       integer,            intent(in)  :: root
       integer,            intent(in)  :: comm
OUTPUT PARAMETERS:
       type(Accumulator),  intent(out) :: oC
       integer, optional,  intent(out) :: stat
REVISION HISTORY:
   	15Jan01 - Jay Larson <[email protected]> - API specification.
   	10May01 - Jay Larson <[email protected]> - Initial code/prologue
         09Aug01 - E.T. Ong <[email protected]> 2nd prototype. Used the
                   initialized and accumulator init routines.

14.2.5 bcast_ - Broadcast an Accumulator

This routine takes the input Accumulator argument aC (on input valid only on the root), and broadcasts it to all the processes associated with the communicator handle comm. The success (failure) of this operation is signified by the zero (nonzero) returned value of the INTEGER flag stat.


INTERFACE:

  subroutine bcast_(aC, root, comm, stat)
USES:
       use m_die
       use m_mpif90
       use m_AttrVectComms, only : AttrVect_bcast => bcast
 
       use m_Accumulator, only : Accumulator
       use m_Accumulator, only : Accumulator_initialized => initialized
 
       implicit none
INPUT PARAMETERS:
       integer,intent(in) :: root
       integer,intent(in) :: comm
INPUT/OUTPUT PARAMETERS:
       type(Accumulator), intent(inout) :: aC ! (IN) on root, (OUT) elsewhere
OUTPUT PARAMETERS:
       integer, optional, intent(out)   :: stat
REVISION HISTORY:
   	14Sep00 - Jay Larson <[email protected]> - initial prototype
   	31Oct00 - Jay Larson <[email protected]> - moved from the module
                   m_Accumulator to m_AccumulatorComms
         09May01 - Jay Larson <[email protected]> - cleaned up prologue
         09Aug01 - E.T. Ong <[email protected]> - 2nd prototype. Made use of
                   bcastp_ routine. Also more argument checks.

14.2.6 bcastp_ - Broadcast an Accumulator (but Not its Registers)

This routine broadcasts all components of the accumulator aC except for aCto be used by accumulator scatter and gather routines.


INTERFACE:

  subroutine bcastp_(aC, root, comm, stat)
USES:
       use m_die
       use m_mpif90
       use m_AttrVectComms, only : AttrVect_bcast => bcast
       use m_Accumulator, only : Accumulator
       use m_Accumulator, only : Accumulator_initp => initp
       use m_Accumulator, only : Accumulator_nIAttr => nIAttr
       use m_Accumulator, only : Accumulator_nRAttr => nRAttr
 
       implicit none
INPUT PARAMETERS:
       integer,intent(in) :: root
       integer,intent(in) :: comm
INPUT/OUTPUT PARAMETERS:
       type(Accumulator), intent(inout) :: aC ! (IN) on root, (OUT) elsewhere
OUTPUT PARAMETERS:
       integer, optional, intent(out)   :: stat
REVISION HISTORY:
         09Aug01 - E.T. Ong <[email protected]> - initial prototype



next up previous contents
Next: 15 Global To Local Up: 2 High Level API's Previous: 13 Merging of Flux   Contents
[email protected]