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

Safe HaskellSafe
LanguageHaskell2010

Numeric.LinearAlgebra.Class

Contents

Synopsis

Additive ring

class Functor f => Additive f where Source #

Minimal complete definition

zero, (^+^)

Methods

zero :: Num a => f a Source #

Ring zero element

(^+^) :: Num a => f a -> f a -> f a Source #

Ring +

Instances

negated :: (Num a, Functor f) => f a -> f a Source #

negate the values in a functor

(^-^) :: (Additive f, Num a) => f a -> f a -> f a Source #

subtract two Additive objects

Vector space

class Additive f => VectorSpace f where Source #

Minimal complete definition

(.*)

Methods

(.*) :: Num a => a -> f a -> f a Source #

multiplication by a scalar

Instances

VectorSpace SpVector Source # 

Methods

(.*) :: Num a => a -> SpVector a -> SpVector a Source #

lerp :: (VectorSpace f, Num a) => a -> f a -> f a -> f a Source #

linear interpolation

Hilbert space (inner product)

class VectorSpace f => Hilbert f where Source #

Minimal complete definition

dot

Methods

dot :: Num a => f a -> f a -> a Source #

inner product

Instances

Hilbert SpVector Source # 

Methods

dot :: Num a => SpVector a -> SpVector a -> a Source #

Hilbert-space distance function

hilbertDistSq :: (Hilbert f, Num a) => f a -> f a -> a Source #

`hilbertDistSq x y = || x - y ||^2`

Normed vector space

class Hilbert f => Normed f where Source #

Minimal complete definition

norm

Methods

norm :: (Floating a, Eq a) => a -> f a -> a Source #

Instances

Normed SpVector Source # 

Methods

norm :: (Floating a, Eq a) => a -> SpVector a -> a Source #

Norms and related results

normSq :: (Hilbert f, Num a) => f a -> a Source #

Squared 2-norm

norm1 :: (Foldable t, Num a, Functor t) => t a -> a Source #

L1 norm

norm2 :: (Hilbert f, Floating a) => f a -> a Source #

Euclidean norm

normP :: (Foldable t, Functor t, Floating a) => a -> t a -> a Source #

Lp norm (p > 0)

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

Infinity-norm

normalize :: (Normed f, Floating a, Eq a) => a -> f a -> f a Source #

Normalize w.r.t. p-norm (p finite)

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

FiniteDim : finite-dimensional objects

class Additive 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 # 

Associated Types

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

FiniteDim SpMatrix Source # 

Associated Types

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

withDim :: (FiniteDim f, Show e) => f a -> (FDSize f -> f a -> Bool) -> (f a -> c) -> String -> (f a -> e) -> c Source #

unary dimension-checking bracket

withDim2 :: (FiniteDim f, FiniteDim g, Show e) => f a -> g b -> (FDSize f -> FDSize g -> f a -> g b -> Bool) -> (f a -> g b -> c) -> String -> (f a -> g b -> e) -> c Source #

binary dimension-checking bracket

HasData : accessing inner data (do not export)

class Additive f => HasData f a where Source #

Minimal complete definition

dat

Associated Types

type HDData f a :: * Source #

Methods

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

Instances

HasData SpVector a Source # 

Associated Types

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

Methods

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

HasData SpMatrix a Source # 

Associated Types

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

Methods

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

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 -> b -> c) -> f a -> f b -> f c 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 -> b -> c) -> SpVector a -> SpVector b -> SpVector c Source #

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 #

IxContainer : indexed container types

class IxContainer c a where Source #

Associated Types

type Ix c :: * Source #

Methods

ixcLookup :: Ix c -> c a -> Maybe a Source #

ixcLookupDefault :: a -> Ix c -> c a -> a Source #

ixcFilter :: (a -> Bool) -> c a -> c a Source #

ixcIfilter :: (Ix c -> a -> Bool) -> c a -> c a Source #

ixcInsert :: Ix c -> a -> c a -> c a Source #

ixcFromList :: [(Ix c, a)] -> c a Source #

ixcToList :: c a -> [(Ix c, a)] Source #