G.1 Mathematic_Vector Class Code Listing

The main documentation of the Mathematic_Vector Class contains additional explanation of this code listing.

!
! Author: Michael L. Hall
!         P.O. Box 1663, MS-D413, LANL
!         Los Alamos, NM 87545
!         ph: 505-665-4312
!         email: Hall@LANL.gov
! 
! Created on: 12/15/02
! CVS Info:   $Id: mathematic_vector.F90,v 1.36 2009/09/11 21:44:06 hall Exp $

module Caesar_Mathematic_Vector_Class

  ! Global use associations.

  use Caesar_Data_Structures_Module

  ! Start up with everything untyped and private.

  implicit none
  private

  ! Public procedures.

  public :: Initialize, Finalize, Valid_State, Initialized
  public :: Assignment(=), Operator(.DotProduct.), Operator(.Orthogonal.)
  public :: Add_Values, Average, Duplicate, First_PE, Get_Values, &
            Infinity_Norm, Last_PE, Length_PE, Length_Total, Locus, Maximum, &
            Mean, Minimum, Name, Norm, One_Norm, Output, P_Norm, &
            Set_Not_Up_to_Date, Set_Value, Set_Values, Sum, Total, Two_Norm, &
            Update_DV

  interface Initialize
    module procedure Initialize_Mathematic_Vector
  end interface

  interface Finalize
    module procedure Finalize_Mathematic_Vector
  end interface

  interface Valid_State
    module procedure Valid_State_Mathematic_Vector
  end interface

  interface Initialized
    module procedure Initialized_Mathematic_Vector
  end interface

  interface Assignment(=)
    module procedure Get_Values_Mathematic_Vector
    module procedure Set_Values_Mathematic_Vector_A
    module procedure Set_Value_Mathematic_Vector_A
  end interface

  interface OPERATOR (.DotProduct.)
    module procedure DotProduct_Mathematic_Vector
  end interface

  interface OPERATOR (.Orthogonal.)
    module procedure Orthogonal_Mathematic_Vector
  end interface

  interface Add_Values
    module procedure Add_Values_Mathematic_Vector_0
    module procedure Add_Values_Mathematic_Vector_1
    module procedure Add_Values_Mathematic_Vector_A
  end interface

  fortext([Value],[Average First_PE Infinity_Norm Last_PE Length_PE 
                   Length_Total Locus Maximum Minimum Name One_Norm 
                   P_Norm Sum Two_Norm],[
    interface Value
      module procedure expand(Get_Value_MV)
    end interface
  ])

  interface DotProduct
    module procedure DotProduct_Mathematic_Vector
  end interface

  interface Duplicate
    module procedure Duplicate_Mathematic_Vector
  end interface

  interface Get_Values
    module procedure Get_Values_Mathematic_Vector
  end interface

  interface Mean
    module procedure Get_Average_MV
  end interface

  interface Norm
    module procedure Get_Two_Norm_MV
  end interface

  interface Orthogonal
    module procedure Orthogonal_Mathematic_Vector
  end interface

  interface Output
    module procedure Output_Mathematic_Vector
  end interface

  interface Set_Not_Up_to_Date
    module procedure Set_Not_Up_to_Date_MV
  end interface

  interface Set_Value
    module procedure Set_Value_Mathematic_Vector_A
  end interface

  interface Set_Values
    module procedure Set_Values_Mathematic_Vector_0
    module procedure Set_Values_Mathematic_Vector_1
    module procedure Set_Values_Mathematic_Vector_A
  end interface

  interface Total
    module procedure Get_Sum_MV
  end interface

  interface Update_DV
    module procedure Update_DV_Mathematic_Vector
  end interface

  ! Public variable (must precede type defs where it is used).

  type(integer), parameter :: Number_of_OVs_in_an_MV=4
  public :: Number_of_OVs_in_an_MV

  ! Public type definitions.

  public :: Mathematic_Vector_type

  type Mathematic_Vector_type

    ! Initialization flag.

    type(integer) :: Initialized               

    ! The name for this variable (especially useful in a vector of
    ! Mathematic Vectors).

    type(character,name_length) :: Name

    ! Basic data structure.

    type(Base_Structure_type), pointer :: Structure

    ! Values for the Mathematic Vector.

    type(real,1) :: Values

    ! MV dimensionality is unity.

    type(integer) :: Dimensionality=1

    ! Distributed and Overlapped Vectors that are used for matvecs.

    type(Distributed_Vector_type) :: DV
    type(Overlapped_Vector_type), dimension(Number_of_OVs_in_an_MV) :: OV

    ! Pointers to the Data_Index for each Overlapped Vector -- cannot
    ! have an array of pointers in F90 (Arrgh). Note that there are four
    ! of these because the current value of Number_of_OVs_in_an_MV is 4.

    type(Data_Index_type), pointer :: Index1, Index2, Index3, Index4

    ! Number used to match with a similar number for a matrix during a
    ! MatVec. This would be better done by using a pointered Data_Index
    ! in the matrix and checking association status, but that won't work
    ! currently in F90 -- pointered internals should only be used to point
    ! to things initialized elsewhere, and cannot be initialized themselves
    ! because they contain no internals. So, the current solution is somewhat
    ! of a kludge.

    type(integer), dimension(Number_of_OVs_in_an_MV) :: Index_Match_Number

    ! Norm variables and "updated?" toggles.

    type(real) :: Average, Infinity_Norm, Maximum, Minimum, One_Norm, P_Norm, &
                  Sum, Two_Norm
    type(integer) :: P_Norm_Exponent
    type(logical) :: Average_is_Updated, Infinity_Norm_is_Updated, &
                     Maximum_is_Updated, Minimum_is_Updated, &
                     One_Norm_is_Updated, DV_is_Updated, P_Norm_is_Updated, &
                     Sum_is_Updated, Two_Norm_is_Updated

  end type Mathematic_Vector_type

contains

The Mathematic_Vector Class contains the following routines which are listed in separate sections:

* Initialize_Mathematic_Vector
* Finalize_Mathematic_Vector
* Valid_State_Mathematic_Vector
* Initialized_Mathematic_Vector
* Add_Values_Mathematic_Vector
* DotProduct_Mathematic_Vector
* Duplicate_Mathematic_Vector
* Get Value Mathematic_Vector
* Get_Values_Mathematic_Vector
* Orthogonal_Mathematic_Vector
* Output_Mathematic_Vector
* Set_Not_Up_to_Date_Mathematic_Vector
* Set_Values_Mathematic_Vector
* Update_DV_Mathematic_Vector

end module Caesar_Mathematic_Vector_Class



Subsections
Michael L. Hall