Safe Haskell | None |
---|---|
Language | Haskell2010 |
Algebra for Modules
- class Additive a => AdditiveModule r a where
- class (AdditiveGroup a, AdditiveModule r a) => AdditiveGroupModule r a where
- class Multiplicative a => MultiplicativeModule r a where
- class (MultiplicativeGroup a, MultiplicativeModule r a) => MultiplicativeGroupModule r a where
- class (ExpField a, Normed (r a) a, MultiplicativeGroupModule r a) => Banach r a where
- class Semiring a => Hilbert r a where
- type family (a :: k1) >< (b :: k2) :: *
- class TensorProduct a where
Documentation
class Additive a => AdditiveModule r a where Source #
Additive Module Laws
(a + b) .+ c == a + (b .+ c) (a + b) .+ c == (a .+ c) + b a .+ zero == a a .+ b == b +. a
class (AdditiveGroup a, AdditiveModule r a) => AdditiveGroupModule r a where Source #
Subtraction Module Laws
(a + b) .- c == a + (b .- c) (a + b) .- c == (a .- c) + b a .- zero == a a .- b == negate b +. a
class Multiplicative a => MultiplicativeModule r a where Source #
Multiplicative Module Laws
a .* one == a (a + b) .* c == (a .* c) + (b .* c) c *. (a + b) == (c *. a) + (c *. b) a .* zero == zero a .* b == b *. a
class (MultiplicativeGroup a, MultiplicativeModule r a) => MultiplicativeGroupModule r a where Source #
Division Module Laws
nearZero a || a ./ one == a b == zero || a ./ b == recip b *. a
class (ExpField a, Normed (r a) a, MultiplicativeGroupModule r a) => Banach r a where Source #
Banach (with Norm) laws form rules around size and direction of a number, with a potential crossing into another codomain.
a == singleton zero || normalizeL2 a *. normL2 a == a
normalizeL1 :: r a -> r a Source #
normalizeL2 :: r a -> r a Source #
normalizeLp :: a -> r a -> r a Source #
class Semiring a => Hilbert r a where Source #
the inner product of a representable over a semiring
a <.> b == b <.> a a <.> (b +c) == a <.> b + a <.> c a <.> (s *. b + c) == s * (a <.> b) + a <.> c
type family (a :: k1) >< (b :: k2) :: * infix 8 Source #
tensorial type
type (><) * * (r a) b Source # | |
type (><) * * Double Double Source # | |
type (><) * * Float Float Source # | |
type (><) * * Int Int Source # | |
type (><) * * Int8 Int8 Source # | |
type (><) * * Int16 Int16 Source # | |
type (><) * * Int32 Int32 Source # | |
type (><) * * Int64 Int64 Source # | |
type (><) * * Integer Integer Source # | |
type (><) * * Natural Natural Source # | |
type (><) * * Word Word Source # | |
type (><) * * Word8 Word8 Source # | |
type (><) * * Word16 Word16 Source # | |
type (><) * * Word32 Word32 Source # | |
type (><) * * Word64 Word64 Source # | |
class TensorProduct a where Source #
generalised outer product
a><b + c><b == (a+c) >< b a><b + a><c == a >< (b+c)
todo: work out why these laws down't apply > a *. (b>== (a<b) .* c > (a>.* c == a *. (b<c)