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

ZkFold.Base.Data.Vector

Documentation

newtype Vector (size :: Natural) a Source #

Constructors

Vector 

Fields

Instances

Instances details
(Ring a, KnownNat n) => LinearCombinationWith a (Vector n a) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.Fold

Methods

linearCombinationWith :: a -> Vector n a -> Vector n a -> Vector n a Source #

(Arithmetic a, Scale a f, MultiplicativeMonoid f, Exponent f Natural, AdditiveMonoid f) => AlgebraicMap f (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

Associated Types

type MapInput f (ArithmeticCircuit a (Vector n) o) Source #

type MapMessage f (ArithmeticCircuit a (Vector n) o) Source #

Methods

algebraicMap :: ArithmeticCircuit a (Vector n) o -> MapInput f (ArithmeticCircuit a (Vector n) o) -> [MapMessage f (ArithmeticCircuit a (Vector n) o)] -> [f] -> f -> [f] Source #

KnownNat size => Representable (Vector size) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Associated Types

type Rep (Vector size) #

Methods

tabulate :: (Rep (Vector size) -> a) -> Vector size a #

index :: Vector size a -> Rep (Vector size) -> a #

Foldable (Vector size) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

fold :: Monoid m => Vector size m -> m #

foldMap :: Monoid m => (a -> m) -> Vector size a -> m #

foldMap' :: Monoid m => (a -> m) -> Vector size a -> m #

foldr :: (a -> b -> b) -> b -> Vector size a -> b #

foldr' :: (a -> b -> b) -> b -> Vector size a -> b #

foldl :: (b -> a -> b) -> b -> Vector size a -> b #

foldl' :: (b -> a -> b) -> b -> Vector size a -> b #

foldr1 :: (a -> a -> a) -> Vector size a -> a #

foldl1 :: (a -> a -> a) -> Vector size a -> a #

toList :: Vector size a -> [a] #

null :: Vector size a -> Bool #

length :: Vector size a -> Int #

elem :: Eq a => a -> Vector size a -> Bool #

maximum :: Ord a => Vector size a -> a #

minimum :: Ord a => Vector size a -> a #

sum :: Num a => Vector size a -> a #

product :: Num a => Vector size a -> a #

Traversable (Vector size) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

traverse :: Applicative f => (a -> f b) -> Vector size a -> f (Vector size b) #

sequenceA :: Applicative f => Vector size (f a) -> f (Vector size a) #

mapM :: Monad m => (a -> m b) -> Vector size a -> m (Vector size b) #

sequence :: Monad m => Vector size (m a) -> m (Vector size a) #

KnownNat size => Applicative (Vector size) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

pure :: a -> Vector size a #

(<*>) :: Vector size (a -> b) -> Vector size a -> Vector size b #

liftA2 :: (a -> b -> c) -> Vector size a -> Vector size b -> Vector size c #

(*>) :: Vector size a -> Vector size b -> Vector size b #

(<*) :: Vector size a -> Vector size b -> Vector size a #

Functor (Vector size) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

fmap :: (a -> b) -> Vector size a -> Vector size b #

(<$) :: a -> Vector size b -> Vector size a #

KnownNat size => Distributive (Vector size) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

distribute :: Functor f => f (Vector size a) -> Vector size (f a) #

collect :: Functor f => (a -> Vector size b) -> f a -> Vector size (f b) #

distributeM :: Monad m => m (Vector size a) -> Vector size (m a) #

collectM :: Monad m => (a -> Vector size b) -> m a -> Vector size (m b) #

Semialign (Vector size) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

align :: Vector size a -> Vector size b -> Vector size (These a b) #

alignWith :: (These a b -> c) -> Vector size a -> Vector size b -> Vector size c #

Zip (Vector size) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

zip :: Vector size a -> Vector size b -> Vector size (a, b) #

zipWith :: (a -> b -> c) -> Vector size a -> Vector size b -> Vector size c #

(Arithmetic a, Symbolic ctx, FromConstant a (BaseField ctx), Scale a (BaseField ctx)) => SpecialSoundProtocol (FieldElement ctx) (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

(Arbitrary a, KnownNat size) => Arbitrary (Vector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

arbitrary :: Gen (Vector size a) #

shrink :: Vector size a -> [Vector size a] #

ToJSON a => ToJSON (Vector n a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

toJSON :: Vector n a -> Value #

toEncoding :: Vector n a -> Encoding #

toJSONList :: [Vector n a] -> Value #

toEncodingList :: [Vector n a] -> Encoding #

Generic (Vector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Associated Types

type Rep (Vector size a) :: Type -> Type #

Methods

from :: Vector size a -> Rep (Vector size a) x #

to :: Rep (Vector size a) x -> Vector size a #

IsList (Vector n a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Associated Types

type Item (Vector n a) #

Methods

fromList :: [Item (Vector n a)] -> Vector n a #

fromListN :: Int -> [Item (Vector n a)] -> Vector n a #

toList :: Vector n a -> [Item (Vector n a)] #

Show a => Show (Vector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

showsPrec :: Int -> Vector size a -> ShowS #

show :: Vector size a -> String #

showList :: [Vector size a] -> ShowS #

(KnownNat n, Binary a) => Binary (Vector n a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

put :: Vector n a -> Put #

get :: Get (Vector n a) #

putList :: [Vector n a] -> Put #

NFData a => NFData (Vector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

rnf :: Vector size a -> () #

Eq a => Eq (Vector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

(==) :: Vector size a -> Vector size a -> Bool #

(/=) :: Vector size a -> Vector size a -> Bool #

Ord a => Ord (Vector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

compare :: Vector size a -> Vector size a -> Ordering #

(<) :: Vector size a -> Vector size a -> Bool #

(<=) :: Vector size a -> Vector size a -> Bool #

(>) :: Vector size a -> Vector size a -> Bool #

(>=) :: Vector size a -> Vector size a -> Bool #

max :: Vector size a -> Vector size a -> Vector size a #

min :: Vector size a -> Vector size a -> Vector size a #

(Random a, KnownNat size) => Random (Vector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

Methods

randomR :: RandomGen g => (Vector size a, Vector size a) -> g -> (Vector size a, g) #

random :: RandomGen g => g -> (Vector size a, g) #

randomRs :: RandomGen g => (Vector size a, Vector size a) -> g -> [Vector size a] #

randoms :: RandomGen g => g -> [Vector size a] #

(SymbolicData x, Package (Context x), KnownNat n) => SymbolicData (Vector n x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

Associated Types

type Context (Vector n x) :: (Type -> Type) -> Type Source #

type Support (Vector n x) Source #

type Layout (Vector n x) :: Type -> Type Source #

Methods

pieces :: Vector n x -> Support (Vector n x) -> Context (Vector n x) (Layout (Vector n x)) Source #

restore :: (Support (Vector n x) -> Context (Vector n x) (Layout (Vector n x))) -> Vector n x Source #

(Symbolic (Context x), KnownNat n, SymbolicInput x) => SymbolicInput (Vector n x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Input

Methods

isValid :: Vector n x -> Bool (Context (Vector n x)) Source #

Substitution (Vector n b) (Zp n) b Source # 
Instance details

Defined in ZkFold.Base.Algebra.Polynomials.Multivariate.Substitution

Methods

subs :: Vector n b -> Zp n -> b Source #

(Ring a, KnownNat n, KnownNat k) => LinearCombination (Vector n a) (Vector n (PolyVec a k)) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.Fold

Methods

linearCombination :: Vector n a -> Vector n a -> Vector n (PolyVec a k) Source #

(Arithmetic a, Arbitrary a, Binary a, Arbitrary (Rep i), Binary (Rep i), Ord (Rep i), Representable i, Foldable i, KnownNat l) => Arbitrary (ArithmeticCircuit a i (Vector l)) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Instance

type MapInput f (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

type MapInput f (ArithmeticCircuit a (Vector n) o) = Vector n f
type MapMessage f (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

type Rep (Vector size) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

type Rep (Vector size) = Zp size
type Input (FieldElement ctx) (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

type ProverMessage (FieldElement ctx) (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

type VerifierMessage (FieldElement ctx) (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

type VerifierOutput (FieldElement ctx) (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

type Witness (FieldElement ctx) (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

type Rep (Vector size a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

type Rep (Vector size a) = D1 ('MetaData "Vector" "ZkFold.Base.Data.Vector" "symbolic-base-0.1.0.0-inplace" 'True) (C1 ('MetaCons "Vector" 'PrefixI 'True) (S1 ('MetaSel ('Just "toV") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector a))))
type Item (Vector n a) Source # 
Instance details

Defined in ZkFold.Base.Data.Vector

type Item (Vector n a) = a
type Context (Vector n x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

type Context (Vector n x) = Context x
type Layout (Vector n x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

type Layout (Vector n x) = Vector n :.: Layout x
type Support (Vector n x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Class

type Support (Vector n x) = Support x
type Degree (ArithmeticCircuit a (Vector n) o) Source # 
Instance details

Defined in ZkFold.Base.Protocol.Protostar.ArithmeticCircuit

type Degree (ArithmeticCircuit a (Vector n) o) = 2

knownNat :: forall size n. (KnownNat size, Integral n) => n Source #

vtoVector :: forall size a. KnownNat size => Vector a -> Maybe (Vector size a) Source #

toVector :: forall size a. KnownNat size => [a] -> Maybe (Vector size a) Source #

unsafeToVector :: forall size a. [a] -> Vector size a Source #

unfold :: forall size a b. KnownNat size => (b -> (a, b)) -> b -> Vector size a Source #

fromVector :: Vector size a -> [a] Source #

(!!) :: Vector size a -> Natural -> a Source #

uncons :: Vector size a -> (a, Vector (size - 1) a) Source #

reverse :: Vector size a -> Vector size a Source #

head :: Vector size a -> a Source #

tail :: Vector size a -> Vector (size - 1) a Source #

singleton :: a -> Vector 1 a Source #

item :: Vector 1 a -> a Source #

mapWithIx :: forall n a b. KnownNat n => (Natural -> a -> b) -> Vector n a -> Vector n b Source #

mapMWithIx :: forall n m a b. (KnownNat n, Monad m) => (Natural -> a -> m b) -> Vector n a -> m (Vector n b) Source #

take :: forall n size a. KnownNat n => Vector size a -> Vector n a Source #

drop :: forall n m a. KnownNat n => Vector (n + m) a -> Vector m a Source #

splitAt :: forall n m a. KnownNat n => Vector (n + m) a -> (Vector n a, Vector m a) Source #

rotate :: forall size a. KnownNat size => Vector size a -> Integer -> Vector size a Source #

shift :: forall size a. KnownNat size => Vector size a -> Integer -> a -> Vector size a Source #

vectorDotProduct :: forall size a. Semiring a => Vector size a -> Vector size a -> a Source #

(.:) :: a -> Vector n a -> Vector (n + 1) a infixr 5 Source #

append :: Vector m a -> Vector n a -> Vector (m + n) a Source #

concat :: Vector m (Vector n a) -> Vector (m * n) a Source #

unsafeConcat :: forall m n a. [Vector n a] -> Vector (m * n) a Source #

chunks :: forall m n a. KnownNat n => Vector (m * n) a -> Vector m (Vector n a) Source #