sparse-linear-algebra-0.2.0.9: Numerical computation in native Haskell

Safe HaskellSafe
LanguageHaskell2010

Data.Sparse.SpMatrix

Contents

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 #

Set SpMatrix Source # 

Methods

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

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

FiniteDim SpMatrix Source # 

Associated Types

type FDSize (SpMatrix :: * -> *) :: * Source #

Additive SpMatrix Source # 

Methods

zero :: Num a => SpMatrix a Source #

(^+^) :: Num a => SpMatrix a -> SpMatrix a -> 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

dat :: SpMatrix a -> HDData SpMatrix a 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 #

type FDSize SpMatrix Source # 
type HDData SpMatrix a 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 #

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) :

0,1,0,0,0
0,0,0,1,0
0,0,1,0,0
1,0,0,0,0
0,0,0,0,1

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, 4) :

1,0,0,0,0
0,1,0,0,0
0,0,0,0,1
0,0,0,1,0
0,0,1,0,0

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 list (row, col, value)

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

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

toList

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

Populate list with SpMatrix contents and populate missing entries with 0

Lookup

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)

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

Zero-default lookup, infix form ("safe" : throws exception if lookup is outside matrix bounds)

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

lookupWD_IM :: Num a => IntMap (IntMap a) -> (IxRow, IxCol) -> a Source #

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_

Extract i'th row

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

Extract column within a row range

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

Extract column within a row range, rebalance keys

Extract j'th column

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

Extract all 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?

isOrthogonalSM :: SpMatrix Double -> Bool Source #

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

Matrix data and metadata

immSM :: SpMatrix t -> IntMap (IntMap t) Source #

Data in internal representation (do not export)

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

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

Vertical stacking

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

Horizontal stacking

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

Horizontal stacking

Misc. SpMatrix operations

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)

sparsifySM :: SpMatrix Double -> SpMatrix Double Source #

Sparsify an SpMatrix

Value rounding

roundZeroOneSM :: SpMatrix Double -> SpMatrix Double Source #

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

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

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

transposeSM, (#^) : Matrix transpose

Multiply matrix by a scalar

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

Frobenius norm

Matrix-matrix product

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

Matrix-matrix product, sparsified

matMatSparsified :: SpMatrix Double -> SpMatrix Double -> SpMatrix Double Source #

Removes all elements x for which `| x | <= eps`)

(#~#) :: SpMatrix Double -> SpMatrix Double -> SpMatrix Double Source #

Removes all elements x for which `| x | <= eps`)

Sparsified matrix products of two matrices

Matrix contraction

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

Contract two matrices A and B up to an index n, i.e. summing over repeated indices: Aij Bjk , for j in [0 .. n]