Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class VectorSpace a v where
- addV :: (AdditiveSemigroup a, VectorSpace a v) => v a -> v a -> v a
- zeroV :: (AdditiveMonoid a, VectorSpace a v) => v a
- subtractV :: (AdditiveGroup a, VectorSpace a v) => v a -> v a -> v a
- negateV :: (AdditiveGroup a, VectorSpace a v) => v a -> v a
- scaleV :: (MultiplicativeSemigroup a, VectorSpace a v) => a -> v a -> v a
- basisV :: (Semiring a, VectorSpace a v, Eq (Basis a v)) => Basis a v -> v a
- dotV :: (Semiring a, VectorSpace a v, Foldable v) => v a -> v a -> a
- mapV :: VectorSpace a v => (a -> a) -> v a -> v a
- pureV :: VectorSpace a v => a -> v a
- zipWithV :: VectorSpace a v => (a -> a -> a) -> v a -> v a -> v a
- dimV :: forall a v. (Functor v, Foldable v, VectorSpace a v) => Natural
- fromListV :: forall a v. (AdditiveMonoid a, Traversable v, VectorSpace a v) => [a] -> v a
- iterateV :: forall a v x. (Traversable v, VectorSpace a v) => (x -> x) -> x -> v x
- newtype Representably v (a :: Type) = Representably {
- runRepresentably :: v a
- class (VectorSpace a (InputSpace a f), VectorSpace a (OutputSpace a f)) => FunctionSpace a f where
- uncurryV :: f -> InputSpace a f a -> OutputSpace a f a
- curryV :: (InputSpace a f a -> OutputSpace a f a) -> f
- type family InputSpace a f where ...
- type family OutputSpace a f where ...
- composeFunctions :: (FunctionSpace a g, FunctionSpace a f, OutputSpace a f ~ InputSpace a g) => g -> f -> InputSpace a f a -> OutputSpace a g a
Documentation
class VectorSpace a v where Source #
Class of vector spaces with a basis. More accurately, when a
is
a Field
then v a
is a vector space over it. If a
is a Ring
then
we have a free module, rather than a vector space. VectorSpace
may also be thought of
as a "monorepresentable" class, similar to Representable
but with a fixed
element type. A VectorSpace
can be thought of as a space of fixed size
tuple of variables (x1,..,xn)
.
type Basis a v :: Type Source #
The Basis
for a VectorSpace
. More accurately, Basis
will be a spanning
set with "out-of-bounds" basis elements corresponding with 0.
Instances
VectorSpace a Par1 Source # | |
VectorSpace a (U1 :: Type -> Type) Source # | |
Representable v => VectorSpace a (Representably v) Source # | |
Defined in ZkFold.Base.Algebra.Basic.VectorSpace type Basis a (Representably v) Source # tabulateV :: (Basis a (Representably v) -> a) -> Representably v a Source # indexV :: Representably v a -> Basis a (Representably v) -> a Source # | |
(Generic1 v, VectorSpace a (Rep1 v)) => VectorSpace a (Generically1 v) Source # | |
Defined in ZkFold.Base.Algebra.Basic.VectorSpace type Basis a (Generically1 v) Source # tabulateV :: (Basis a (Generically1 v) -> a) -> Generically1 v a Source # indexV :: Generically1 v a -> Basis a (Generically1 v) -> a Source # | |
(VectorSpace a v, VectorSpace a u) => VectorSpace a (v :*: u) Source # | |
(Representable u, VectorSpace a v) => VectorSpace a (u :.: v) Source # | |
VectorSpace a v => VectorSpace a (M1 i c v) Source # | |
addV :: (AdditiveSemigroup a, VectorSpace a v) => v a -> v a -> v a Source #
zeroV :: (AdditiveMonoid a, VectorSpace a v) => v a Source #
subtractV :: (AdditiveGroup a, VectorSpace a v) => v a -> v a -> v a Source #
negateV :: (AdditiveGroup a, VectorSpace a v) => v a -> v a Source #
scaleV :: (MultiplicativeSemigroup a, VectorSpace a v) => a -> v a -> v a Source #
basisV :: (Semiring a, VectorSpace a v, Eq (Basis a v)) => Basis a v -> v a Source #
basis vector e_i
dotV :: (Semiring a, VectorSpace a v, Foldable v) => v a -> v a -> a Source #
dot product
prop> v dotV
basis i = indexV v i
mapV :: VectorSpace a v => (a -> a) -> v a -> v a Source #
pureV :: VectorSpace a v => a -> v a Source #
zipWithV :: VectorSpace a v => (a -> a -> a) -> v a -> v a -> v a Source #
fromListV :: forall a v. (AdditiveMonoid a, Traversable v, VectorSpace a v) => [a] -> v a Source #
iterateV :: forall a v x. (Traversable v, VectorSpace a v) => (x -> x) -> x -> v x Source #
newtype Representably v (a :: Type) Source #
Representably | |
|
Instances
Representable v => VectorSpace a (Representably v) Source # | |
Defined in ZkFold.Base.Algebra.Basic.VectorSpace type Basis a (Representably v) Source # tabulateV :: (Basis a (Representably v) -> a) -> Representably v a Source # indexV :: Representably v a -> Basis a (Representably v) -> a Source # | |
type Basis a (Representably v) Source # | |
Defined in ZkFold.Base.Algebra.Basic.VectorSpace |
class (VectorSpace a (InputSpace a f), VectorSpace a (OutputSpace a f)) => FunctionSpace a f where Source #
FunctionSpace
class of functions between VectorSpace
s.
The type FunctionSpace a f => f
should be equal to some
(VectorSpace a v0, .. ,VectorSpace a vN) => vN a -> .. -> v1 a -> v0 a
which via multiple-uncurrying is equivalent to
(VectorSpace a v0, .. ,VectorSpace a vN) => (vN :*: .. :*: v1 :*: U1) a -> v0 a
A FunctionSpace
can be thought of as the space of functions of the form
(y1,..,yj) = f(x1,..,xi)
uncurryV :: f -> InputSpace a f a -> OutputSpace a f a Source #
curryV :: (InputSpace a f a -> OutputSpace a f a) -> f Source #
Instances
(VectorSpace a y, OutputSpace a (y a) ~ y, InputSpace a (y a) ~ (U1 :: Type -> Type)) => FunctionSpace a (y a) Source # | |
Defined in ZkFold.Base.Algebra.Basic.VectorSpace uncurryV :: y a -> InputSpace a (y a) a -> OutputSpace a (y a) a Source # curryV :: (InputSpace a (y a) a -> OutputSpace a (y a) a) -> y a Source # | |
(VectorSpace a x, OutputSpace a (x a -> f) ~ OutputSpace a f, InputSpace a (x a -> f) ~ (x :*: InputSpace a f), FunctionSpace a f) => FunctionSpace a (x a -> f) Source # | |
Defined in ZkFold.Base.Algebra.Basic.VectorSpace uncurryV :: (x a -> f) -> InputSpace a (x a -> f) a -> OutputSpace a (x a -> f) a Source # curryV :: (InputSpace a (x a -> f) a -> OutputSpace a (x a -> f) a) -> x a -> f Source # |
type family InputSpace a f where ... Source #
InputSpace a (x a -> f) = x :*: InputSpace a f | |
InputSpace a (y a) = U1 |
type family OutputSpace a f where ... Source #
OutputSpace a (x a -> f) = OutputSpace a f | |
OutputSpace a (y a) = y |
composeFunctions :: (FunctionSpace a g, FunctionSpace a f, OutputSpace a f ~ InputSpace a g) => g -> f -> InputSpace a f a -> OutputSpace a g a Source #