hTensor-0.9.0: Multidimensional arrays and simple tensor computations.

Copyright(c) Alberto Ruiz 2009
LicenseBSD3
MaintainerAlberto Ruiz
Stabilityprovisional
Safe HaskellNone
LanguageHaskell98

Numeric.LinearAlgebra.Array.Util

Description

Additional tools for manipulation of multidimensional arrays.

Synopsis

Documentation

class (Num (Vector t), Normed (Vector t), Show t, Numeric t, Indexable (Vector t) t) => Coord t Source

Types that can be elements of the multidimensional arrays.

class (Eq a, Show (Idx a)) => Compat a where Source

Class of compatible indices for contractions.

Methods

compat :: Idx a -> Idx a -> Bool Source

opos :: Idx a -> Idx a Source

data NArray i t Source

A multidimensional array with index type i and elements t.

Instances

Coord t => Show (Array t) 
Coord t => Show (Tensor t) 

data Idx i Source

Dimension descriptor.

Constructors

Idx 

Fields

iType :: i
 
iDim :: Int
 
iName :: Name
 

Instances

Eq i => Eq (Idx i) Source 
Eq i => Ord (Idx i) Source 
Show (Idx None) 
Show (Idx Variant) 

type Name = String Source

indices are denoted by strings, (frequently single-letter)

scalar :: Coord t => t -> NArray i t Source

Create a 0-dimensional structure.

order :: NArray i t -> Int Source

The number of dimensions of a multidimensional array.

names :: NArray i t -> [Name] Source

Index names.

size :: Name -> NArray i t -> Int Source

Dimension of given index.

sizes :: NArray i t -> [Int] Source

typeOf :: Compat i => Name -> NArray i t -> i Source

Type of given index.

dims :: NArray i t -> [Idx i] Source

Get detailed dimension information about the array.

coords :: NArray i t -> Vector t Source

Get the coordinates of an array as a flattened structure (in the order specified by dims).

renameExplicit :: (Compat i, Coord t) => [(Name, Name)] -> NArray i t -> NArray i t Source

Rename indices using an association list.

(!>) :: (Compat i, Coord t) => NArray i t -> [Char] -> NArray i t infixl 9 Source

Explicit renaming of single letter index names.

For instance, t >@> "pi qj" changes index "p" to "i" and "q" to "j".

renameO :: (Coord t, Compat i) => NArray i t -> [Name] -> NArray i t Source

Rename indices in alphabetical order. Equal indices of compatible type are contracted out.

(!) :: (Compat i, Coord t) => NArray i t -> [Char] -> NArray i t infixl 9 Source

Rename indices in alphabetical order (renameO) using single letter names.

parts Source

Arguments

:: Coord t 
=> NArray i t 
-> Name

index to expand

-> [NArray i t] 

Create a list of the substructures at the given level.

newIndex Source

Arguments

:: (Coord t, Compat i) 
=> i

index type

-> 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 b Source

Apply a function (defined on hmatrix Vectors) to all elements of a structure. Use mapArray (mapVector f) for general functions.

zipArray Source

Arguments

:: (Coord a, Coord b, Compat i) 
=> (Vector a -> Vector b -> Vector c)

transformation

-> NArray i a 
-> NArray i b 
-> NArray i c 

Apply an element-by-element binary function to the coordinates of two arrays. The arguments are automatically made conformant.

(|*|) :: (Coord t, Compat i) => NArray i t -> NArray i t -> NArray i t infixl 5 Source

Tensor product with automatic contraction of repeated indices, following Einstein summation convention.

smartProduct :: (Coord t, Compat i, Num (NArray i t)) => [NArray i t] -> NArray i t Source

This is equivalent to the regular product, but in the order that minimizes the size of the intermediate factors.

outers :: (Coord a, Compat i) => [NArray i a] -> NArray i a Source

Outer product of a list of arrays along the common indices.

extract :: (Compat i, Coord t) => (Int -> NArray i t -> Bool) -> Name -> NArray i t -> NArray i t Source

Select some parts of an array, 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 b Source

Apply a list function to the parts of an array at a given index.

mapTat :: (Coord a, Coord b, Compat i) => (NArray i a -> NArray i b) -> [Name] -> NArray i a -> NArray i b Source

Map a function at the internal level selected by a set of indices

reorder :: Coord t => [Name] -> NArray i t -> NArray i t Source

Change the internal layout of coordinates. The array, considered as an abstract object, does not change.

(~>) :: Coord t => NArray i t -> String -> NArray i t infixl 8 Source

reorder (transpose) 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.

formatArray Source

Arguments

:: (Coord t, Compat i) 
=> (t -> String)

format function (eg. printf "5.2f")

-> NArray i t 
-> String 

Show a multidimensional array as a nested 2D table.

formatFixed Source

Arguments

:: Compat i 
=> Int

number of of decimal places

-> 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.

formatScaled Source

Arguments

:: Compat i 
=> Int

number of of decimal places

-> NArray i Double 
-> String 

Show the array as a nested table with autoscaled entries.

dummyAt :: Coord t => Int -> NArray i t -> NArray i t Source

Insert a dummy index of dimension 1 at a given level (for formatting purposes).

noIdx :: Compat i => NArray i t -> NArray i t Source

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 -> Bool Source

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.

atT :: (Compat i, Coord t) => NArray i t -> [Int] -> NArray i t Source

takeDiagT :: (Compat i, Coord t) => NArray i t -> [t] Source

diagT :: [Double] -> Int -> Array Double Source

Multidimensional diagonal of given order.

mkFun :: [Int] -> ([Int] -> Double) -> Array Double Source

Define an array using a function.

mkAssoc :: [Int] -> [([Int], Double)] -> Array Double Source

Define an array using an association list.

setType :: (Compat i, Coord t) => Name -> i -> NArray i t -> NArray i t Source

Change type of index.

renameParts Source

Arguments

:: (Compat i, Coord t) 
=> Name

index of the parts to extract

-> NArray i t

input array

-> Name

index to renameRaw

-> String

prefix for the new names

-> [NArray i t]

list or results

Extract the parts of an array, and renameRaw one of the remaining indices with succesive integers.

resetCoords :: Coord t => NArray i t -> Vector t -> NArray i t Source

change the whole set of coordinates.

asScalar :: Coord t => NArray i t -> t Source

Extract the scalar element corresponding to a 0-dimensional array.

asVector :: Coord t => NArray i t -> Vector t Source

Extract the Vector corresponding to a one-dimensional array.

asMatrix :: Coord t => NArray i t -> Matrix t Source

Extract the Matrix corresponding to a two-dimensional array, in the rows,cols order.

applyAsMatrix :: (Coord t, Compat i) => (Matrix t -> Matrix t) -> NArray i t -> NArray i t Source

fibers :: Coord t => Name -> NArray i t -> Matrix t Source

Obtain a matrix whose columns are the fibers of the array in the given dimension. The column order depends on the selected index (see matrixator).

matrixator Source

Arguments

:: Coord t 
=> NArray i t

input array

-> [Name]

row dimensions

-> [Name]

column dimensions

-> Matrix t

result

Reshapes an array as a matrix with the desired dimensions as flattened rows and flattened columns.

matrixatorFree Source

Arguments

:: Coord t 
=> NArray i t

input array

-> [Name]

row dimensions

-> (Matrix t, [Name])

(result, column dimensions)

Reshapes an array as a matrix with the desired dimensions as flattened rows and flattened columns. We do not force the order of the columns.

analyzeProduct :: (Coord t, Compat i) => NArray i t -> NArray i t -> Maybe (NArray i t, Int) Source

fromVector :: (Coord t, Compat i) => i -> Vector t -> NArray i t Source

Create a 1st order array from a Vector.

fromMatrix :: (Compat i, Coord t) => i -> i -> Matrix t -> NArray i t Source

Create a 2nd order array from a Matrix.