sparse-linear-algebra-0.2.9.1: Sparse linear algebra in native Haskell.

Copyright(c) Marco Zocca 2017
LicenseGPL-style (see the file LICENSE)
Maintainerzocca marco gmail
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Numeric.LinearAlgebra.Class

Contents

Description

Typeclasses for linear algebra and related concepts

Synopsis

Matrix and vector elements (possibly Complex)

class (Eq e, Fractional e, Floating e, Num (EltMag e), Ord (EltMag e)) => Elt e where Source #

Minimal complete definition

mag

Associated Types

type EltMag e :: * Source #

Methods

conj :: e -> e Source #

mag :: e -> EltMag e Source #

Instances

Elt Double Source # 

Associated Types

type EltMag Double :: * Source #

Elt Float Source # 

Associated Types

type EltMag Float :: * Source #

RealFloat e => Elt (Complex e) Source # 

Associated Types

type EltMag (Complex e) :: * Source #

Methods

conj :: Complex e -> Complex e Source #

mag :: Complex e -> EltMag (Complex e) Source #

Vector space

(.*) :: VectorSpace v => Scalar v -> v -> v Source #

Scale a vector

(./) :: (VectorSpace v, Fractional (Scalar v)) => v -> Scalar v -> v Source #

Scale a vector by the reciprocal of a number (e.g. for normalization)

lerp :: (VectorSpace e, Num (Scalar e)) => Scalar e -> e -> e -> e Source #

Convex combination of two vectors (NB: 0 <= a <= 1).

Hilbert space (inner product)

dot :: InnerSpace v => v -> v -> Scalar v Source #

Inner product

Hilbert-space distance function

hilbertDistSq :: InnerSpace v => v -> v -> Scalar v Source #

`hilbertDistSq x y = || x - y ||^2` computes the squared L2 distance between two vectors

Normed vector spaces

class (InnerSpace v, Num (RealScalar v), Eq (RealScalar v), Epsilon (Magnitude v), Show (Magnitude v), Ord (Magnitude v)) => Normed v where Source #

Minimal complete definition

norm1, norm2Sq, normP, normalize, normalize2

Associated Types

type Magnitude v :: * Source #

type RealScalar v :: * Source #

Instances

Normed Double Source # 
Normed (Complex Double) Source # 
Normed (SpVector Double) Source # 
Normed (SpVector (Complex Double)) Source # 

normInftyR :: (Foldable t, Ord a) => t a -> a Source #

Infinity-norm (Real)

normInftyC :: (Foldable t, RealFloat a, Functor t) => t (Complex a) -> a Source #

Infinity-norm (Complex)

dotLp :: (Set t, Foldable t, Floating a) => a -> t a -> t a -> a Source #

Lp inner product (p > 0)

reciprocal :: (Functor f, Fractional b) => f b -> f b Source #

Reciprocal

scale :: (Num b, Functor f) => b -> f b -> f b Source #

Scale

Matrix ring

class (AdditiveGroup m, Epsilon (MatrixNorm m)) => MatrixRing m where Source #

A matrix ring is any collection of matrices over some ring R that form a ring under matrix addition and matrix multiplication

Minimal complete definition

(##), (##^), transpose, normFrobenius

Associated Types

type MatrixNorm m :: * Source #

Methods

(##) :: m -> m -> m Source #

(##^) :: m -> m -> m Source #

(#^#) :: m -> m -> m Source #

transpose :: m -> m Source #

normFrobenius :: m -> MatrixNorm m Source #

Linear vector space

class (VectorSpace v, MatrixRing (MatrixType v)) => LinearVectorSpace v where Source #

Minimal complete definition

(#>), (<#)

Associated Types

type MatrixType v :: * Source #

Methods

(#>) :: MatrixType v -> v -> v Source #

(<#) :: v -> MatrixType v -> v Source #

LinearVectorSpace + Normed

Linear systems

class LinearVectorSpace v => LinearSystem v where Source #

Minimal complete definition

(<\>)

Methods

(<\>) :: (MonadIO m, MonadThrow m) => MatrixType v -> v -> m v Source #

FiniteDim : finite-dimensional objects

class Functor f => FiniteDim f where Source #

Minimal complete definition

dim

Associated Types

type FDSize f :: * Source #

Methods

dim :: f a -> FDSize f Source #

Instances

FiniteDim SpVector Source #

SpVectors form a vector space because they can be multiplied by a scalar

SpVectors are finite-dimensional vectors

Associated Types

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

FiniteDim SpMatrix Source #

SpMatrixes are maps between finite-dimensional spaces

Associated Types

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

class FiniteDim' f where Source #

Minimal complete definition

dim'

Associated Types

type FDSize' f :: * Source #

Methods

dim' :: f -> FDSize' f Source #

HasData : accessing inner data (do not export)

class HasData f a where Source #

Minimal complete definition

nnz, dat

Associated Types

type HDData f a :: * Source #

Methods

nnz :: f a -> Int Source #

dat :: f a -> HDData f a Source #

Instances

HasData SpVector a Source # 

Associated Types

type HDData (SpVector :: * -> *) a :: * Source #

HasData SpMatrix a Source # 

Associated Types

type HDData (SpMatrix :: * -> *) a :: * Source #

class HasData' f where Source #

Minimal complete definition

nnz', dat'

Associated Types

type HDD f :: * Source #

Methods

nnz' :: f -> Int Source #

dat' :: f -> HDD f Source #

Sparse : sparse datastructures

class (FiniteDim f, HasData f a) => Sparse f a where Source #

Minimal complete definition

spy

Methods

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

Instances

Sparse SpVector a Source # 

Methods

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

Sparse SpMatrix a Source # 

Methods

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

class (FiniteDim' f, HasData' f) => Sparse' f where Source #

Minimal complete definition

spy'

Methods

spy' :: Fractional b => f -> b Source #

Set : types that behave as sets

class Functor f => Set f where Source #

Minimal complete definition

liftU2, liftI2

Methods

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

union binary lift : apply function on _union_ of two "sets"

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

intersection binary lift : apply function on _intersection_ of two "sets"

Instances

Set SpVector Source # 

Methods

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

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

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 #

SpContainer : sparse container datastructures. Insertion, lookup, toList, lookup with 0 default

class Sparse c a => SpContainer c a where Source #

Minimal complete definition

scInsert, scLookup, scToList, (@@)

Associated Types

type ScIx c :: * Source #

Methods

scInsert :: ScIx c -> a -> c a -> c a Source #

scLookup :: c a -> ScIx c -> Maybe a Source #

scToList :: c a -> [(ScIx c, a)] Source #

(@@) :: c a -> ScIx c -> a Source #

Instances

Elt a => SpContainer SpVector a Source #

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

Associated Types

type ScIx (SpVector :: * -> *) :: * Source #

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 :: * -> *) :: * Source #

class SpContainer' c where Source #

Minimal complete definition

scInsert', scLookup', scToList'

Associated Types

type ScIx' c :: * Source #

Methods

scInsert' :: ScIx' c -> a -> c -> c Source #

scLookup' :: c -> ScIx' c -> Maybe a Source #

scToList' :: c -> [a] Source #

SparseVector

class SpContainer v e => SparseVector v e where Source #

Minimal complete definition

svFromList, svFromListDense, svConcat

Associated Types

type SpvIx v :: * Source #

Methods

svFromList :: Int -> [(SpvIx v, e)] -> v e Source #

svFromListDense :: Int -> [e] -> v e Source #

svConcat :: Foldable t => t (v e) -> v e Source #

SparseMatrix

class SpContainer m e => SparseMatrix m e where Source #

Minimal complete definition

smFromVector, smTranspose, encodeIx, decodeIx

Methods

smFromVector :: LexOrd -> (Int, Int) -> Vector (IxRow, IxCol, e) -> m e Source #

smTranspose :: m e -> m e Source #

encodeIx :: m e -> LexOrd -> (IxRow, IxCol) -> LexIx Source #

decodeIx :: m e -> LexOrd -> LexIx -> (IxRow, IxCol) Source #

SparseMatVec

Utilities

toC :: Num a => a -> Complex a Source #

Lift a real number onto the complex plane