zkfold-base-0.1.0.0: ZkFold Symbolic compiler and zero-knowledge proof protocols
Safe HaskellSafe-Inferred
LanguageHaskell2010

ZkFold.Base.Algebra.Basic.VectorSpace

Synopsis

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).

Associated Types

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.

Methods

tabulateV :: (Basis a v -> a) -> v a Source #

indexV :: v a -> Basis a v -> a Source #

Instances

Instances details
VectorSpace a Par1 Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

Associated Types

type Basis a Par1 Source #

Methods

tabulateV :: (Basis a Par1 -> a) -> Par1 a Source #

indexV :: Par1 a -> Basis a Par1 -> a Source #

VectorSpace a (U1 :: Type -> Type) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

Associated Types

type Basis a U1 Source #

Methods

tabulateV :: (Basis a U1 -> a) -> U1 a Source #

indexV :: U1 a -> Basis a U1 -> a Source #

Representable v => VectorSpace a (Representably v) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

Associated Types

type Basis a (Representably v) Source #

Methods

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 # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

Associated Types

type Basis a (Generically1 v) Source #

Methods

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 # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

Associated Types

type Basis a (v :*: u) Source #

Methods

tabulateV :: (Basis a (v :*: u) -> a) -> (v :*: u) a Source #

indexV :: (v :*: u) a -> Basis a (v :*: u) -> a Source #

(Representable u, VectorSpace a v) => VectorSpace a (u :.: v) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

Associated Types

type Basis a (u :.: v) Source #

Methods

tabulateV :: (Basis a (u :.: v) -> a) -> (u :.: v) a Source #

indexV :: (u :.: v) a -> Basis a (u :.: v) -> a Source #

VectorSpace a v => VectorSpace a (M1 i c v) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

Associated Types

type Basis a (M1 i c v) Source #

Methods

tabulateV :: (Basis a (M1 i c v) -> a) -> M1 i c v a Source #

indexV :: M1 i c v a -> Basis a (M1 i c v) -> a Source #

addV :: (AdditiveSemigroup a, VectorSpace a v) => v a -> v a -> 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 #

dimV :: forall a v. (Functor v, Foldable v, VectorSpace a v) => Natural 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 #

Constructors

Representably 

Fields

Instances

Instances details
Representable v => VectorSpace a (Representably v) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

Associated Types

type Basis a (Representably v) Source #

Methods

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 # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

type Basis a (Representably v) = Rep v

class (VectorSpace a (InputSpace a f), VectorSpace a (OutputSpace a f)) => FunctionSpace a f where Source #

FunctionSpace class of functions between VectorSpaces.

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)

Methods

uncurryV :: f -> InputSpace a f a -> OutputSpace a f a Source #

curryV :: (InputSpace a f a -> OutputSpace a f a) -> f Source #

Instances

Instances details
(VectorSpace a y, OutputSpace a (y a) ~ y, InputSpace a (y a) ~ (U1 :: Type -> Type)) => FunctionSpace a (y a) Source # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

Methods

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 # 
Instance details

Defined in ZkFold.Base.Algebra.Basic.VectorSpace

Methods

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 #

Equations

InputSpace a (x a -> f) = x :*: InputSpace a f 
InputSpace a (y a) = U1 

type family OutputSpace a f where ... Source #

Equations

OutputSpace a (x a -> f) = OutputSpace a f 
OutputSpace a (y a) = y