hTensor-0.1.0: Multidimensional arrays and simple tensor computations.Source codeContentsIndex
Numeric.LinearAlgebra.Array.Util
Portabilityportable
Stabilityprovisional
MaintainerAlberto Ruiz <aruiz@um.es>
Description
Additional tools for manipulation of multidimensional arrays.
Synopsis
class (Num (Vector t), Field t) => Coord t
class (Eq a, Show (Idx a)) => Compat a where
compat :: Idx a -> Idx a -> Bool
data NArray i t
data Idx i = Idx {
iDim :: Int
iName :: Name
iType :: i
}
type Name = String
scalar :: Coord t => t -> NArray i t
rank :: NArray i t -> Int
names :: NArray i t -> [Name]
size :: Name -> NArray i t -> Int
typeOf :: Compat i => Name -> NArray i t -> i
dims :: NArray i t -> [Idx i]
coords :: NArray i t -> Vector t
rename :: (Coord t, Compat i) => NArray i t -> [Name] -> NArray i t
(!) :: (Coord t, Compat i) => NArray i t -> String -> NArray i t
parts :: Coord t => NArray i t -> Name -> [NArray i t]
newIndex :: (Coord t, Compat i) => i -> Name -> [NArray i t] -> NArray i t
mapArray :: Coord b => (Vector a -> Vector b) -> NArray i a -> NArray i b
zipArray :: (Coord a, Coord b, Compat i) => (Vector a -> Vector b -> Vector c) -> NArray i a -> NArray i b -> NArray i c
(|*|) :: (Coord t, Compat i) => NArray i t -> NArray i t -> NArray i t
extract :: (Compat i, Coord t) => (Int -> NArray i t -> Bool) -> Name -> NArray i t -> NArray i t
onIndex :: (Coord a, Coord b, Compat i) => ([NArray i a] -> [NArray i b]) -> Name -> NArray i a -> NArray i b
reorder :: Coord t => [Name] -> NArray i t -> NArray i t
(~>) :: Coord t => NArray i t -> String -> NArray i t
formatArray :: (Coord t, Compat i) => (t -> String) -> NArray i t -> String
formatFixed :: Compat i => Int -> NArray i Double -> String
formatScaled :: Compat i => Int -> NArray i Double -> String
dummyAt :: Int -> NArray i t -> NArray i t
noIdx :: Compat i => NArray i t -> NArray i t
conformable :: Compat i => [[Idx i]] -> Maybe [Idx i]
sameStructure :: Eq i => NArray i t1 -> NArray i t2 -> Bool
makeConformant :: (Coord t, Compat i) => [NArray i t] -> [NArray i t]
basisOf :: Coord t => NArray i t -> [NArray i t]
asScalar :: Coord t => NArray i t -> t
asVector :: Coord t => NArray i t -> Vector t
asMatrix :: Coord t => NArray i t -> Matrix t
fromVector :: Compat i => i -> Vector t -> NArray i t
fromMatrix :: (Compat i, Coord t) => i -> i -> Matrix t -> NArray i t
class Element e => Container c e where
toComplex :: (c e, c e) -> c (Complex e)
fromComplex :: c (Complex e) -> (c e, c e)
comp :: c e -> c (Complex e)
conj :: c (Complex e) -> c (Complex e)
real :: c Double -> c e
complex :: c e -> c (Complex Double)
Documentation
class (Num (Vector t), Field t) => Coord t Source
Types that can be elements of the multidimensional arrays.
show/hide Instances
class (Eq a, Show (Idx a)) => Compat a whereSource
Class of compatible indices for contractions.
Methods
compat :: Idx a -> Idx a -> BoolSource
show/hide Instances
data NArray i t Source
A multidimensional array with index type i and elements t.
show/hide Instances
(Coord t, Coord (Complex t), Compat i, Container Vector t) => Container (NArray i) t
(Coord t, Compat i) => Eq (NArray i t)
(Coord t, Compat i, Fractional (NArray i t), Floating (Vector t)) => Floating (NArray i t)
(Coord t, Compat i, Num (NArray i t)) => Fractional (NArray i t)
(Show (NArray i t), Coord t, Compat i) => Num (NArray i t)
data Idx i Source
Dimension descriptor.
Constructors
Idx
iDim :: Int
iName :: Name
iType :: i
show/hide Instances
type Name = StringSource
indices are denoted by strings, (frequently single-letter)
scalar :: Coord t => t -> NArray i tSource
Create a 0-dimensional structure.
rank :: NArray i t -> IntSource
The number of dimensions of a multidimensional array.
names :: NArray i t -> [Name]Source
Index names.
size :: Name -> NArray i t -> IntSource
Dimension of given index.
typeOf :: Compat i => Name -> NArray i t -> iSource
Type of given index.
dims :: NArray i t -> [Idx i]Source
Get detailed dimension information about the array.
coords :: NArray i t -> Vector tSource
Get the coordinates of an array as a flattened structure (in the order specified by dims).
renameSource
:: (Coord t, Compat i)
=> NArray i tnew names
-> [Name]
-> NArray i t
Rename indices. Equal indices are contracted out.
(!)Source
:: (Coord t, Compat i)
=> NArray i tnew indices
-> String
-> NArray i t
rename the indices with single-letter names. Equal indices of compatible type are contracted out.
partsSource
:: Coord t
=> NArray i tindex to expand
-> Name
-> [NArray i t]
Create a list of the substructures at the given level.
newIndexSource
:: (Coord t, Compat i)
=> i
-> Name
-> [NArray i t]
-> NArray i t
Create an array from a list of subarrays. (The inverse of parts.)
mapArray :: Coord b => (Vector a -> Vector b) -> NArray i a -> NArray i bSource
Apply a function (defined on hmatrix Vectors) to all elements of a structure. Use mapArray (mapVector f) for general functions.
zipArraySource
:: (Coord a, Coord b, Compat i)
=> Vector a -> Vector b -> Vector c
-> NArray i a
-> NArray i b
-> NArray i c
Apply a function on vectors to conformant arrays. Two arrays are conformant if the dimensional structure of one of them is contained in the other one. The smaller structure is replicated along the extra dimensions. The result has the same index order as the largest structure (or as the first argument, if they are equal).
(|*|) :: (Coord t, Compat i) => NArray i t -> NArray i t -> NArray i tSource
Tensor product with automatic contraction of repeated indices, following Einstein summation convention.
extract :: (Compat i, Coord t) => (Int -> NArray i t -> Bool) -> Name -> NArray i t -> NArray i tSource
Select some parts of a tensor, taking into account position and value.
onIndex :: (Coord a, Coord b, Compat i) => ([NArray i a] -> [NArray i b]) -> Name -> NArray i a -> NArray i bSource
Apply a list function to the parts of an array at a given index.
reorder :: Coord t => [Name] -> NArray i t -> NArray i tSource
Change the internal layout of coordinates. The array, considered as an abstract object, does not change.
(~>) :: Coord t => NArray i t -> String -> NArray i tSource

reorder (transpose) the dimensions of the array (with single letter names).

Operations are defined by named indices, so the transposed array is operationally equivalent to the original one.

formatArraySource
:: (Coord t, Compat i)
=> t -> String
-> NArray i t
-> String
Show a multidimensional array as a nested 2D table.
formatFixedSource
:: Compat i
=> Int
-> NArray i Double
-> String
Show the array as a nested table with a "%.nf" format. If all entries are approximate integers the array is shown without the .00.. digits.
formatScaledSource
:: Compat i
=> Int
-> NArray i Double
-> String
Show the array as a nested table with autoscaled entries.
dummyAt :: Int -> NArray i t -> NArray i tSource
Insert a dummy index of dimension 1 at a given level (for formatting purposes).
noIdx :: Compat i => NArray i t -> NArray i tSource
Rename indices so that they are not shown in formatted output.
conformable :: Compat i => [[Idx i]] -> Maybe [Idx i]Source
Obtains most general structure of a list of dimension specifications
sameStructure :: Eq i => NArray i t1 -> NArray i t2 -> BoolSource
Check if two arrays have the same structure.
makeConformant :: (Coord t, Compat i) => [NArray i t] -> [NArray i t]Source
Converts a list of arrays to a common structure.
basisOf :: Coord t => NArray i t -> [NArray i t]Source
Obtain a canonical base for the array.
asScalar :: Coord t => NArray i t -> tSource
Extract the scalar element corresponding to a 0-dimensional array.
asVector :: Coord t => NArray i t -> Vector tSource
Extract the Vector corresponding to a one-dimensional array.
asMatrix :: Coord t => NArray i t -> Matrix tSource
Extract the Matrix corresponding to a two-dimensional array, in the rows,cols order.
fromVector :: Compat i => i -> Vector t -> NArray i tSource
Create a rank-1 array from an hmatrix Vector.
fromMatrix :: (Compat i, Coord t) => i -> i -> Matrix t -> NArray i tSource
Create a rank-2 array from an hmatrix Matrix.
class Element e => Container c e whereSource
conversion utilities
Methods
toComplex :: (c e, c e) -> c (Complex e)Source
fromComplex :: c (Complex e) -> (c e, c e)Source
comp :: c e -> c (Complex e)Source
conj :: c (Complex e) -> c (Complex e)Source
real :: c Double -> c eSource
complex :: c e -> c (Complex Double)Source
show/hide Instances
Produced by Haddock version 2.6.0