| Copyright | (c) Alberto Ruiz 2009 | 
|---|---|
| License | BSD3 | 
| Maintainer | Alberto Ruiz | 
| Stability | provisional | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Numeric.LinearAlgebra.Array.Util
Description
Additional tools for manipulation of multidimensional arrays.
- class (Num (Vector t), Field t, Normed Vector t, Show t) => Coord t
- class (Eq a, Show (Idx a)) => Compat a where
- data NArray i t
- data Idx i = Idx {}
- type Name = String
- scalar :: Coord t => t -> NArray i t
- order :: NArray i t -> Int
- names :: NArray i t -> [Name]
- size :: Name -> NArray i t -> Int
- sizes :: NArray i t -> [Int]
- typeOf :: Compat i => Name -> NArray i t -> i
- dims :: NArray i t -> [Idx i]
- coords :: NArray i t -> Vector t
- renameExplicit :: (Compat i, Coord t) => [(Name, Name)] -> NArray i t -> NArray i t
- (!>) :: (Compat i, Coord t) => NArray i t -> [Char] -> NArray i t
- renameO :: (Coord t, Compat i) => NArray i t -> [Name] -> NArray i t
- (!) :: (Compat i, Coord t) => NArray i t -> [Char] -> 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
- smartProduct :: (Coord t, Compat i, Num (NArray i t)) => [NArray i t] -> NArray i t
- outers :: (Coord a, Compat i) => [NArray i a] -> NArray i a
- 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
- mapTat :: (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 :: Coord t => 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]
- atT :: (Compat i, Coord t) => NArray i t -> [Int] -> NArray i t
- takeDiagT :: (Compat i, Coord t) => NArray i t -> [t]
- diagT :: [Double] -> Int -> Array Double
- mkFun :: [Int] -> ([Int] -> Double) -> Array Double
- mkAssoc :: [Int] -> [([Int], Double)] -> Array Double
- setType :: (Compat i, Coord t) => Name -> i -> NArray i t -> NArray i t
- renameParts :: (Compat i, Coord t) => Name -> NArray i t -> Name -> String -> [NArray i t]
- resetCoords :: Coord t => NArray i t -> Vector 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
- applyAsMatrix :: (Coord t, Compat i) => (Matrix t -> Matrix t) -> NArray i t -> NArray i t
- fibers :: Coord t => Name -> NArray i t -> Matrix t
- matrixator :: Coord t => NArray i t -> [Name] -> [Name] -> Matrix t
- matrixatorFree :: Coord t => NArray i t -> [Name] -> (Matrix t, [Name])
- analyzeProduct :: (Coord t, Compat i) => NArray i t -> NArray i t -> Maybe (NArray i t, Int)
- fromVector :: (Coord t, Compat i) => i -> Vector t -> NArray i t
- fromMatrix :: (Compat i, Coord t) => i -> i -> Matrix t -> NArray i t
Documentation
class (Num (Vector t), Field t, Normed Vector t, Show t) => Coord t Source
Types that can be elements of the multidimensional arrays.
A multidimensional array with index type i and elements t.
Instances
| Coord t => Show (Array t) | |
| Coord t => Show (Tensor t) | |
| (Eq t, Coord t, Compat i) => Eq (NArray i t) | |
| (Coord t, Compat i, Fractional (NArray i t), Floating 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) | 
Dimension descriptor.
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.
Create a list of the substructures at the given level.
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.
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.
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.
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.
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.
mkAssoc :: [Int] -> [([Int], Double)] -> Array Double Source
Define an array using an association list.
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.
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).
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.
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.