hmatrix-backprop-0.1.0.0: hmatrix operations lifted for backprop

Copyright(c) Justin Le 2018
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Numeric.LinearAlgebra.Static.Backprop

Contents

Description

A wrapper over Numeric.LinearAlgebra.Static (type-safe vector and matrix operations based on blas/lapack) that allows its operations to work with backprop.

In short, these functions are "lifted" to work with BVars.

Using evalBP will run the original operation:

evalBP :: (forall s. Reifies s W. BVar s a -> BVar s b) -> a -> b

But using gradBP or backprop will give you the gradient:

gradBP :: (forall s. Reifies s W. BVar s a -> BVar s b) -> a -> a

These can act as a drop-in replacement to the API of Numeric.LinearAlgebra.Static. Just change your imports, and your functions are automatically backpropagatable. Useful types are all re-exported.

Formulas for gradients come from the following papers:

Some functions are notably unlifted:

Some other notes:

Synopsis

Vector

data R (n :: Nat) :: Nat -> * #

Instances

Domain R L 

Methods

mul :: (KnownNat m, KnownNat k, KnownNat n) => L m k -> L k n -> L m n #

app :: (KnownNat m, KnownNat n) => L m n -> R n -> R m #

dot :: KnownNat n => R n -> R n -> #

cross :: R 3 -> R 3 -> R 3 #

diagR :: (KnownNat m, KnownNat n, KnownNat k) => -> R k -> L m n #

dvmap :: KnownNat n => ( -> ) -> R n -> R n #

dmmap :: (KnownNat m, KnownNat n) => ( -> ) -> L n m -> L n m #

outer :: (KnownNat m, KnownNat n) => R n -> R m -> L n m #

zipWithVector :: KnownNat n => ( -> -> ) -> R n -> R n -> R n #

det :: KnownNat n => L n n -> #

invlndet :: KnownNat n => L n n -> (L n n, (, )) #

expm :: KnownNat n => L n n -> L n n #

sqrtm :: KnownNat n => L n n -> L n n #

inv :: KnownNat n => L n n -> L n n #

KnownNat n => Sized (R n) Vector 

Methods

konst :: -> R n #

unwrap :: R n -> Vector #

fromList :: [] -> R n #

extract :: R n -> Vector #

create :: Vector -> Maybe (R n) #

size :: R n -> IndexOf Vector #

Floating (R n) 

Methods

pi :: R n #

exp :: R n -> R n #

log :: R n -> R n #

sqrt :: R n -> R n #

(**) :: R n -> R n -> R n #

logBase :: R n -> R n -> R n #

sin :: R n -> R n #

cos :: R n -> R n #

tan :: R n -> R n #

asin :: R n -> R n #

acos :: R n -> R n #

atan :: R n -> R n #

sinh :: R n -> R n #

cosh :: R n -> R n #

tanh :: R n -> R n #

asinh :: R n -> R n #

acosh :: R n -> R n #

atanh :: R n -> R n #

log1p :: R n -> R n #

expm1 :: R n -> R n #

log1pexp :: R n -> R n #

log1mexp :: R n -> R n #

Fractional (R n) 

Methods

(/) :: R n -> R n -> R n #

recip :: R n -> R n #

fromRational :: Rational -> R n #

Num (R n) 

Methods

(+) :: R n -> R n -> R n #

(-) :: R n -> R n -> R n #

(*) :: R n -> R n -> R n #

negate :: R n -> R n #

abs :: R n -> R n #

signum :: R n -> R n #

fromInteger :: Integer -> R n #

KnownNat n => Show (R n) 

Methods

showsPrec :: Int -> R n -> ShowS #

show :: R n -> String #

showList :: [R n] -> ShowS #

Generic (R n) 

Associated Types

type Rep (R n) :: * -> * #

Methods

from :: R n -> Rep (R n) x #

to :: Rep (R n) x -> R n #

KnownNat n => Binary (R n) 

Methods

put :: R n -> Put #

get :: Get (R n) #

putList :: [R n] -> Put #

NFData (R n) 

Methods

rnf :: R n -> () #

KnownNat n => Disp (R n) 

Methods

disp :: Int -> R n -> IO () #

Additive (R n) 

Methods

add :: R n -> R n -> R n #

KnownNat n => Eigen (Sym n) (R n) (L n n) 

Methods

eigensystem :: Sym n -> (R n, L n n) #

eigenvalues :: Sym n -> R n #

KnownNat n => Diag (L n n) (R n) 

Methods

takeDiag :: L n n -> R n #

type Rep (R n) 
type Rep (R n) = D1 * (MetaData "R" "Internal.Static" "hmatrix-0.18.2.0-DXaCWiguolVIpMFjrN8tlp" True) (C1 * (MetaCons "R" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Dim n (Vector )))))

type = Double #

vec2 :: Reifies s W => BVar s -> BVar s -> BVar s (R 2) Source #

vec3 :: Reifies s W => BVar s -> BVar s -> BVar s -> BVar s (R 3) Source #

vec4 :: Reifies s W => BVar s -> BVar s -> BVar s -> BVar s -> BVar s (R 4) Source #

(&) :: (Reifies s W, KnownNat n, 1 <= n, KnownNat (n + 1)) => BVar s (R n) -> BVar s -> BVar s (R (n + 1)) infixl 4 Source #

(#) :: (Reifies s W, KnownNat n, KnownNat m) => BVar s (R n) -> BVar s (R m) -> BVar s (R (n + m)) infixl 4 Source #

split :: forall p n s. (Reifies s W, KnownNat p, KnownNat n, p <= n) => BVar s (R n) -> (BVar s (R p), BVar s (R (n - p))) Source #

headTail :: (Reifies s W, KnownNat n, 1 <= n) => BVar s (R n) -> (BVar s , BVar s (R (n - 1))) Source #

vector :: forall n s. (Reifies s W, KnownNat n) => Vector n (BVar s ) -> BVar s (R n) Source #

Potentially extremely bad for anything but short lists!!!

linspace :: forall n s. (Reifies s W, KnownNat n) => BVar s -> BVar s -> BVar s (R n) Source #

range :: KnownNat n => R n #

dim :: KnownNat n => R n #

Matrix

data L (m :: Nat) (n :: Nat) :: Nat -> Nat -> * #

Instances

Domain R L 

Methods

mul :: (KnownNat m, KnownNat k, KnownNat n) => L m k -> L k n -> L m n #

app :: (KnownNat m, KnownNat n) => L m n -> R n -> R m #

dot :: KnownNat n => R n -> R n -> #

cross :: R 3 -> R 3 -> R 3 #

diagR :: (KnownNat m, KnownNat n, KnownNat k) => -> R k -> L m n #

dvmap :: KnownNat n => ( -> ) -> R n -> R n #

dmmap :: (KnownNat m, KnownNat n) => ( -> ) -> L n m -> L n m #

outer :: (KnownNat m, KnownNat n) => R n -> R m -> L n m #

zipWithVector :: KnownNat n => ( -> -> ) -> R n -> R n -> R n #

det :: KnownNat n => L n n -> #

invlndet :: KnownNat n => L n n -> (L n n, (, )) #

expm :: KnownNat n => L n n -> L n n #

sqrtm :: KnownNat n => L n n -> L n n #

inv :: KnownNat n => L n n -> L n n #

(KnownNat m, KnownNat n) => Sized (L m n) Matrix 

Methods

konst :: -> L m n #

unwrap :: L m n -> Matrix #

fromList :: [] -> L m n #

extract :: L m n -> Matrix #

create :: Matrix -> Maybe (L m n) #

size :: L m n -> IndexOf Matrix #

KnownNat n => Eigen (Sq n) (C n) (M n n) 

Methods

eigensystem :: Sq n -> (C n, M n n) #

eigenvalues :: Sq n -> C n #

KnownNat n => Eigen (Sym n) (R n) (L n n) 

Methods

eigensystem :: Sym n -> (R n, L n n) #

eigenvalues :: Sym n -> R n #

(KnownNat n, KnownNat m) => Floating (L n m) 

Methods

pi :: L n m #

exp :: L n m -> L n m #

log :: L n m -> L n m #

sqrt :: L n m -> L n m #

(**) :: L n m -> L n m -> L n m #

logBase :: L n m -> L n m -> L n m #

sin :: L n m -> L n m #

cos :: L n m -> L n m #

tan :: L n m -> L n m #

asin :: L n m -> L n m #

acos :: L n m -> L n m #

atan :: L n m -> L n m #

sinh :: L n m -> L n m #

cosh :: L n m -> L n m #

tanh :: L n m -> L n m #

asinh :: L n m -> L n m #

acosh :: L n m -> L n m #

atanh :: L n m -> L n m #

log1p :: L n m -> L n m #

expm1 :: L n m -> L n m #

log1pexp :: L n m -> L n m #

log1mexp :: L n m -> L n m #

(KnownNat n, KnownNat m) => Fractional (L n m) 

Methods

(/) :: L n m -> L n m -> L n m #

recip :: L n m -> L n m #

fromRational :: Rational -> L n m #

(KnownNat n, KnownNat m) => Num (L n m) 

Methods

(+) :: L n m -> L n m -> L n m #

(-) :: L n m -> L n m -> L n m #

(*) :: L n m -> L n m -> L n m #

negate :: L n m -> L n m #

abs :: L n m -> L n m #

signum :: L n m -> L n m #

fromInteger :: Integer -> L n m #

(KnownNat m, KnownNat n) => Show (L m n) 

Methods

showsPrec :: Int -> L m n -> ShowS #

show :: L m n -> String #

showList :: [L m n] -> ShowS #

Generic (L m n) 

Associated Types

type Rep (L m n) :: * -> * #

Methods

from :: L m n -> Rep (L m n) x #

to :: Rep (L m n) x -> L m n #

(KnownNat n, KnownNat m) => Binary (L m n) 

Methods

put :: L m n -> Put #

get :: Get (L m n) #

putList :: [L m n] -> Put #

NFData (L n m) 

Methods

rnf :: L n m -> () #

(KnownNat m, KnownNat n) => Disp (L m n) 

Methods

disp :: Int -> L m n -> IO () #

(KnownNat m, KnownNat n) => Additive (L m n) 

Methods

add :: L m n -> L m n -> L m n #

KnownNat n => Diag (L n n) (R n) 

Methods

takeDiag :: L n n -> R n #

(KnownNat n, KnownNat m) => Transposable (L m n) (L n m) 

Methods

tr :: L m n -> L n m #

tr' :: L m n -> L n m #

type Rep (L m n) 
type Rep (L m n) = D1 * (MetaData "L" "Internal.Static" "hmatrix-0.18.2.0-DXaCWiguolVIpMFjrN8tlp" True) (C1 * (MetaCons "L" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Dim m (Dim n (Matrix ))))))

type Sq (n :: Nat) = L n n #

row :: (Reifies s W, KnownNat n) => BVar s (R n) -> BVar s (L 1 n) Source #

col :: (Reifies s W, KnownNat n) => BVar s (R n) -> BVar s (L n 1) Source #

(|||) :: (Reifies s W, KnownNat c, KnownNat r1, KnownNat (r1 + r2)) => BVar s (L c r1) -> BVar s (L c r2) -> BVar s (L c (r1 + r2)) infixl 3 Source #

(===) :: (Reifies s W, KnownNat c, KnownNat r1, KnownNat (r1 + r2)) => BVar s (L r1 c) -> BVar s (L r2 c) -> BVar s (L (r1 + r2) c) infixl 2 Source #

splitRows :: forall p m n s. (Reifies s W, KnownNat p, KnownNat m, KnownNat n, p <= m) => BVar s (L m n) -> (BVar s (L p n), BVar s (L (m - p) n)) Source #

splitCols :: forall p m n s. (Reifies s W, KnownNat p, KnownNat m, KnownNat n, KnownNat (n - p), p <= n) => BVar s (L m n) -> (BVar s (L m p), BVar s (L m (n - p))) Source #

unrow :: (Reifies s W, KnownNat n) => BVar s (L 1 n) -> BVar s (R n) Source #

uncol :: (Reifies s W, KnownNat n) => BVar s (L n 1) -> BVar s (R n) Source #

tr :: (Reifies s W, Transposable m mt, Transposable mt m, Num m, Num mt) => BVar s m -> BVar s mt Source #

eye :: KnownNat n => Sq n #

diag :: (Reifies s W, KnownNat n) => BVar s (R n) -> BVar s (Sq n) Source #

matrix :: forall m n s. (Reifies s W, KnownNat m, KnownNat n) => [BVar s ] -> BVar s (L m n) Source #

Potentially extremely bad for anything but short lists!!!

Complex

data C (n :: Nat) :: Nat -> * #

Instances

Domain C M 

Methods

mul :: (KnownNat m, KnownNat k, KnownNat n) => M m k -> M k n -> M m n #

app :: (KnownNat m, KnownNat n) => M m n -> C n -> C m #

dot :: KnownNat n => C n -> C n -> #

cross :: C 3 -> C 3 -> C 3 #

diagR :: (KnownNat m, KnownNat n, KnownNat k) => -> C k -> M m n #

dvmap :: KnownNat n => ( -> ) -> C n -> C n #

dmmap :: (KnownNat m, KnownNat n) => ( -> ) -> M n m -> M n m #

outer :: (KnownNat m, KnownNat n) => C n -> C m -> M n m #

zipWithVector :: KnownNat n => ( -> -> ) -> C n -> C n -> C n #

det :: KnownNat n => M n n -> #

invlndet :: KnownNat n => M n n -> (M n n, (, )) #

expm :: KnownNat n => M n n -> M n n #

sqrtm :: KnownNat n => M n n -> M n n #

inv :: KnownNat n => M n n -> M n n #

KnownNat n => Sized (C n) Vector 

Methods

konst :: -> C n #

unwrap :: C n -> Vector #

fromList :: [] -> C n #

extract :: C n -> Vector #

create :: Vector -> Maybe (C n) #

size :: C n -> IndexOf Vector #

Floating (C n) 

Methods

pi :: C n #

exp :: C n -> C n #

log :: C n -> C n #

sqrt :: C n -> C n #

(**) :: C n -> C n -> C n #

logBase :: C n -> C n -> C n #

sin :: C n -> C n #

cos :: C n -> C n #

tan :: C n -> C n #

asin :: C n -> C n #

acos :: C n -> C n #

atan :: C n -> C n #

sinh :: C n -> C n #

cosh :: C n -> C n #

tanh :: C n -> C n #

asinh :: C n -> C n #

acosh :: C n -> C n #

atanh :: C n -> C n #

log1p :: C n -> C n #

expm1 :: C n -> C n #

log1pexp :: C n -> C n #

log1mexp :: C n -> C n #

Fractional (C n) 

Methods

(/) :: C n -> C n -> C n #

recip :: C n -> C n #

fromRational :: Rational -> C n #

Num (C n) 

Methods

(+) :: C n -> C n -> C n #

(-) :: C n -> C n -> C n #

(*) :: C n -> C n -> C n #

negate :: C n -> C n #

abs :: C n -> C n #

signum :: C n -> C n #

fromInteger :: Integer -> C n #

KnownNat n => Show (C n) 

Methods

showsPrec :: Int -> C n -> ShowS #

show :: C n -> String #

showList :: [C n] -> ShowS #

Generic (C n) 

Associated Types

type Rep (C n) :: * -> * #

Methods

from :: C n -> Rep (C n) x #

to :: Rep (C n) x -> C n #

NFData (C n) 

Methods

rnf :: C n -> () #

KnownNat n => Disp (C n) 

Methods

disp :: Int -> C n -> IO () #

Additive (C n) 

Methods

add :: C n -> C n -> C n #

KnownNat n => Eigen (Sq n) (C n) (M n n) 

Methods

eigensystem :: Sq n -> (C n, M n n) #

eigenvalues :: Sq n -> C n #

KnownNat n => Diag (M n n) (C n) 

Methods

takeDiag :: M n n -> C n #

type Rep (C n) 
type Rep (C n) = D1 * (MetaData "C" "Internal.Static" "hmatrix-0.18.2.0-DXaCWiguolVIpMFjrN8tlp" True) (C1 * (MetaCons "C" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Dim n (Vector )))))

data M (m :: Nat) (n :: Nat) :: Nat -> Nat -> * #

Instances

Domain C M 

Methods

mul :: (KnownNat m, KnownNat k, KnownNat n) => M m k -> M k n -> M m n #

app :: (KnownNat m, KnownNat n) => M m n -> C n -> C m #

dot :: KnownNat n => C n -> C n -> #

cross :: C 3 -> C 3 -> C 3 #

diagR :: (KnownNat m, KnownNat n, KnownNat k) => -> C k -> M m n #

dvmap :: KnownNat n => ( -> ) -> C n -> C n #

dmmap :: (KnownNat m, KnownNat n) => ( -> ) -> M n m -> M n m #

outer :: (KnownNat m, KnownNat n) => C n -> C m -> M n m #

zipWithVector :: KnownNat n => ( -> -> ) -> C n -> C n -> C n #

det :: KnownNat n => M n n -> #

invlndet :: KnownNat n => M n n -> (M n n, (, )) #

expm :: KnownNat n => M n n -> M n n #

sqrtm :: KnownNat n => M n n -> M n n #

inv :: KnownNat n => M n n -> M n n #

(KnownNat m, KnownNat n) => Sized (M m n) Matrix 

Methods

konst :: -> M m n #

unwrap :: M m n -> Matrix #

fromList :: [] -> M m n #

extract :: M m n -> Matrix #

create :: Matrix -> Maybe (M m n) #

size :: M m n -> IndexOf Matrix #

KnownNat n => Eigen (Sq n) (C n) (M n n) 

Methods

eigensystem :: Sq n -> (C n, M n n) #

eigenvalues :: Sq n -> C n #

(KnownNat n, KnownNat m) => Floating (M n m) 

Methods

pi :: M n m #

exp :: M n m -> M n m #

log :: M n m -> M n m #

sqrt :: M n m -> M n m #

(**) :: M n m -> M n m -> M n m #

logBase :: M n m -> M n m -> M n m #

sin :: M n m -> M n m #

cos :: M n m -> M n m #

tan :: M n m -> M n m #

asin :: M n m -> M n m #

acos :: M n m -> M n m #

atan :: M n m -> M n m #

sinh :: M n m -> M n m #

cosh :: M n m -> M n m #

tanh :: M n m -> M n m #

asinh :: M n m -> M n m #

acosh :: M n m -> M n m #

atanh :: M n m -> M n m #

log1p :: M n m -> M n m #

expm1 :: M n m -> M n m #

log1pexp :: M n m -> M n m #

log1mexp :: M n m -> M n m #

(KnownNat n, KnownNat m) => Fractional (M n m) 

Methods

(/) :: M n m -> M n m -> M n m #

recip :: M n m -> M n m #

fromRational :: Rational -> M n m #

(KnownNat n, KnownNat m) => Num (M n m) 

Methods

(+) :: M n m -> M n m -> M n m #

(-) :: M n m -> M n m -> M n m #

(*) :: M n m -> M n m -> M n m #

negate :: M n m -> M n m #

abs :: M n m -> M n m #

signum :: M n m -> M n m #

fromInteger :: Integer -> M n m #

(KnownNat m, KnownNat n) => Show (M m n) 

Methods

showsPrec :: Int -> M m n -> ShowS #

show :: M m n -> String #

showList :: [M m n] -> ShowS #

Generic (M m n) 

Associated Types

type Rep (M m n) :: * -> * #

Methods

from :: M m n -> Rep (M m n) x #

to :: Rep (M m n) x -> M m n #

NFData (M n m) 

Methods

rnf :: M n m -> () #

(KnownNat m, KnownNat n) => Disp (M m n) 

Methods

disp :: Int -> M m n -> IO () #

(KnownNat m, KnownNat n) => Additive (M m n) 

Methods

add :: M m n -> M m n -> M m n #

KnownNat n => Diag (M n n) (C n) 

Methods

takeDiag :: M n n -> C n #

(KnownNat n, KnownNat m) => Transposable (M m n) (M n m) 

Methods

tr :: M m n -> M n m #

tr' :: M m n -> M n m #

type Rep (M m n) 
type Rep (M m n) = D1 * (MetaData "M" "Internal.Static" "hmatrix-0.18.2.0-DXaCWiguolVIpMFjrN8tlp" True) (C1 * (MetaCons "M" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Dim m (Dim n (Matrix ))))))

𝑖 :: Sized s c => s #

Products

(<>) :: (Reifies s W, KnownNat m, KnownNat k, KnownNat n) => BVar s (L m k) -> BVar s (L k n) -> BVar s (L m n) infixr 8 Source #

Matrix product

(#>) :: (Reifies s W, KnownNat m, KnownNat n) => BVar s (L m n) -> BVar s (R n) -> BVar s (R m) infixr 8 Source #

Matrix-vector product

(<.>) :: (Reifies s W, KnownNat n) => BVar s (R n) -> BVar s (R n) -> BVar s infixr 8 Source #

Dot product

Factorizations

svd :: forall m n s. (Reifies s W, KnownNat m, KnownNat n) => BVar s (L m n) -> BVar s (R n) Source #

Can only get the singular values, for now. Let me know if you find an algorithm that can compute the gradients based on differentials for the other matricies!

svd_ :: forall m n s. (Reifies s W, KnownNat m, KnownNat n) => BVar s (L m n) -> (BVar s (L m m), BVar s (R n), BVar s (L n n)) Source #

Version of svd that returns the full SVD, but if you attempt to find the gradient, it will fail at runtime if you ever use U or V.

class Eigen m l v | m -> l, m -> v #

Minimal complete definition

eigensystem, eigenvalues

Instances

KnownNat n => Eigen (Sq n) (C n) (M n n) 

Methods

eigensystem :: Sq n -> (C n, M n n) #

eigenvalues :: Sq n -> C n #

KnownNat n => Eigen (Sym n) (R n) (L n n) 

Methods

eigensystem :: Sym n -> (R n, L n n) #

eigenvalues :: Sym n -> R n #

eigensystem :: forall n s. (Reifies s W, KnownNat n) => BVar s (Sym n) -> (BVar s (R n), BVar s (L n n)) Source #

NOTE The gradient is not necessarily symmetric! The gradient is not meant to be retireved directly; insteadl, eigenvalues is meant to be used as a part of a larger computation, and the gradient as an intermediate step.

eigenvalues :: forall n s. (Reifies s W, KnownNat n) => BVar s (Sym n) -> BVar s (R n) Source #

NOTE The gradient is not necessarily symmetric! The gradient is not meant to be retireved directly; insteadl, eigenvalues is meant to be used as a part of a larger computation, and the gradient as an intermediate step.

chol :: forall n s. (Reifies s W, KnownNat n) => BVar s (Sym n) -> BVar s (Sq n) Source #

Algorithm from https://arxiv.org/abs/1602.07527

The paper also suggests a potential imperative algorithm that might help. Need to benchmark to see what is best.

NOTE The gradient is not necessarily symmetric! The gradient is not meant to be retireved directly; insteadl, eigenvalues is meant to be used as a part of a larger computation, and the gradient as an intermediate step.

Norms

class Normed a #

p-norm for vectors, operator norm for matrices

Minimal complete definition

norm_0, norm_1, norm_2, norm_Inf

Instances

Normed (Matrix R) 

Methods

norm_0 :: Matrix R -> R #

norm_1 :: Matrix R -> R #

norm_2 :: Matrix R -> R #

norm_Inf :: Matrix R -> R #

Normed (Matrix C) 

Methods

norm_0 :: Matrix C -> R #

norm_1 :: Matrix C -> R #

norm_2 :: Matrix C -> R #

norm_Inf :: Matrix C -> R #

Normed (Vector Float) 
Normed (Vector (Complex Float)) 
KnownNat m => Normed (Vector (Mod m I)) 

Methods

norm_0 :: Vector (Mod m I) -> R #

norm_1 :: Vector (Mod m I) -> R #

norm_2 :: Vector (Mod m I) -> R #

norm_Inf :: Vector (Mod m I) -> R #

KnownNat m => Normed (Vector (Mod m Z)) 

Methods

norm_0 :: Vector (Mod m Z) -> R #

norm_1 :: Vector (Mod m Z) -> R #

norm_2 :: Vector (Mod m Z) -> R #

norm_Inf :: Vector (Mod m Z) -> R #

Normed (Vector I) 

Methods

norm_0 :: Vector I -> R #

norm_1 :: Vector I -> R #

norm_2 :: Vector I -> R #

norm_Inf :: Vector I -> R #

Normed (Vector Z) 

Methods

norm_0 :: Vector Z -> R #

norm_1 :: Vector Z -> R #

norm_2 :: Vector Z -> R #

norm_Inf :: Vector Z -> R #

Normed (Vector R) 

Methods

norm_0 :: Vector R -> R #

norm_1 :: Vector R -> R #

norm_2 :: Vector R -> R #

norm_Inf :: Vector R -> R #

Normed (Vector C) 

Methods

norm_0 :: Vector C -> R #

norm_1 :: Vector C -> R #

norm_2 :: Vector C -> R #

norm_Inf :: Vector C -> R #

norm_0 :: (Reifies s W, Normed a, Num a) => BVar s a -> BVar s Source #

Number of non-zero items

norm_1V :: (Reifies s W, KnownNat n) => BVar s (R n) -> BVar s Source #

Sum of absolute values

norm_1M :: (Reifies s W, KnownNat n, KnownNat m) => BVar s (L n m) -> BVar s Source #

Maximum norm_1 of columns

norm_2V :: (Reifies s W, KnownNat n) => BVar s (R n) -> BVar s Source #

Square root of sum of squares

Be aware that gradient diverges when the norm is zero

norm_2M :: (Reifies s W, KnownNat n, KnownNat m) => BVar s (L n m) -> BVar s Source #

Maximum singular value

norm_InfV :: (Reifies s W, KnownNat n) => BVar s (R n) -> BVar s Source #

Maximum absolute value

norm_InfM :: (Reifies s W, KnownNat n, KnownNat m) => BVar s (L n m) -> BVar s Source #

Maximum norm_1 of rows

Misc

mean :: (Reifies s W, KnownNat n, 1 <= n) => BVar s (R n) -> BVar s Source #

meanCov :: forall m n s. (Reifies s W, KnownNat n, KnownNat m, 1 <= m) => BVar s (L m n) -> (BVar s (R n), BVar s (Sym n)) Source #

Mean and covariance. If you know you only want to use one or the other, use meanL or cov.

meanL :: forall m n s. (Reifies s W, KnownNat n, KnownNat m, 1 <= m) => BVar s (L m n) -> BVar s (R n) Source #

meanCov, but if you know you won't use the covariance.

cov :: forall m n s. (Reifies s W, KnownNat n, KnownNat m, 1 <= m) => BVar s (L m n) -> BVar s (Sym n) Source #

cov, but if you know you won't use the covariance.

class Disp t where #

Minimal complete definition

disp

Methods

disp :: Int -> t -> IO () #

Instances

KnownNat n => Disp (Sym n) 

Methods

disp :: Int -> Sym n -> IO () #

KnownNat n => Disp (Her n) 

Methods

disp :: Int -> Her n -> IO () #

KnownNat n => Disp (R n) 

Methods

disp :: Int -> R n -> IO () #

KnownNat n => Disp (C n) 

Methods

disp :: Int -> C n -> IO () #

(KnownNat m, KnownNat n) => Disp (L m n) 

Methods

disp :: Int -> L m n -> IO () #

(KnownNat m, KnownNat n) => Disp (M m n) 

Methods

disp :: Int -> M m n -> IO () #

Domain

class Domain field (vec :: Nat -> *) (mat :: Nat -> Nat -> *) | mat -> vec field, vec -> mat field, field -> mat vec #

Minimal complete definition

mul, app, dot, cross, diagR, dvmap, dmmap, outer, zipWithVector, det, invlndet, expm, sqrtm, inv

Instances

Domain R L 

Methods

mul :: (KnownNat m, KnownNat k, KnownNat n) => L m k -> L k n -> L m n #

app :: (KnownNat m, KnownNat n) => L m n -> R n -> R m #

dot :: KnownNat n => R n -> R n -> #

cross :: R 3 -> R 3 -> R 3 #

diagR :: (KnownNat m, KnownNat n, KnownNat k) => -> R k -> L m n #

dvmap :: KnownNat n => ( -> ) -> R n -> R n #

dmmap :: (KnownNat m, KnownNat n) => ( -> ) -> L n m -> L n m #

outer :: (KnownNat m, KnownNat n) => R n -> R m -> L n m #

zipWithVector :: KnownNat n => ( -> -> ) -> R n -> R n -> R n #

det :: KnownNat n => L n n -> #

invlndet :: KnownNat n => L n n -> (L n n, (, )) #

expm :: KnownNat n => L n n -> L n n #

sqrtm :: KnownNat n => L n n -> L n n #

inv :: KnownNat n => L n n -> L n n #

Domain C M 

Methods

mul :: (KnownNat m, KnownNat k, KnownNat n) => M m k -> M k n -> M m n #

app :: (KnownNat m, KnownNat n) => M m n -> C n -> C m #

dot :: KnownNat n => C n -> C n -> #

cross :: C 3 -> C 3 -> C 3 #

diagR :: (KnownNat m, KnownNat n, KnownNat k) => -> C k -> M m n #

dvmap :: KnownNat n => ( -> ) -> C n -> C n #

dmmap :: (KnownNat m, KnownNat n) => ( -> ) -> M n m -> M n m #

outer :: (KnownNat m, KnownNat n) => C n -> C m -> M n m #

zipWithVector :: KnownNat n => ( -> -> ) -> C n -> C n -> C n #

det :: KnownNat n => M n n -> #

invlndet :: KnownNat n => M n n -> (M n n, (, )) #

expm :: KnownNat n => M n n -> M n n #

sqrtm :: KnownNat n => M n n -> M n n #

inv :: KnownNat n => M n n -> M n n #

mul :: (Reifies s W, KnownNat m, KnownNat k, KnownNat n, Domain field vec mat, Num (mat m k), Num (mat k n), Num (mat m n), Transposable (mat m k) (mat k m), Transposable (mat k n) (mat n k)) => BVar s (mat m k) -> BVar s (mat k n) -> BVar s (mat m n) Source #

app :: (Reifies s W, KnownNat m, KnownNat n, Domain field vec mat, Num (mat m n), Num (vec n), Num (vec m), Transposable (mat m n) (mat n m)) => BVar s (mat m n) -> BVar s (vec n) -> BVar s (vec m) Source #

dot :: (Reifies s W, KnownNat n, Domain field vec mat, Sized field (vec n) d, Num (vec n)) => BVar s (vec n) -> BVar s (vec n) -> BVar s field Source #

cross :: (Reifies s W, Domain field vec mat, Num (vec 3)) => BVar s (vec 3) -> BVar s (vec 3) -> BVar s (vec 3) Source #

diagR Source #

Arguments

:: (Reifies s W, Domain field vec mat, Num (vec k), Num (mat m n), KnownNat m, KnownNat n, KnownNat k, Container Vector field, Sized field (mat m n) Matrix, Sized field (vec k) Vector) 
=> BVar s field

default value

-> BVar s (vec k)

diagonal

-> BVar s (mat m n) 

Create matrix with diagonal, and fill with default entries

dvmap :: (Reifies s W, Num (vec n), Storable field, Storable (field, field), Sized field (vec n) Vector) => (forall s'. Reifies s' W => BVar s' field -> BVar s' field) -> BVar s (vec n) -> BVar s (vec n) Source #

dvmap' :: (Reifies s W, KnownNat n, Domain field vec mat, Num (vec n), Num field) => (forall s'. Reifies s' W => BVar s' field -> BVar s' field) -> BVar s (vec n) -> BVar s (vec n) Source #

A version of dvmap that is less performant but is based on zipWithVector from Domain.

dmmap :: forall n m mat field s. (Reifies s W, KnownNat m, Num (mat n m), Storable (field, field), Sized field (mat n m) Matrix, Element field) => (forall s'. Reifies s' W => BVar s' field -> BVar s' field) -> BVar s (mat n m) -> BVar s (mat n m) Source #

dmmap' :: (Reifies s W, KnownNat n, KnownNat m, Domain field vec mat, Num (mat n m), Num field) => (forall s'. Reifies s' W => BVar s' field -> BVar s' field) -> BVar s (mat n m) -> BVar s (mat n m) Source #

outer :: (Reifies s W, KnownNat m, KnownNat n, Domain field vec mat, Transposable (mat n m) (mat m n), Num (vec n), Num (vec m), Num (mat n m)) => BVar s (vec n) -> BVar s (vec m) -> BVar s (mat n m) Source #

zipWithVector :: (Reifies s W, Num (vec n), Storable field, Storable (field, field, field), Sized field (vec n) Vector) => (forall s'. Reifies s' W => BVar s' field -> BVar s' field -> BVar s' field) -> BVar s (vec n) -> BVar s (vec n) -> BVar s (vec n) Source #

zipWithVector' :: (Reifies s W, KnownNat n, Domain field vec mat, Num (vec n), Num field) => (forall s'. Reifies s' W => BVar s' field -> BVar s' field -> BVar s' field) -> BVar s (vec n) -> BVar s (vec n) -> BVar s (vec n) Source #

A version of zipWithVector that is less performant but is based on zipWithVector from Domain.

det :: (Reifies s W, KnownNat n, Num (mat n n), Domain field vec mat, Sized field (mat n n) d, Transposable (mat n n) (mat n n)) => BVar s (mat n n) -> BVar s field Source #

invlndet :: forall n mat field vec d s. (Reifies s W, KnownNat n, Num (mat n n), Domain field vec mat, Sized field (mat n n) d, Transposable (mat n n) (mat n n)) => BVar s (mat n n) -> (BVar s (mat n n), (BVar s field, BVar s field)) Source #

The inverse and the natural log of the determinant together. If you know you don't need the inverse, it is best to use lndet.

lndet :: forall n mat field vec d s. (Reifies s W, KnownNat n, Num (mat n n), Domain field vec mat, Sized field (mat n n) d, Transposable (mat n n) (mat n n)) => BVar s (mat n n) -> BVar s field Source #

The natural log of the determinant.

inv :: (Reifies s W, KnownNat n, Num (mat n n), Domain field vec mat, Transposable (mat n n) (mat n n)) => BVar s (mat n n) -> BVar s (mat n n) Source #

Conversions

toRows :: forall m n s. (Reifies s W, KnownNat m, KnownNat n) => BVar s (L m n) -> Vector m (BVar s (R n)) Source #

toColumns :: forall m n s. (Reifies s W, KnownNat m, KnownNat n) => BVar s (L m n) -> Vector n (BVar s (R m)) Source #

fromRows :: forall m n s. (Reifies s W, KnownNat m, KnownNat n) => Vector m (BVar s (R n)) -> BVar s (L m n) Source #

fromColumns :: forall m n s. (Reifies s W, KnownNat m, KnownNat n) => Vector n (BVar s (R m)) -> BVar s (L m n) Source #

Misc Operations

konst :: forall t s d q. (Reifies q W, Sized t s d, Container d t, Num s) => BVar q t -> BVar q s Source #

sumElements :: forall t s d q. (Reifies q W, Sized t s d, Container d t, Num s) => BVar q s -> BVar q t Source #

extractV :: forall t s q. (Reifies q W, Sized t s Vector, Num s, Konst t Int Vector, Container Vector t, Num (Vector t)) => BVar q s -> BVar q (Vector t) Source #

If there are extra items in the total derivative, they are dropped. If there are missing items, they are treated as zero.

extractM :: forall t s q. (Reifies q W, Sized t s Matrix, Num s, Konst t (Int, Int) Matrix, Container Matrix t, Num (Matrix t)) => BVar q s -> BVar q (Matrix t) Source #

If there are extra items in the total derivative, they are dropped. If there are missing items, they are treated as zero.

create :: forall t s d q. (Reifies q W, Sized t s d, Num s, Num (d t)) => BVar q (d t) -> Maybe (BVar q s) Source #

class Diag m d | m -> d #

Minimal complete definition

takeDiag

Instances

KnownNat n => Diag (L n n) (R n) 

Methods

takeDiag :: L n n -> R n #

KnownNat n => Diag (M n n) (C n) 

Methods

takeDiag :: M n n -> C n #

takeDiag :: (Reifies s W, KnownNat n, Diag (mat n n) (vec n), Domain field vec mat, Num (vec n), Num (mat n n), Num field) => BVar s (mat n n) -> BVar s (vec n) Source #

data Sym (n :: Nat) :: Nat -> * #

Instances

KnownNat n => Floating (Sym n) 

Methods

pi :: Sym n #

exp :: Sym n -> Sym n #

log :: Sym n -> Sym n #

sqrt :: Sym n -> Sym n #

(**) :: Sym n -> Sym n -> Sym n #

logBase :: Sym n -> Sym n -> Sym n #

sin :: Sym n -> Sym n #

cos :: Sym n -> Sym n #

tan :: Sym n -> Sym n #

asin :: Sym n -> Sym n #

acos :: Sym n -> Sym n #

atan :: Sym n -> Sym n #

sinh :: Sym n -> Sym n #

cosh :: Sym n -> Sym n #

tanh :: Sym n -> Sym n #

asinh :: Sym n -> Sym n #

acosh :: Sym n -> Sym n #

atanh :: Sym n -> Sym n #

log1p :: Sym n -> Sym n #

expm1 :: Sym n -> Sym n #

log1pexp :: Sym n -> Sym n #

log1mexp :: Sym n -> Sym n #

KnownNat n => Fractional (Sym n) 

Methods

(/) :: Sym n -> Sym n -> Sym n #

recip :: Sym n -> Sym n #

fromRational :: Rational -> Sym n #

KnownNat n => Num (Sym n) 

Methods

(+) :: Sym n -> Sym n -> Sym n #

(-) :: Sym n -> Sym n -> Sym n #

(*) :: Sym n -> Sym n -> Sym n #

negate :: Sym n -> Sym n #

abs :: Sym n -> Sym n #

signum :: Sym n -> Sym n #

fromInteger :: Integer -> Sym n #

KnownNat n => Show (Sym n) 

Methods

showsPrec :: Int -> Sym n -> ShowS #

show :: Sym n -> String #

showList :: [Sym n] -> ShowS #

KnownNat n => Disp (Sym n) 

Methods

disp :: Int -> Sym n -> IO () #

KnownNat n => Additive (Sym n) 

Methods

add :: Sym n -> Sym n -> Sym n #

KnownNat n => Transposable (Sym n) (Sym n) 

Methods

tr :: Sym n -> Sym n #

tr' :: Sym n -> Sym n #

KnownNat n => Eigen (Sym n) (R n) (L n n) 

Methods

eigensystem :: Sym n -> (R n, L n n) #

eigenvalues :: Sym n -> R n #

sym :: (Reifies s W, KnownNat n) => BVar s (Sq n) -> BVar s (Sym n) Source #

\[ \frac{1}{2} (M + M^T) \]

mTm :: (Reifies s W, KnownNat m, KnownNat n) => BVar s (L m n) -> BVar s (Sym n) Source #

\[ M^T M \]

unSym :: (Reifies s W, KnownNat n) => BVar s (Sym n) -> BVar s (Sq n) Source #

Warning: the gradient is going necessarily symmetric, and so is not meant to be used directly. Rather, it is meant to be used in the middle (or at the end) of a longer computation.

(<·>) :: (Reifies s W, KnownNat n) => BVar s (R n) -> BVar s (R n) -> BVar s infixr 8 Source #

Unicode synonym for <.>>