sparse-linear-algebra-0.2.9.9: Numerical computing in native Haskell

Copyright(C) 2016 Marco Zocca
LicenseGPL-3 (see LICENSE)
Maintainerzocca.marco gmail
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Sparse.SpMatrix

Contents

Description

 

Synopsis

Sparse Matrix

data SpMatrix a Source #

Constructors

SM 

Fields

Instances

Functor SpMatrix Source # 

Methods

fmap :: (a -> b) -> SpMatrix a -> SpMatrix b #

(<$) :: a -> SpMatrix b -> SpMatrix a #

Foldable SpMatrix Source # 

Methods

fold :: Monoid m => SpMatrix m -> m #

foldMap :: Monoid m => (a -> m) -> SpMatrix a -> m #

foldr :: (a -> b -> b) -> b -> SpMatrix a -> b #

foldr' :: (a -> b -> b) -> b -> SpMatrix a -> b #

foldl :: (b -> a -> b) -> b -> SpMatrix a -> b #

foldl' :: (b -> a -> b) -> b -> SpMatrix a -> b #

foldr1 :: (a -> a -> a) -> SpMatrix a -> a #

foldl1 :: (a -> a -> a) -> SpMatrix a -> a #

toList :: SpMatrix a -> [a] #

null :: SpMatrix a -> Bool #

length :: SpMatrix a -> Int #

elem :: Eq a => a -> SpMatrix a -> Bool #

maximum :: Ord a => SpMatrix a -> a #

minimum :: Ord a => SpMatrix a -> a #

sum :: Num a => SpMatrix a -> a #

product :: Num a => SpMatrix a -> a #

Set SpMatrix Source # 

Methods

liftU2 :: (a -> a -> a) -> SpMatrix a -> SpMatrix a -> SpMatrix a Source #

liftI2 :: (a -> a -> b) -> SpMatrix a -> SpMatrix a -> SpMatrix b Source #

Eq a => Eq (SpMatrix a) Source # 

Methods

(==) :: SpMatrix a -> SpMatrix a -> Bool #

(/=) :: SpMatrix a -> SpMatrix a -> Bool #

Show a => Show (SpMatrix a) Source # 

Methods

showsPrec :: Int -> SpMatrix a -> ShowS #

show :: SpMatrix a -> String #

showList :: [SpMatrix a] -> ShowS #

Num a => SpContainer (SpMatrix a) Source #

SpMatrixes are sparse containers too, i.e. any specific component may be missing (so it is assumed to be 0)

Associated Types

type ScIx (SpMatrix a) :: * Source #

type ScElem (SpMatrix a) :: * Source #

Sparse (SpMatrix a) Source # 

Methods

spy :: Fractional b => SpMatrix a -> b Source #

HasData (SpMatrix a) Source # 

Associated Types

type HDData (SpMatrix a) :: * Source #

Methods

nnz :: SpMatrix a -> Int Source #

dat :: SpMatrix a -> HDData (SpMatrix a) Source #

FiniteDim (SpMatrix a) Source #

SpMatrixes are maps between finite-dimensional spaces

Associated Types

type FDSize (SpMatrix a) :: * Source #

Methods

dim :: SpMatrix a -> FDSize (SpMatrix a) Source #

MatrixRing (SpMatrix Double) Source # 
MatrixRing (SpMatrix (Complex Double)) Source # 
Num a => AdditiveGroup (SpMatrix a) Source #

SpMatrixes form an additive group, in that they can have an invertible associtative operation (matrix sum)

type ScIx (SpMatrix a) Source # 
type ScIx (SpMatrix a) = (Rows, Cols)
type ScElem (SpMatrix a) Source # 
type ScElem (SpMatrix a) = a
type HDData (SpMatrix a) Source # 
type HDData (SpMatrix a)
type FDSize (SpMatrix a) Source # 
type FDSize (SpMatrix a) = (Rows, Cols)
type MatrixNorm (SpMatrix Double) Source # 
type MatrixNorm (SpMatrix (Complex Double)) Source # 

Creation

zeroSM :: Rows -> Cols -> SpMatrix a Source #

`zeroSM m n` : Empty SpMatrix of size (m, n)

Diagonal matrix

mkDiagonal :: Int -> [a] -> SpMatrix a Source #

`mkDiagonal n ll` : create a diagonal matrix of size n from a list ll of elements

Identity matrix

eye :: Num a => Int -> SpMatrix a Source #

`eye n` : identity matrix of rank n

Permutation matrix

permutationSM :: Num a => Int -> [IxRow] -> SpMatrix a Source #

Permutation matrix from a (possibly incomplete) list of row swaps starting from row 0 e.g. `permutationSM 5 [1,3]` first swaps rows (0, 1) and then rows (1, 3) :

>>> prd (permutationSM 5 [1,3] :: SpMatrix Double)
( 5 rows, 5 columns ) , 5 NZ ( density 20.000 % )

_      , 1.00   , _      , _      , _      
_      , _      , _      , 1.00   , _      
_      , _      , 1.00   , _      , _      
1.00   , _      , _      , _      , _      
_      , _      , _      , _      , 1.00

permutPairsSM :: Num a => Int -> [(IxRow, IxRow)] -> SpMatrix a Source #

Permutation matrix from a (possibly incomplete) list of row pair swaps e.g. `permutPairs 5 [(2,4)]` swaps rows 2 and 4 :

>>> prd (permutPairsSM 5 [(2,4)] :: SpMatrix Double)
( 5 rows, 5 columns ) , 5 NZ ( density 20.000 % )

1.00   , _      , _      , _      , _      
_      , 1.00   , _      , _      , _      
_      , _      , _      , _      , 1.00   
_      , _      , _      , 1.00   , _      
_      , _      , 1.00   , _      , _

Super- or sub- diagonal matrix

mkSubDiagonal :: Int -> Int -> [a] -> SpMatrix a Source #

`mkSubDiagonal n o xx` creates a square SpMatrix of size n with xx on the oth subdiagonal

Element insertion

insertSpMatrix :: IxRow -> IxCol -> a -> SpMatrix a -> SpMatrix a Source #

Insert an element in a preexisting Spmatrix at the specified indices

fromList

fromListSM' :: Foldable t => t (IxRow, IxCol, a) -> SpMatrix a -> SpMatrix a Source #

Add to existing SpMatrix using data from list (row, col, value)

fromListSM :: Foldable t => (Int, Int) -> t (IxRow, IxCol, a) -> SpMatrix a Source #

Create new SpMatrix using data from a Foldable (e.g. a list) in (row, col, value) form

mkSpMR :: Foldable t => (Int, Int) -> t (IxRow, IxCol, Double) -> SpMatrix Double Source #

mkSpMC :: Foldable t => (Int, Int) -> t (IxRow, IxCol, Complex Double) -> SpMatrix (Complex Double) Source #

fromListDenseSM :: Int -> [a] -> SpMatrix a Source #

Create new SpMatrix assuming contiguous, 0-based indexing of elements

toList

toListSM :: SpMatrix t -> [(IxRow, IxCol, t)] Source #

Populate list with SpMatrix contents

toDenseListSM :: Num t => SpMatrix t -> [(IxRow, IxCol, t)] Source #

Populate list with SpMatrix contents and populate missing entries with 0

Lookup

lookupSM :: SpMatrix a -> IxRow -> IxCol -> Maybe a Source #

lookupWD_SM :: Num a => SpMatrix a -> (IxRow, IxCol) -> a Source #

Looks up an element in the matrix with a default (if the element is not found, zero is returned)

(@@!) :: Num a => SpMatrix a -> (IxRow, IxCol) -> a Source #

Zero-default lookup, infix form (no bound checking)

Looks up an element in the matrix with a default (if the element is not found, zero is returned)

Sub-matrices

filterSM :: (Key -> Key -> a -> Bool) -> SpMatrix a -> SpMatrix a Source #

Indexed filtering function

extractDiag :: SpMatrix a -> SpMatrix a Source #

Diagonal, subdiagonal, superdiagonal partitions of a SpMatrix (useful for writing preconditioners)

extractSuperDiag :: SpMatrix a -> SpMatrix a Source #

Diagonal, subdiagonal, superdiagonal partitions of a SpMatrix (useful for writing preconditioners)

extractSubDiag :: SpMatrix a -> SpMatrix a Source #

Diagonal, subdiagonal, superdiagonal partitions of a SpMatrix (useful for writing preconditioners)

extractSubmatrixSM :: (Key -> Key) -> (Key -> Key) -> SpMatrix a -> (IxRow, IxRow) -> (IxCol, IxCol) -> SpMatrix a Source #

Extract a submatrix given the specified index bounds, rebalancing keys with the two supplied functions

extractSubmatrixRebalanceKeys :: SpMatrix a -> (IxRow, IxRow) -> (IxCol, IxCol) -> SpMatrix a Source #

Extract a submatrix given the specified index bounds NB : subtracts (i1, j1) from the indices

extractSubmatrix :: SpMatrix a -> (IxRow, IxRow) -> (IxCol, IxCol) -> SpMatrix a Source #

Extract a submatrix given the specified index bounds NB : submatrix indices are _preserved_

takeRows :: IxRow -> SpMatrix a -> SpMatrix a Source #

takeCols :: IxCol -> SpMatrix a -> SpMatrix a Source #

Extract i'th row

Extract j'th column

extractColSM :: SpMatrix a -> IxCol -> SpMatrix a Source #

Extract whole column

extractSubColSM :: SpMatrix a -> IxCol -> (IxRow, IxRow) -> SpMatrix a Source #

Extract column within a row range

extractSubColSM_RK :: SpMatrix a -> IxCol -> (IxRow, IxRow) -> SpMatrix a Source #

Extract column within a row range, rebalance keys

Predicates

isValidIxSM :: SpMatrix a -> (Int, Int) -> Bool Source #

Are the supplied indices within matrix bounds?

isSquareSM :: SpMatrix a -> Bool Source #

Is the matrix square?

isDiagonalSM :: SpMatrix a -> Bool Source #

Is the matrix diagonal?

isLowerTriSM :: Eq a => SpMatrix a -> Bool Source #

Is the matrix lower/upper triangular?

isUpperTriSM :: Eq a => SpMatrix a -> Bool Source #

Is the matrix lower/upper triangular?

isOrthogonalSM :: (Eq a, Epsilon a, MatrixRing (SpMatrix a)) => SpMatrix a -> Bool Source #

Is the matrix orthogonal? i.e. Q^t ## Q == I

Matrix data and metadata

immSM :: SpMatrix a -> IntM (IntM a) Source #

Data in internal representation (do not export) immSM :: SpMatrix t -> IM.IntMap (IM.IntMap t)

dimSM :: SpMatrix t -> (Rows, Cols) Source #

(Number of rows, Number of columns)

nelSM :: SpMatrix t -> Int Source #

Number of rows times number of columns

nrows :: SpMatrix a -> Rows Source #

Number of rows

ncols :: SpMatrix a -> Cols Source #

Number of columns

data SMInfo Source #

Constructors

SMInfo 

Fields

Instances

Non-zero elements in a row

Bandwidth bounds (min, max)

Matrix stacking

vertStackSM :: SpMatrix a -> SpMatrix a -> SpMatrix a Source #

Vertical stacking of matrix blocks

(-=-) :: SpMatrix a -> SpMatrix a -> SpMatrix a Source #

Vertical stacking of matrix blocks

horizStackSM :: SpMatrix a -> SpMatrix a -> SpMatrix a Source #

Horizontal stacking of matrix blocks

(-||-) :: SpMatrix a -> SpMatrix a -> SpMatrix a Source #

Horizontal stacking of matrix blocks

fromBlocksDiag :: [SpMatrix a] -> SpMatrix a Source #

Assemble a block-diagonal square matrix from a list of square matrices, arranging these along the main diagonal

Misc. SpMatrix operations

ifilterSM :: (Key -> Key -> a -> Bool) -> SpMatrix a -> SpMatrix a Source #

Indexed filter over SpMatrix

foldlSM :: (a -> b -> b) -> b -> SpMatrix a -> b Source #

Left fold over SpMatrix

ifoldlSM :: (Key -> Key -> a -> b -> b) -> b -> SpMatrix a -> b Source #

Indexed left fold over SpMatrix

countSubdiagonalNZSM :: SpMatrix a -> Int Source #

Count sub-diagonal nonzeros

subdiagIndicesSM :: SpMatrix a -> [(IxRow, IxCol)] Source #

Filter the index subset that lies below the diagonal (used in the QR decomposition, for example)

Sparsify : remove almost-0 elements (|x| < eps)

sparsifyIM2 :: Epsilon a => IntM (IntM a) -> IntM (IntM a) Source #

sparsifySM :: Epsilon a => SpMatrix a -> SpMatrix a Source #

Sparsify an SpMatrix

Value rounding

roundZeroOneSM :: Epsilon a => SpMatrix a -> SpMatrix a Source #

Round almost-0 and almost-1 to 0 and 1 respectively

modifyKeysSM' :: (IxRow -> a) -> (IxCol -> b) -> SpMatrix c -> [(a, b, c)] Source #

Modify (row, column) keys, leaving data intact. Be careful when using this! modifyKeysSM' :: (IxRow -> IxRow) -> (IxCol -> IxCol) -> SpMatrix a -> SpMatrix a

modifyKeysSM :: (IxRow -> IxRow) -> (IxCol -> IxCol) -> SpMatrix a -> SpMatrix a Source #

Primitive algebra operations

Matrix row swap

swapRows :: IxRow -> IxRow -> SpMatrix a -> SpMatrix a Source #

Swap two rows of a SpMatrix (bounds not checked)

swapRowsSafe :: IxRow -> IxRow -> SpMatrix a -> SpMatrix a Source #

Swap two rows of a SpMatrix (bounds checked)

Matrix transpose

transposeSM :: SpMatrix a -> SpMatrix a Source #

transposeSM : Matrix transpose

hermitianConj :: Num a => SpMatrix (Complex a) -> SpMatrix (Complex a) Source #

Hermitian conjugate

Multiply matrix by a scalar

matScale :: Num a => a -> SpMatrix a -> SpMatrix a Source #

Trace

trace :: Num b => SpMatrix b -> b Source #

Matrix trace

Frobenius norm

Matrix-matrix product

data MatProd_ Source #

Internal implementation

Constructors

AB 
ABt 

matMatUnsafeWith :: Num a1 => (IntM (IntM a2) -> IntM (IntM a1)) -> SpMatrix a1 -> SpMatrix a2 -> SpMatrix a1 Source #

Matrix product without dimension checks

Matrix-matrix product, sparsified

matMatSparsified :: (MatrixRing (SpMatrix a), Epsilon a) => SpMatrix a -> SpMatrix a -> SpMatrix a Source #

After multiplying the two matrices, all elements x for which `| x | <= eps` are removed.

(#~#) :: (MatrixRing (SpMatrix a), Epsilon a) => SpMatrix a -> SpMatrix a -> SpMatrix a Source #

After multiplying the two matrices, all elements x for which `| x | <= eps` are removed.

Sparsified matrix products of two matrices

(#~#^) :: (MatrixRing (SpMatrix a), Epsilon a) => SpMatrix a -> SpMatrix a -> SpMatrix a Source #

Sparsifying A^T B

(#~^#) :: (MatrixRing (SpMatrix a), Epsilon a) => SpMatrix a -> SpMatrix a -> SpMatrix a Source #

Sparsifying A B^T

Partial inner product

contractSub :: Elt a => SpMatrix a -> SpMatrix a -> IxRow -> IxCol -> Int -> a Source #

Contract row i of A with column j of B up to an index n, i.e. summing over repeated indices: Aij Bjk , for j in [0 .. n]