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

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

Data.Sparse.Common

Contents

Description

 

Synopsis

Documentation

insertRowWith :: (IxCol -> IxCol) -> SpMatrix a -> SpVector a -> Key -> SpMatrix a Source #

Insert row , using the provided row index transformation function

insertRow :: SpMatrix a -> SpVector a -> Key -> SpMatrix a Source #

Insert row

insertColWith :: (IxRow -> IxRow) -> SpMatrix a -> SpVector a -> IxCol -> SpMatrix a Source #

Insert column, using the provided row index transformation function

insertCol :: SpMatrix a -> SpVector a -> IxCol -> SpMatrix a Source #

Insert column

diagonalSM :: SpVector a -> SpMatrix a Source #

Fill the diagonal of a SpMatrix with the components of a SpVector

outerProdSV :: Num a => SpVector a -> SpVector a -> SpMatrix a Source #

Outer product

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

Outer product

toSV :: SpMatrix a -> SpVector a Source #

Demote (n x 1) or (1 x n) SpMatrix to SpVector

svToSM :: SpVector a -> SpMatrix a Source #

promote a SV to SM

lookupRowSM :: SpMatrix a -> IxRow -> Maybe (SpVector a) Source #

Lookup a row in a SpMatrix; returns an SpVector with the row, if this is non-empty

extractCol :: SpMatrix a -> IxCol -> SpVector a Source #

Extract jth column

extractRow :: SpMatrix a -> IxRow -> SpVector a Source #

Extract ith row

extractVectorDenseWith :: Num a => (Int -> (IxRow, IxCol)) -> SpMatrix a -> SpVector a Source #

Generic extraction function

extractRowDense :: Num a => SpMatrix a -> IxRow -> SpVector a Source #

Extract ith row (dense)

extractColDense :: Num a => SpMatrix a -> IxCol -> SpVector a Source #

Extract jth column

extractDiagDense :: Num a => SpMatrix a -> SpVector a Source #

Extract the diagonal

extractSubRow :: SpMatrix a -> IxRow -> (Int, Int) -> SpVector a Source #

extract row interval (all entries between columns j1 and j2, INCLUDED, are returned) extractSubRow :: SpMatrix a -> IxRow -> (IxCol, IxCol) -> SpVector a extractSubRow m i (j1, j2) = case lookupRowSM m i of Nothing -> zeroSV (ncols m) Just rv -> ifilterSV (j _ -> j >= j1 && j <= j2) rv

", returning in Maybe extractSubRow :: SpMatrix a -> IxRow -> (Int, Int) -> Maybe (SpVector a) extractSubRow m i (j1, j2) = resizeSV (j2 - j1) . ifilterSV (j _ -> j >= j1 && j j2) <$ lookupRowSM m i

Extract an interval of SpVector components, changing accordingly the resulting SpVector size. Keys are _not_ rebalanced, i.e. components are still labeled according with respect to the source matrix.

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

extract column interval

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

extract row interval, rebalance keys by subtracting lowest one

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

extract column interval, rebalance keys by subtracting lowest one

fromRowsL :: [SpVector a] -> SpMatrix a Source #

Pack a list of SpVectors as rows of an SpMatrix

fromRowsV :: Vector (SpVector a) -> SpMatrix a Source #

Pack a V.Vector of SpVectors as rows of an SpMatrix

fromColsV :: Vector (SpVector a) -> SpMatrix a Source #

Pack a V.Vector of SpVectors as columns of an SpMatrix

fromColsL :: [SpVector a] -> SpMatrix a Source #

Pack a list of SpVectors as columns an SpMatrix

toRowsL :: SpMatrix a -> [SpVector a] Source #

Unpack the rows of an SpMatrix into a list of SpVectors

toColsL :: SpMatrix a -> [SpVector a] Source #

Unpack the columns of an SpMatrix into a list of SpVectors

Orphan instances

PrintDense (SpVector Double) Source # 
PrintDense (SpVector (Complex Double)) Source # 
PrintDense (SpMatrix Double) Source # 
PrintDense (SpMatrix (Complex Double)) Source # 
(InnerSpace t, (~) * (Scalar t) t) => LinearVectorSpace (SpVector t) Source # 

Associated Types

type MatrixType (SpVector t) :: * Source #