next up previous contents
Next: 14 Time Averaging Up: 2 High Level API's Previous: 12 Spatial Integration and   Contents

Subsections

13 Merging of Flux and State Data from Multiple Sources

13.1 Module m_Merge - Merge flux and state data from multiple sources. (Source File: m_Merge.F90)

This module supports merging of state and flux data from multiple components with overlapping spatial domains for use by another component. For example, let the vectors ${\bf a}$ and ${\bf b}$ be data from Components $A$ and $B$ that have been interpolated onto the physical grid of another component $C$. We wish to combine the data from $A$ and $B$ to get a vector ${\bf c}$, which represents the merged data on the grid of component $C$. This merge process is an element-by-element masked weighted average:

\begin{displaymath}c_i = {{{{\prod_{j=1}^J} M_{i}^j} {{\prod_{k=1}^K} F_{i}^k} a...
...^k} +
{{\prod_{p=1}^P} N_{i}^p} {{\prod_{q=1}^Q} G_{i}^q}}}, \end{displaymath}

Where ${M_{i}^j}$ and ${N_{i}^p}$ are integer masks (which have value either $0$ or $1$), and ${F_{i}^k}$ and ${G_{i}^q}$ are real masks (which are in the closed interval $[0,1]$).

Currently, we assume that the integer and real masks are stored in the same GeneralGrid datatype. We also assume-and this is of critical importance to the user-that the attributes to be merged are the same for all the inputs and output. If the user violates this assumption, incorrect merges will occur for any attributes that are present in only some (that is not all) of the inputs.

This module supports explicitly the merging data from two, three, and four components. There is also a routine named MergeInData that allows the user to construct other merging schemes.


INTERFACE:

 
  module m_Merge
USES:
       No other modules used in the declaration section of this module.
 
       implicit none
 
       private   ! except
PUBLIC TYPES:
 
       None.
PUBLIC MEMBER FUNCTIONS:
 
       public :: MergeTwo      ! Merge Output from two components
                               ! for use by a third.
       public :: MergeThree    ! Merge Output from three components
                               ! for use by a fourth.
       public :: MergeFour     ! Merge Output from four components
                               ! for use by a fifth.
       public :: MergeInData   ! Merge in data from a single component.
 
     interface MergeTwo ; module procedure &
          MergeTwoGGSP_, &
          MergeTwoGGDP_
     end interface
     interface MergeThree ; module procedure &
          MergeThreeGGSP_, &
 	 MergeThreeGGDP_
     end interface
     interface MergeFour ; module procedure &
          MergeFourGGSP_, &
          MergeFourGGDP_
     end interface
     interface MergeInData ; module procedure &
          MergeInDataGGSP_, &
          MergeInDataGGDP_
     end interface
PUBLIC DATA MEMBERS:
 
       None.
REVISION HISTORY:
         19Jun02 - J.W. Larson <[email protected]> - Initial version.

13.1.1 MergeTwoGGSP_ - Merge Data from Two Sources

This routine merges REAL attribute data from two input AttrVect arguments inAv1 and inAv2 to a third AttrVect outAv. The attributes to be merged are determined entirely by the real attributes of outAv. If outAv shares one or more attributes with either of the inputs inAv1 or inAv2, a merge is performed on the individual intersections of attributes between the pairs $({\tt outAv},
{\tt inAv1})$ and $({\tt outAv},
{\tt inAv1})$. Currently, it is assumed that these pairwise intersections are all equal. This assumption is of critical importance to the user. If the user violates this assumption, incorrect merges of attributes that are present in some (but not all) of the inputs will result.

The merge operatrion is a masked weighted element-by-element sum, as outlined in the following example. Let the vectors ${\bf a}$ and ${\bf b}$ be data from Components $A$ and $B$ that have been interpolated onto the physical grid of another component $C$. We wish to combine the data from $A$ and $B$ to get a vector ${\bf c}$, which represents the merged data on the grid of component $C$. The merge relation to obtain the $i$th element of c is

\begin{displaymath}c_i = {1 \over {W_i}} \bigg\{ {{\prod_{j=1}^J} \kappa_{i}^j} ...
...\lambda_{i}^l}
{{\prod_{m=1}^M} \beta_{i}^m} {b_i} \bigg\} , \end{displaymath}

where

\begin{displaymath}{W_i} = {{\prod_{j=1}^J} \kappa_{i}^j} {{\prod_{k=1}^K} \alph...
...{{\prod_{l=1}^L} \lambda_{i}^l} {{\prod_{m=1}^M} \beta_{i}^m}. \end{displaymath}

The quantities ${\kappa_{i}^j}$ and ${\lambda_{i}^l}$ are integer masks (which have value either $0$ or $1$), and ${\alpha_{i}^k}$ and ${\beta_{i}^m}$ are real masks (which are in the closed interval $[0,1]$).

The integer and real masks are stored as attributes to the same input GeneralGrid argument GGrid. The mask attribute names are stored as substrings to the colon-separated strings contained in the input CHARACTER arguments iMaskTags1, iMaskTags2, rMaskTags1, and rMaskTags2. The LOGICAL input argument CheckMasks governs how the masks are applied. If ${\tt CheckMasks} = {\tt .TRUE.}$, the entries are checked to ensure they meet the definitions of real and integer masks. If ${\tt CheckMasks} = {\tt .TRUE.}$ then the masks are multiplied together on an element-by-element basis with no validation of their entries (this option results in slightly higher performance).

This routine returns the sume of the masked weights as a diagnostic. This quantity is returned in the output REAL array WeightSum.

The correspondence between the quantities in the above merge relation and the arguments to this routine are summarized in the table.

Quantity Stored in Referenced by
  Argument Argument
$ {a_i} $ inAv1  
$ {b_i} $ inAv2  
$ {c_i} $ outAv  
$ {\kappa_i^j}, j=1,\ldots,J $ GGrid iMaskTags1
    ($J$ items)
$ {\alpha_i^k}, k=1,\ldots,K $ GGrid rMaskTags1
    ($K$ items)
$ {\lambda_i^l}, l=1,\ldots,L $ GGrid iMaskTags2
    ($L$ items)
$ {\beta_i^m}, m=1,\ldots,M $ GGrid rMaskTags2
    ($M$ items)
$ {W_i} $ WeightSum  


INTERFACE:

 
  subroutine MergeTwoGGSP_(inAv1, iMaskTags1, rMaskTags1, &
                         inAv2, iMaskTags2, rMaskTags2, &
                         GGrid, CheckMasks, outAv, WeightSum)
USES:
       use m_stdio
       use m_die
 
       use m_realkinds, only : SP, FP
 
       use m_List, only : List
       use m_List, only : List_allocated => allocated
 
       use m_AttrVect, only : AttrVect
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_nRAttr => nRAttr
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
 
       implicit none
INPUT PARAMETERS:
       type(AttrVect),               intent(IN)    :: inAv1
       character(len=*),   optional, intent(IN)    :: iMaskTags1
       character(len=*),   optional, intent(IN)    :: rMaskTags1
       type(AttrVect),               intent(IN)    :: inAv2
       character(len=*),   optional, intent(IN)    :: iMaskTags2
       character(len=*),   optional, intent(IN)    :: rMaskTags2
       type(GeneralGrid),            intent(IN)    :: GGrid
       logical,                      intent(IN)    :: CheckMasks
INPUT/OUTPUT PARAMETERS:
       type(AttrVect),               intent(INOUT) :: outAv
       real(SP),       dimension(:), pointer       :: WeightSum
REVISION HISTORY:
         19Jun02 - Jay Larson <[email protected]> - Interface spec.
          3Jul02 - Jay Larson <[email protected]> - Implementation.
         10Jul02 - J. Larson <[email protected]> - Improved argument 
                   checking.

13.1.2 MergeThreeGGSP_ - Merge Data from Three Sources

This routine merges REAL attribute data from three input AttrVect arguments inAv1 , inAv2, and inAv3 to a fourth AttrVect outAv. The attributes to be merged are determined entirely by the real attributes of outAv. If outAv shares one or more attributes with any of the inputs inAv1, inAv2, or inAv3, a merge is performed on the individual intersections of attributes between the pairs $({\tt outAv},
{\tt inAv1})$, $({\tt outAv},{\tt inAv2})$, and $({\tt outAv},{\tt inAv3})$. Currently, it is assumed that these pairwise intersections are all equal. This assumption is of critical importance to the user. If the user violates this assumption, incorrect merges of any attributes present only in some (but not all) inputs will result.

The merge operatrion is a masked weighted element-by-element sum, as outlined in the following example. Let the vectors ${\bf a}$,${\bf b}$, and ${\bf c}$ be data from Components $A$, $B$, and $C$ that have been interpolated onto the physical grid of another component $D$. We wish to combine the data from $A$, $B$ and $C$ to get a vector ${\bf d}$, which represents the merged data on the grid of component $D$. The merge relation to obtain the $i$th element of ${\bf d}$ is

\begin{displaymath}d_i = {1 \over {W_i}} \bigg\{ {{\prod_{j=1}^J} \kappa_{i}^j} ...
...P} \mu_{i}^p}
{{\prod_{q=1}^Q} \gamma_{i}^q} {c_i} \bigg\} , \end{displaymath}

where

\begin{displaymath}{W_i} = {{\prod_{j=1}^J} \kappa_{i}^j} {{\prod_{k=1}^K} \alph...
...
{{\prod_{p=1}^P} \mu_{i}^p} {{\prod_{q=1}^Q} \gamma_{i}^q}. \end{displaymath}

The quantities ${\kappa_{i}^j}$, ${\lambda_{i}^p}$, and ${\mu_{i}^p}$ are integer masks (which have value either $0$ or $1$), and ${\alpha_{i}^k}$, ${\beta_{i}^m}$, and ${\gamma_{i}^q}$ are real masks (which are in the closed interval $[0,1]$).

The integer and real masks are stored as attributes to the same input GeneralGrid argument GGrid. The mask attribute names are stored as substrings to the colon-separated strings contained in the input CHARACTER arguments iMaskTags1, iMaskTags2, iMaskTags3, rMaskTags1, rMaskTags2, and rMaskTags3. The LOGICAL input argument CheckMasks governs how the masks are applied. If ${\tt CheckMasks} = {\tt .TRUE.}$, the entries are checked to ensure they meet the definitions of real and integer masks. If ${\tt CheckMasks} = {\tt .FALSE.}$ then the masks are multiplied together on an element-by-element basis with no validation of their entries (this option results in slightly higher performance).

This routine returns the sum of the masked weights as a diagnostic. This quantity is returned in the output REAL array WeightSum.

The correspondence between the quantities in the above merge relation and the arguments to this routine are summarized in the table.

Quantity Stored in Referenced by
  Argument Argument
$ {a_i} $ inAv1  
$ {b_i} $ inAv2  
$ {c_i} $ inAv3  
$ {d_i} $ outAv  
$ {\kappa_i^j}, j=1,\ldots,J $ GGrid iMaskTags1
    ($J$ items)
$ {\alpha_i^k}, k=1,\ldots,K $ GGrid rMaskTags1
    ($K$ items)
$ {\lambda_i^l}, l=1,\ldots,L $ GGrid iMaskTags2
    ($L$ items)
$ {\beta_i^m}, m=1,\ldots,M $ GGrid rMaskTags2
    ($M$ items)
$ {\mu_i^p}, p=1,\ldots,P $ GGrid iMaskTags3
    ($L$ items)
$ {\gamma_i^q}, q=1,\ldots,Q $ GGrid rMaskTags3
    ($M$ items)
$ {W_i} $ WeightSum  


INTERFACE:

 
  subroutine MergeThreeGGSP_(inAv1, iMaskTags1, rMaskTags1, &
                             inAv2, iMaskTags2, rMaskTags2, &
                             inAv3, iMaskTags3, rMaskTags3, &
                             GGrid, CheckMasks, outAv, WeightSum)
USES:
       use m_stdio
       use m_die
 
       use m_realkinds, only : SP, FP
 
       use m_List, only : List
       use m_List, only : List_allocated => allocated
 
       use m_AttrVect, only : AttrVect
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_nRAttr => nRAttr
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
 
       implicit none
INPUT PARAMETERS:
       type(AttrVect),               intent(IN)    :: inAv1
       character(len=*),   optional, intent(IN)    :: iMaskTags1
       character(len=*),   optional, intent(IN)    :: rMaskTags1
       type(AttrVect),               intent(IN)    :: inAv2
       character(len=*),   optional, intent(IN)    :: iMaskTags2
       character(len=*),   optional, intent(IN)    :: rMaskTags2
       type(AttrVect),               intent(IN)    :: inAv3
       character(len=*),   optional, intent(IN)    :: iMaskTags3
       character(len=*),   optional, intent(IN)    :: rMaskTags3
       type(GeneralGrid),            intent(IN)    :: GGrid
       logical,                      intent(IN)    :: CheckMasks
INPUT/OUTPUT PARAMETERS:
       type(AttrVect),               intent(INOUT) :: outAv
       real(SP),       dimension(:), pointer       :: WeightSum
REVISION HISTORY:
         19Jun02 - Jay Larson <[email protected]> - Interface spec.
          3Jul02 - Jay Larson <[email protected]> - Implementation.
         10Jul02 - J. Larson <[email protected]> - Improved argument 
                   checking.

13.1.3 MergeFourGGSP_ - Merge Data from Four Sources

This routine merges REAL attribute data from four input AttrVect arguments inAv1 , inAv2, inAv3, and inAv4 to a fifth AttrVect outAv. The attributes to be merged are determined entirely by the real attributes of outAv. If outAv shares one or more attributes with any of the inputs inAv1, inAv2, inAv3, or inAv4, a merge is performed on the individual intersections of attributes between the pairs $({\tt outAv},
{\tt inAv1})$, $({\tt outAv},{\tt inAv2})$, $({\tt outAv},{\tt inAv3})$, and $({\tt outAv},{\tt inAv3})$. Currently, it is assumed that these pairwise intersections are all equal. This assumption is of critical importance to the user. If the user violates this assumption, incorrect merges of any attributes present only in some (but not all) the inputs will result.

The merge operatrion is a masked weighted element-by-element sum, as outlined in the following example. Let the vectors ${\bf a}$,${\bf b}$, ${\bf c}$ and ${\bf d}$ be data from Components $A$, $B$, $C$, and $D$ that have been interpolated onto the physical grid of another component $E$. We wish to combine the data from $A$, $B$, $C$, and $D$ to get a vector ${\bf e}$, which represents the merged data on the grid of component $E$. The merge relation to obtain the $i$th element of e is

\begin{displaymath}e_i = {1 \over {W_i}} \bigg\{ {{\prod_{j=1}^J} \kappa_{i}^j} ...
...}^R} \nu_{i}^r} {{\prod_{s=1}^S} \delta_{i}^s} {d_i} \bigg\} , \end{displaymath}

where

\begin{displaymath}{W_i} = {{\prod_{j=1}^J} \kappa_{i}^j} {{\prod_{k=1}^K} \alph...
...
{{\prod_{r=1}^R} \nu_{i}^r} {{\prod_{s=1}^S} \delta_{i}^s}. \end{displaymath}

The quantities ${\kappa_{i}^j}$, ${\lambda_{i}^p}$, ${\mu_{i}^p}$, and ${\nu_{i}^r}$ are integer masks (which have value either $0$ or $1$), and ${\alpha_{i}^k}$, ${\beta_{i}^m}$, ${\gamma_{i}^q}$, and ${\delta_{i}^s}$ are real masks (which are in the closed interval $[0,1]$).

The integer and real masks are stored as attributes to the same input GeneralGrid argument GGrid. The mask attribute names are stored as substrings to the colon-separated strings contained in the input CHARACTER arguments iMaskTags1, iMaskTags2, iMaskTags3, iMaskTags4, rMaskTags1, and rMaskTags2, rMaskTags3, and rMaskTags4, . The LOGICAL input argument CheckMasks governs how the masks are applied. If ${\tt CheckMasks} = {\tt .TRUE.}$, the entries are checked to ensure they meet the definitions of real and integer masks. If ${\tt CheckMasks} = {\tt .FALSE.}$ then the masks are multiplied together on an element-by-element basis with no validation of their entries (this option results in slightly higher performance).

This routine returns the sume of the masked weights as a diagnostic. This quantity is returned in the output REAL array WeightSum.

The correspondence between the quantities in the above merge relation and the arguments to this routine are summarized in the table.

Quantity Stored in Referenced by
  Argument Argument
$ {a_i} $ inAv1  
$ {b_i} $ inAv2  
$ {c_i} $ inAv3  
$ {d_i} $ inAv4  
$ {e_i} $ outAv  
$ {\kappa_i^j}, j=1,\ldots,J $ GGrid iMaskTags1
    ($J$ items)
$ {\alpha_i^k}, k=1,\ldots,K $ GGrid rMaskTags1
    ($K$ items)
$ {\lambda_i^l}, l=1,\ldots,L $ GGrid iMaskTags2
    ($L$ items)
$ {\beta_i^m}, m=1,\ldots,M $ GGrid rMaskTags2
    ($M$ items)
$ {\mu_i^p}, p=1,\ldots,P $ GGrid iMaskTags3
    ($L$ items)
$ {\gamma_i^q}, q=1,\ldots,Q $ GGrid rMaskTags3
    ($M$ items)
$ {\nu_i^r}, r=1,\ldots,R $ GGrid iMaskTags4
    ($L$ items)
$ {\delta_i^s}, s=1,\ldots,S $ GGrid rMaskTags4
    ($M$ items)
$ {W_i} $ WeightSum  


INTERFACE:

 
  subroutine MergeFourGGSP_(inAv1, iMaskTags1, rMaskTags1, &
                            inAv2, iMaskTags2, rMaskTags2, &
                            inAv3, iMaskTags3, rMaskTags3, &
                            inAv4, iMaskTags4, rMaskTags4, &
                            GGrid, CheckMasks, outAv, WeightSum)
USES:
       use m_stdio
       use m_die
 
       use m_realkinds, only : SP, FP
 
       use m_List, only : List
       use m_List, only : List_allocated => allocated
 
       use m_AttrVect, only : AttrVect
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_nRAttr => nRAttr
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
 
       implicit none
INPUT PARAMETERS:
       type(AttrVect),               intent(IN)    :: inAv1
       character(len=*),   optional, intent(IN)    :: iMaskTags1
       character(len=*),   optional, intent(IN)    :: rMaskTags1
       type(AttrVect),               intent(IN)    :: inAv2
       character(len=*),   optional, intent(IN)    :: iMaskTags2
       character(len=*),   optional, intent(IN)    :: rMaskTags2
       type(AttrVect),               intent(IN)    :: inAv3
       character(len=*),   optional, intent(IN)    :: iMaskTags3
       character(len=*),   optional, intent(IN)    :: rMaskTags3
       type(AttrVect),               intent(IN)    :: inAv4
       character(len=*),   optional, intent(IN)    :: iMaskTags4
       character(len=*),   optional, intent(IN)    :: rMaskTags4
       type(GeneralGrid),            intent(IN)    :: GGrid
       logical,                      intent(IN)    :: CheckMasks
INPUT/OUTPUT PARAMETERS:
       type(AttrVect),               intent(INOUT) :: outAv
       real(SP),       dimension(:), pointer       :: WeightSum
REVISION HISTORY:
         19Jun02 - Jay Larson <[email protected]> - Interface spec.
          3Jul02 - Jay Larson <[email protected]> - Implementation.
         10Jul02 - J. Larson <[email protected]> - Improved argument 
                   checking.

13.1.4 MergeInDataGGSP_ - Add Data into a Merge

This routine takes input field data from the input AttrVect argument inAv, and merges the real attributes it shares with the input/output AttrVect argument outAv. The merge is a masked merge of the form

\begin{displaymath}c_i = c_i + {{\prod_{j=1}^J} M_{i}^j} {{\prod_{k=1}^K} F_{i}^k}
a_i , \end{displaymath}

where $ {c_i} $ represents one element of one of the real attributes of outAv, and $ {a_i} $ represents one element of one of the real attributes of inAv. The ${M_{i}^j}$ are integer masks which have value either $0$ or $1$, and are integer attributes of the input GeneralGrid argument GGrid. The ${F_{i}^k}$ are real masks whose values are in the closed interval $[0,1]$, and are real attributes of the input GeneralGrid argument GGrid. The input CHARACTER argument iMaskTags is a string of colon- delimited strings that name the integer attributes in GGrid that are used as the masks ${M_{i}^j}$. The input CHARACTER argument rMaskTags is a string of colon-delimited strings that name the real attributes in GGrid that are used as the masks ${F_{i}^k}$. The output REAL array WeightSum is used to store a running sum of the product of the masks. The LOGICAL input argument CheckMasks governs how the masks are applied. If ${\tt CheckMasks} = {\tt .TRUE.}$, the entries are checked to ensure they meet the definitions of real and integer masks. If ${\tt CheckMasks} = {\tt .FALSE.}$ then the masks are multiplied together on an element-by-element basis with no validation of their entries (this option results in slightly higher performance).

N.B.: The lengths of the AttrVect arguments inAv and outAv must be equal, and this length must also equal the lengths of GGrid and WeightSum.

N.B.: This algorithm assumes the AttrVect argument outAv has been created, and its real attributes have been initialized.

N.B.: This algorithm assumes that the array WeightSum has been created and initialized.


INTERFACE:

 
  subroutine MergeInDataGGSP_(inAv, iMaskTags, rMaskTags, GGrid, &
                              CheckMasks, outAv, WeightSum)
USES:
       use m_stdio
       use m_die
 
       use m_realkinds, only : SP, FP
 
       use m_String, only : String
       use m_String, only : String_clean => clean
       use m_String, only : String_ToChar => toChar
 
       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_get => get
       use m_List, only : List_identical => identical
       use m_List, only : List_allocated => allocated
 
       use m_AttrVect, only : AttrVect
       use m_AttrVect, only : AttrVect_lsize => lsize
       use m_AttrVect, only : AttrVect_nRAttr => nRAttr
       use m_AttrVect, only : SharedAttrIndexList
 
       use m_GeneralGrid, only : GeneralGrid
       use m_GeneralGrid, only : GeneralGrid_lsize => lsize
       use m_GeneralGrid, only : GeneralGrid_exportIAttr => exportIAttr
       use m_GeneralGrid, only : GeneralGrid_exportRAttr => exportRAttr
 
       implicit none
INPUT PARAMETERS:
       type(AttrVect),               intent(IN)    :: inAv
       character(len=*),   optional, intent(IN)    :: iMaskTags
       character(len=*),   optional, intent(IN)    :: rMaskTags
       type(GeneralGrid),            intent(IN)    :: GGrid
       logical,                      intent(IN)    :: CheckMasks
INPUT/OUTPUT PARAMETERS:
       type(AttrVect),               intent(INOUT) :: outAv
       real(SP),       dimension(:), pointer       :: WeightSum
REVISION HISTORY:
         19Jun02 - Jay Larson <[email protected]> - initial verson.
         10Jul02 - J. Larson <[email protected]> - Improved argument 
                   checking.



next up previous contents
Next: 14 Time Averaging Up: 2 High Level API's Previous: 12 Spatial Integration and   Contents
[email protected]