next up previous contents
Next: 19 InPackF90 Up: 3 Documentation of MPEU Previous: 17 The String Datatype   Contents

Subsections

18 The List Datatype

18.1 Module m_List - A List Manager (Source File: m_List.F90)

A List is a character buffer comprising substrings called items separated by colons, combined with indexing information describing (1) the starting point in the character buffer of each substring, and (2) the length of each substring. The only constraints on the valid list items are (1) the value of an item does not contain the ``:'' delimitter, and (2) leading and trailing blanks are stripped from any character string presented to define a list item (although any imbeded blanks are retained).

Example: Suppose we wish to define a List containing the items 'latitude', 'longitude', and 'pressure'. The character buffer of the List containing these items will be the 27-character string

   'latitude:longitude:pressure'
and the indexing information is summarized in the table below.


Item Starting Point in Buffer Length
latitude 1 8
longitude 9 9
pressure 20 8

One final note: All operations for the List datatype are case sensitive.


INTERFACE:

 
  module m_List
USES:
   No other Fortran modules are used.
 
       implicit none
 
       private	! except
PUBLIC TYPES:
 
       public :: List		! The class data structure
 
       Type List
 #ifdef SEQUENCE
      sequence
 #endif
 	 character(len=1),dimension(:),pointer :: bf
 	 integer,       dimension(:,:),pointer :: lc
       End Type List
PUBLIC MEMBER FUNCTIONS:
 
       public :: init
       public :: clean
       public :: nullify
       public :: index
       public :: get_indices
       public :: test_indices
       public :: nitem
       public :: get
       public :: identical
       public :: assignment(=)
       public :: allocated
       public :: copy
       public :: exportToChar
       public :: exportToString
       public :: CharBufferSize
       public :: append
       public :: concatenate
       public :: bcast
       public :: send
       public :: recv
       public :: GetSharedListIndices
 
   interface init ; module procedure	&
       init_,		&
       initStr_,	&
       initstr1_
   end interface
   interface clean; module procedure clean_; end interface
   interface nullify; module procedure nullify_; end interface
   interface index; module procedure	&
       index_,     &
       indexStr_
   end interface
   interface get_indices; module procedure get_indices_; end interface
   interface test_indices; module procedure test_indices_; end interface
   interface nitem; module procedure nitem_; end interface
   interface get  ; module procedure	&
       get_,		&
       getall_,	&
       getrange_
   end interface
   interface identical; module procedure identical_; end interface
   interface assignment(=)
     module procedure copy_
   end interface
   interface allocated ; module procedure &
        allocated_
   end interface
   interface copy ; module procedure copy_ ;  end interface
   interface exportToChar ; module procedure &
        exportToChar_
   end interface
   interface exportToString ; module procedure &
        exportToString_
   end interface
   interface CharBufferSize ; module procedure &
       CharBufferSize_
   end interface
   interface append ; module procedure append_ ; end interface
   interface concatenate ; module procedure concatenate_ ; end interface
   interface bcast; module procedure bcast_; end interface
   interface send; module procedure send_; end interface
   interface recv; module procedure recv_; end interface
   interface GetSharedListIndices; module procedure &
       GetSharedListIndices_ 
   end interface
REVISION HISTORY:
   22Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code
   16May01 - J. Larson <[email protected]> - Several changes / fixes:
             public interface for copy_(), corrected version of copy_(),
             corrected version of bcast_().
   15Oct01 - J. Larson <[email protected]> - Added the LOGICAL 
             function identical_().
   14Dec01 - J. Larson <[email protected]> - Added the LOGICAL 
             function allocated_().
   13Feb02 - J. Larson <[email protected]> - Added the List query 
             functions exportToChar() and CharBufferLength().
   13Jun02-  R.L. Jacob <[email protected]> - Move GetSharedListIndices
             from mct to this module.

18.1.1 init_ - Initialize a List from a CHARACTER String

A list is a string in the form of ``Larry:Moe:Curly'', or ``lat:lon:lev'', combined with substring location and length information. Through the initialization call, the items delimited by ``:'' are stored as an array of sub- strings of a long string, accessible through an array of substring indices. The only constraints now on the valid list entries are, (1) the value of an entry does not contain ``:'', and (2) The leading and the trailing blanks are insignificant, although any imbeded blanks are. For example,

 
   call init_(aList, 'batman  :SUPERMAN:Green Lantern:  Aquaman')
will result in aList having four items: 'batman', 'SUPERMAN', 'Green Lantern', and 'Aquaman'. That is
 
   aList%bf =  'batman:SUPERMAN:Green Lantern:Aquaman'
   


INTERFACE:

 
  subroutine init_(aList,Values)
USES:
       use m_die,only : die
       use m_mall,only : mall_mci,mall_ison
  
       implicit none
INPUT PARAMETERS:
       character(len=*),intent(in) :: Values ! ":" delimited names
OUTPUT PARAMETERS:
       type(List),intent(out)	  :: aList  ! an indexed string values
REVISION HISTORY:
   22Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code

18.1.2 initStr_ - Initialize a List Using the String Type

This routine initializes a List datatype given an input String datatype (see m_String for more information regarding the String type). The contents of the input String argument pstr must adhere to the restrictions stated for character input stated in the prologue of the routine init_() in this module.


INTERFACE:

 
  subroutine initStr_(aList, pstr)
USES:
       use m_String, only : String,toChar
 
       implicit none
INPUT PARAMETERS:
       type(String),intent(in)	  :: pstr
OUTPUT PARAMETERS:
       type(List),intent(out)	  :: aList  ! an indexed string values
REVISION HISTORY:
   23Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code

18.1.3 initStr1_ - Initialize a List Using an Array of Strings

This routine initializes a List datatype given as input array of String datatypes (see m_String for more information regarding the String type). The contents of each String element of the input array strs must adhere to the restrictions stated for character input stated in the prologue of the routine init_() in this module. Specifically, no element in strs may contain the colon : delimiter, and any leading or trailing blanks will be stripped (though embedded blank spaces will be retained). For example, consider an invocation of initStr1_() where the array strs(:) contains four entries: strs(1)='John', strs(2)=' Paul', strs(3)='George ', and strs(4)=' Ringo'. The resulting List output aList will have

 
   aList%bf =  'John:Paul:George:Ringo'
   


INTERFACE:

 
  subroutine initStr1_(aList, strs)
USES:
       use m_String, only : String,toChar
       use m_String, only : len
       use m_String, only : ptr_chars
       use m_die,only : die
 
       implicit none
INPUT PARAMETERS:
       type(String),dimension(:),intent(in)	  :: strs
OUTPUT PARAMETERS:
       type(List),intent(out)	  :: aList  ! an indexed string values
REVISION HISTORY:
   23Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code

18.1.4 clean_ - Deallocate Memory Used by a List

This routine deallocates the allocated memory components of the input/output List argument aList. Specifically, it deallocates aList%bf and aList%lc. If the optional output INTEGER arguemnt stat is supplied, no warning will be printed if the Fortran intrinsic deallocate() returns with an error condition.


INTERFACE:

 
  subroutine clean_(aList, stat)
USES:
       use m_die,  only : warn
       use m_mall, only : mall_mco,mall_ison
 
       implicit none
INPUT/OUTPUT PARAMETERS:
       type(List),        intent(inout) :: aList
OUTPUT PARAMETERS:
       integer, optional, intent(out)   :: stat
REVISION HISTORY:
   22Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code
    1Mar02 - E.T. Ong <[email protected]> - added stat argument and
             removed die to prevent crashes.

18.1.5 nullify_ - Nullify Pointers in a List

In Fortran 90, pointers may have three states: (1) ASSOCIATED, that is the pointer is pointing at a target, (2) UNASSOCIATED, and (3) UNINITIALIZED. On some platforms, the Fortran intrinsic function associated() will view uninitialized pointers as UNASSOCIATED by default. This is not always the case. It is good programming practice to nullify pointers if they are not to be used. This routine nullifies the pointers present in the List datatype.


INTERFACE:

 
  subroutine nullify_(aList)
USES:
       use m_die,only : die
 
       implicit none
INPUT/OUTPUT PARAMETERS:
       type(List),intent(inout) :: aList
REVISION HISTORY:
   18Jun01 - J.W. Larson - <[email protected]> - initial version

18.1.6 nitem_ - Return the Number of Items in a List

This function enumerates the number of items in the input List argument aList. For example, suppose

    aList%bf = 'John:Paul:George:Ringo'
   
Then,

\begin{displaymath}{\tt nitem\_(aList)} = 4 .\end{displaymath}


INTERFACE:

 
  integer function nitem_(aList)
USES:
       implicit none
INPUT PARAMETERS:
       type(List),intent(in) :: aList
REVISION HISTORY:
   22Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code
   10Oct01 - J.W. Larson <[email protected]> - modified routine to
             check pointers aList%bf and aList%lc using  the f90 
             intrinsic ASSOCIATED before proceeding with the item
             count.  If these pointers are UNASSOCIATED, an item
             count of zero is returned.

18.1.7 index_ - Return Rank in a List of a Given Item (CHARACTER)

This function returns the rank of an item (defined by the CHARACTER argument item) in the input List argument aList. If item is not present in aList, then zero is returned. For example, suppose

    aList%bf = 'Bob:Carol:Ted:Alice'
   
Then, ${\tt index\_(aList, 'Ted')}=3$, ${\tt index\_(aList, 'Carol')}=2$, and ${\tt index\_(aList, 'The Dude')}=0.$


INTERFACE:

 
  integer function index_(aList, item)
USES:
       use m_String, only : toChar
 
       implicit none
INPUT PARAMETERS:
       type(List),      intent(in) :: aList	! a List of names
       character(len=*),intent(in) :: item	! a given item name
REVISION HISTORY:
   22Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code

18.1.8 indexStr_ - Return Rank in a List of a Given Item (String)

This function performs the same operation as the function index_(), but the item to be indexed is instead presented in the form of a String datatype (see the module m_String for more information about the String type). This routine searches through the input List argument aList for an item that matches the item defined by itemStr, and if a match is found, the rank of the item in the list is returned (see also the prologue for the routine index_() in this module). If no match is found, a value of zero is returned.


INTERFACE:

 
  integer function indexStr_(aList, itemStr)
USES:
       use m_String,only : String,toChar
 
       implicit none
INPUT PARAMETERS:
       type(List),      intent(in) :: aList	! a List of names
       type(String),    intent(in) :: itemStr
REVISION HISTORY:
   22Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code
   25Oct02 - R. Jacob <[email protected]> - just call index_ above

18.1.9 allocated_ - Check Pointers in a List for Association Status

This function checks the input List argument inList to determine whether or not it has been allocated. It does this by invoking the Fortran90 intrinsic function associated() on the pointers inList%bf and inList%lc. If both of these pointers are associated, the return value is .TRUE..

N.B.: In Fortran90, pointers have three different states: ASSOCIATED, UNASSOCIATED, and UNDEFINED. If a pointer is UNDEFINED, this function may return either .TRUE. or .FALSE. values, depending on the Fortran90 compiler. To avoid such problems, we advise that users invoke the List method nullify() to nullify any List pointers for List variables that are not initialized.


INTERFACE:

 
  logical function allocated_(inList)
USES:
 
       use m_die,only : die
 
       implicit none
INPUT PARAMETERS:
 
       type(List), intent(in) :: inList
REVISION HISTORY:
   14Dec01 - J. Larson <[email protected]> - inital version

18.1.10 copy_ - Copy a List

This routine copies the contents of the input List argument xL into the output List argument yL.


INTERFACE:

 
  subroutine copy_(yL,xL)	! yL=xL
USES:
       use m_die,only : die
       use m_stdio
       use m_String ,only : String
       use m_String ,only : String_clean
       use m_mall,only : mall_mci,mall_ison
 
       implicit none
INPUT PARAMETERS:
       type(List),intent(in)  :: xL
OUTPUT PARAMETERS:
       type(List),intent(out) :: yL
REVISION HISTORY:
   22Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code
   16May01 - J. Larson <[email protected]> - simpler, working 
             version that exploits the String datatype (see m_String)
    1Aug02 - Larson/Ong - Added logic for correct copying of blank 
             Lists.

18.1.11 exportToChar_ - Export List to a CHARACTER

This function returns the character buffer portion of the input List argument inList--that is, the contents of inList%bf--as a CHARACTER (suitable for printing). An example of the use of this function is:

             write(stdout,'(1a)') exportToChar(inList)
which writes the contents of inList%bf to the Fortran device stdout.


INTERFACE:

 
  function exportToChar_(inList)
USES:
       use m_die,    only : die
       use m_stdio,  only : stderr
       use m_String, only : String
       use m_String, only : String_ToChar => toChar
       use m_String, only : String_clean
 
       implicit none
 
   ! INPUT PARAMETERS:
 
       type(List),        intent(in)  :: inList
 
   ! OUTPUT PARAMETERS:
 
       character(len=size(inList%bf,1)) :: exportToChar_
 
REVISION HISTORY:
   13Feb02 - J. Larson <[email protected]> - initial version.
   06Jun03 - R. Jacob <[email protected]> - return blank if List is not allocated

18.1.12 exportToString_ - Export List to a String

This function returns the character buffer portion of the input List argument inList--that is, the contents of inList%bf--as a String (see the mpeu module m_String for more information regarding the String type). This function was created to circumvent problems with implementing inheritance of the function exportToChar_() to other datatypes build on top of the List type.


INTERFACE:

 
  function exportToString_(inList)
USES:
       use m_die,    only : die
       use m_stdio,  only : stderr
 
       use m_String, only : String
       use m_String, only : String_init => init
 
       implicit none
 
   ! INPUT PARAMETERS:
 
       type(List),       intent(in) :: inList
 
   ! OUTPUT PARAMETERS:
 
       type(String)                 :: exportToString_
REVISION HISTORY:
   14Aug02 - J. Larson <[email protected]> - initial version.

18.1.13 CharBufferSize_ - Return size of a List's Character Buffer

This function returns the length of the character buffer portion of the input List argument inList (that is, the number of characters stored in inList%bf) as an INTEGER. Suppose for the sake of argument that inList was created using the following call to init_():

    call init_(inList, 'Groucho:Harpo:Chico:Zeppo')
Then, using the above example value of inList, we can use CharBufferSize_() as follows:
   integer :: BufferLength
   BufferLength = CharBufferSize(inList)
and the resulting value of BufferLength will be 25.


INTERFACE:

 
  integer function CharBufferSize_(inList)
USES:
       use m_die,    only : die
       use m_stdio,  only : stderr
 
       implicit none
 
   ! INPUT PARAMETERS:
 
       type(List),         intent(in) :: inList
REVISION HISTORY:
   13Feb02 - J. Larson <[email protected]> - initial version.

18.1.14 get_ - Retrieve a Numbered Item from a List as a String

This routine retrieves a numbered item (defined by the input INTEGER argument ith) from the input List argument aList, and returns it in the output String argument itemStr (see the module m_String for more information about the String type). If the argument ith is nonpositive, or greater than the number of items in aList, a String containing one blank space is returned.


INTERFACE:

 
  subroutine get_(itemStr, ith, aList)
USES:
       use m_String, only : String, init, toChar
 
       implicit none
INPUT PARAMETERS:
       integer,     intent(in)  :: ith
       type(List),  intent(in)  :: aList
OUTPUT PARAMETERS:
       type(String),intent(out) :: itemStr
REVISION HISTORY:
   23Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code
   14May07 - Larson, Jacob - add space to else case string so function
                             matches documentation.

18.1.15 getall_ - Return all Items from a List as one String

This routine returns all the items from the input List argument aList in the output String argument itemStr (see the module m_String for more information about the String type). The contents of the character buffer in itemStr will be the all of the items in aList, separated by the colon delimiter.


INTERFACE:

 
  subroutine getall_(itemStr, aList)
USES:
       use m_String, only : String, init, toChar
 
       implicit none
INPUT PARAMETERS:
       type(List),   intent(in)  :: aList
OUTPUT PARAMETERS:
       type(String), intent(out) :: itemStr
REVISION HISTORY:
   23Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code

18.1.16 getrange_ - Return a Range of Items from a List as one String

This routine returns all the items ranked i1 through i2 from the input List argument aList in the output String argument itemStr (see the module m_String for more information about the String type). The contents of the character buffer in itemStr will be items in i1 through i2 aList, separated by the colon delimiter.


INTERFACE:

 
  subroutine getrange_(itemStr, i1, i2, aList)
USES:
       use m_die,    only : die
       use m_stdio,  only : stderr
       use m_String, only : String,init,toChar
 
       implicit none
INPUT PARAMETERS:
       integer,     intent(in)  :: i1
       integer,     intent(in)  :: i2
       type(List),  intent(in)  :: aList
OUTPUT PARAMETERS:
       type(String),intent(out) :: itemStr
REVISION HISTORY:
   23Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code
   26Jul02 - J. Larson - Added argument checks.

18.1.17 identical_ - Compare Two Lists for Equality

This function compares the string buffer and indexing information in the two input List arguments yL and xL. If the string buffers and index buffers of yL and xL match, this function returns a value of .TRUE. Otherwise, it returns a value of .FALSE.


INTERFACE:

 
  logical function identical_(yL, xL)
USES:
       use m_die,only : die
       use m_String ,only : String
       use m_String ,only : String_clean
 
       implicit none
INPUT PARAMETERS:
       type(List), intent(in) :: yL
       type(List), intent(in) :: xL
REVISION HISTORY:
   14Oct01 - J. Larson <[email protected]> - original version

18.1.18 get_indices_ - Index Multiple Items in a List

This routine takes as input a List argument aList, and a CHARACTER string Values, which is a colon- delimited string of items, and returns an INTEGER array indices(:), which contain the rank of each item in aList. For example, suppose aList was created from the character string

   'happy:sleepy:sneezey:grumpy:dopey::bashful:doc'
and get_indices_() is invoked as follows:
   call get_indices_(indices, aList, 'sleepy:grumpy:bashful:doc')
The array indices(:) will be returned with 4 entries: ${\tt indices(1)}=2$, ${\tt indices(2)}=4$, ${\tt indices(3)}=6$, and ${\tt indices(4)}=7$.

N.B.: This routine operates on the assumption that each of the substrings in the colon-delimited string Values is an item in aList. If this assumption is invalid, this routine terminates execution with an error message.

N.B.: The pointer indices must be UNASSOCIATED on entry to this routine, and will be ASSOCIATED upon return. After this pointer is no longer needed, it should be deallocated. Failure to do so will result in a memory leak.


INTERFACE:

 
  subroutine get_indices_(indices, aList, Values)
USES:
       use m_stdio
       use m_die
       use m_String, only : String
       use m_String, only : String_clean => clean
       use m_String, only : String_toChar => toChar
 
       implicit none
INPUT PARAMETERS:
       type(List),            intent(in)	:: aList  ! an indexed string values
       character(len=*),      intent(in) :: Values ! ":" delimited names
OUTPUT PARAMETERS:
       integer, dimension(:), pointer    :: indices
REVISION HISTORY:
   31May98 - Jing Guo <guo@thunder> - initial prototype/prolog/code
   12Feb03 - J. Larson <[email protected]> Working refactored version

18.1.19 test_indices_ - Test/Index Multiple Items in a List

This routine takes as input a List argument aList, and a CHARACTER string Values, which is a colon- delimited string of items, and returns an INTEGER array indices(:), which contain the rank of each item in aList. For example, suppose aList was created from the character string

   'happy:sleepy:sneezey:grumpy:dopey::bashful:doc'
and test_indices_() is invoked as follows:
   call test_indices_(indices, aList, 'sleepy:grumpy:bashful:doc')
The array indices(:) will be returned with 4 entries: ${\tt indices(1)}=2$, ${\tt indices(2)}=4$, ${\tt indices(3)}=6$, and ${\tt indices(4)}=7$.

Now suppose test_indices_() is invoked as follows:

   call test_indices_(indices, aList, 'sleepy:grumpy:bashful:Snow White')
The array indices(:) will be returned with 4 entries: ${\tt indices(1)}=2$, ${\tt indices(2)}=4$, ${\tt indices(3)}=6$, and ${\tt indices(4)}=0$.

N.B.: This routine operates on the assumption that one or more of the substrings in the colon-delimited string Values is may not be an item in aList. If an item in Values is not in aList, its corresponding entry in indices(:) is set to zero.

N.B.: The pointer indices must be UNASSOCIATED on entry to this routine, and will be ASSOCIATED upon return. After this pointer is no longer needed, it should be deallocated. Failure to do so will result in a memory leak.


INTERFACE:

 
  subroutine test_indices_(indices, aList, Values)
USES:
       use m_stdio
       use m_die
       use m_String, only : String
       use m_String, only : String_clean => clean
       use m_String, only : String_toChar => toChar
 
       implicit none
INPUT PARAMETERS:
       type(List),            intent(in)	:: aList  ! an indexed string values
       character(len=*),      intent(in) :: Values ! ":" delimited names
OUTPUT PARAMETERS:
       integer, dimension(:), pointer    :: indices
REVISION HISTORY:
   12Feb03 - J. Larson <[email protected]> Working refactored version

18.1.20 append_ - Append One List Onto the End of Another

This routine takes two List arguments iList1 and iList2, and appends List2 onto the end of List1.

N.B.: There is no check for shared items in the arguments List1 and List2. It is the user's responsibility to ensure List1 and List2 share no items. If this routine is invoked in such a manner that List1 and List2 share common items, the resultant value of List1 will produce ambiguous results for some of the List query functions.

N.B.: The outcome of this routine is order dependent. That is, the entries of iList2 will follow the input entries in iList1.


INTERFACE:

 
     subroutine append_(iList1, iList2)
USES:
       use m_stdio
       use m_die, only : die
 
       use m_mpif90
 
       use m_String, only:  String
       use m_String, only:  String_toChar => toChar
       use m_String, only:  String_len
       use m_String, only:  String_clean => clean
 
       implicit none
INPUT PARAMETERS:
       type(List),         intent(in)    :: iList2
INPUT/OUTPUT PARAMETERS:
       type(List),         intent(inout) :: iList1
REVISION HISTORY:
    6Aug02 - J. Larson - Initial version

18.1.21 concatenate_ - Concatenates two Lists to form a Third List.

This routine takes two input List arguments iList1 and iList2, and concatenates them, producing an output List argument oList.

N.B.: The nature of this routine is such that one must never supply as the actual value of oList the same value supplied for either iList1 or iList2.

N.B.: The outcome of this routine is order dependent. That is, the entries of iList2 will follow iList1.


INTERFACE:

 
     subroutine concatenate_(iList1, iList2, oList)
USES:
       use m_stdio
       use m_die, only : die
 
       use m_mpif90
 
       use m_String, only:  String
       use m_String, only:  String_init => init
       use m_String, only:  String_clean => clean
 
       implicit none
INPUT PARAMETERS:
       type(List),         intent(in)  :: iList1
       type(List),         intent(in)  :: iList2
OUTPUT PARAMETERS:
       type(List),         intent(out) :: oList
BUGS:
   CHARACTER variables as intermediate storage.  The lengths of these
   scratch variables is hard-wired to 10000, which should be large enough
   for most applications.  This undesirable feature should be corrected 
   ASAP.
REVISION HISTORY:
    8May01 - J.W. Larson - initial version.
   17May01 - J.W. Larson - Re-worked and tested successfully.
   17Jul02 - E. Ong - fixed the bug mentioned above

18.1.22 bcast_ - MPI Broadcast for the List Type

This routine takes an input List argument iList (on input, valid on the root only), and broadcasts it.

N.B.: The outcome of this routine, ioList on non-root processes, represents allocated memory. When this List is no longer needed, it must be deallocated by invoking the routine List_clean(). Failure to do so will cause a memory leak.


INTERFACE:

 
     subroutine bcast_(ioList, root, comm, status)
USES:
       use m_stdio,  only : stderr
       use m_die, only : MP_perr_die, die
 
       use m_String, only:  String
       use m_String, only:  String_bcast => bcast
       use m_String, only:  String_clean => clean
 
       use m_mpif90
 
       implicit none
INPUT PARAMETERS:
       integer,            intent(in)     :: root
       integer,            intent(in)     :: comm
INPUT/OUTPUT PARAMETERS:
       type(List),         intent(inout)  :: ioList
OUTPUT PARAMETERS:
       integer, optional,  intent(out)    :: status
REVISION HISTORY:
    7May01 - J.W. Larson - initial version.
   14May01 - R.L. Jacob - fix error checking
   16May01 - J.W. Larson - new, simpler String-based algorigthm
             (see m_String for details), which works properly on
             the SGI platform.
   13Jun01 - J.W. Larson <[email protected]> - Initialize status
             (if present).

18.1.23 send_ - MPI Point-to-Point Send for the List Type

This routine takes an input List argument inList and sends it to processor dest on the communicator associated with the fortran 90 INTEGER handle comm. The message is tagged by the input INTEGER argument TagBase. The success (failure) of this operation is reported in the zero (nonzero) optional output argument status.

N.B.: One must avoid assigning elsewhere the MPI tag values TagBase and TagBase+1. This is because send_() performs the send of the List as a pair of operations. The first send is the number of characters in inList%bf, and is given MPI tag value TagBase. The second send is the CHARACTER data present in inList%bf, and is given MPI tag value TagBase+1.


INTERFACE:

 
     subroutine send_(inList, dest, TagBase, comm, status)
USES:
       use m_stdio
       use m_die, only : MP_perr_die
 
       use m_mpif90
 
       use m_String, only:  String
       use m_String, only:  String_toChar => toChar
       use m_String, only:  String_len
       use m_String, only:  String_clean => clean
 
       implicit none
INPUT PARAMETERS:
       type(List),         intent(in)  :: inList  
       integer,            intent(in)  :: dest
       integer,            intent(in)  :: TagBase
       integer,            intent(in)  :: comm
OUTPUT PARAMETERS:
       integer, optional,  intent(out) :: status
REVISION HISTORY:
    6Jun01 - J.W. Larson - initial version.
   13Jun01 - J.W. Larson <[email protected]> - Initialize status
             (if present).

18.1.24 recv_ - MPI Point-to-Point Receive for the List Type

This routine receives the output List argument outList from processor source on the communicator associated with the fortran 90 INTEGER handle comm. The message is tagged by the input INTEGER argument TagBase. The success (failure) of this operation is reported in the zero (nonzero) optional output argument status.

N.B.: One must avoid assigning elsewhere the MPI tag values TagBase and TagBase+1. This is because recv_() performs the receive of the List as a pair of operations. The first receive is the number of characters in outList%bf, and is given MPI tag value TagBase. The second receive is the CHARACTER data present in outList%bf, and is given MPI tag value TagBase+1.


INTERFACE:

 
     subroutine recv_(outList, source, TagBase, comm, status)
USES:
       use m_stdio, only : stderr
       use m_die,   only : MP_perr_die
 
       use m_mpif90
 
       use m_String, only : String
 
       implicit none
INPUT PARAMETERS:
       integer,            intent(in)  :: source
       integer,            intent(in)  :: TagBase
       integer,            intent(in)  :: comm
OUTPUT PARAMETERS:
       type(List),         intent(out) :: outList  
       integer, optional,  intent(out) :: status
REVISION HISTORY:
    6Jun01 - J.W. Larson - initial version.
   11Jun01 - R. Jacob - small bug fix; status in MPI_RECV
   13Jun01 - J.W. Larson <[email protected]> - Initialize status
             (if present).

18.1.25 GetSharedListIndices_ - Index Shared Items for Two Lists

GetSharedListIndices_() compares two user- supplied List arguments List1 and Lis2 to determine: the number of shared items NumShared, and arrays of the locations Indices1 and Indices2 in List1 and List2, respectively.

N.B.: This routine returns two allocated arrays: Indices1(:) and Indices2(:). Both of these arrays must be deallocated once they are no longer needed. Failure to do this will create a memory leak.


INTERFACE:

 
  subroutine GetSharedListIndices_(List1, List2, NumShared, Indices1, &
                                    Indices2)
USES:
       use m_die,  only : MP_perr_die, die, warn
 
       use m_String, only : String
       use m_String, only : String_clean => clean
 
       implicit none
INPUT PARAMETERS:
       type(List),    intent(in)  :: List1
       type(List),    intent(in)  :: List2
OUTPUT PARAMETERS:
       integer,           intent(out) :: NumShared
 
       integer,dimension(:), pointer  :: Indices1
       integer,dimension(:), pointer  :: Indices2
REVISION HISTORY:
    7Feb01 - J.W. Larson <[email protected]> - initial version



next up previous contents
Next: 19 InPackF90 Up: 3 Documentation of MPEU Previous: 17 The String Datatype   Contents
[email protected]