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

ZkFold.Symbolic.Data.ByteString

Synopsis

Documentation

newtype ByteString (n :: Natural) a Source #

A ByteString which stores n bits and uses elements of a as registers, one element per register. Bit layout is Big-endian.

Constructors

ByteString [a] 

Instances

Instances details
(FromConstant Natural a, KnownNat n) => FromConstant Integer (ByteString n a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(FromConstant Natural a, KnownNat n) => FromConstant Natural (ByteString n a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(Arithmetic a, KnownNat n) => SymbolicData a (ByteString n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(KnownNat n, FromConstant Natural a) => ToWords Natural (ByteString n a) Source #

This allows us to calculate hash of a bytestring represented by a Natural number. This is only useful for testing when the length of the test string is unknown at compile time. This should not be exposed to users (and they probably won't find it useful anyway).

Instance details

Defined in ZkFold.Symbolic.Algorithms.Hash.SHA2

Methods

toWords :: Natural -> [ByteString n a] Source #

(Finite (Zp p), KnownNat n) => Arbitrary (ByteString n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

arbitrary :: Gen (ByteString n (Zp p)) #

shrink :: ByteString n (Zp p) -> [ByteString n (Zp p)] #

Generic (ByteString n a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Associated Types

type Rep (ByteString n a) :: Type -> Type #

Methods

from :: ByteString n a -> Rep (ByteString n a) x #

to :: Rep (ByteString n a) x -> ByteString n a #

Show a => Show (ByteString n a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

showsPrec :: Int -> ByteString n a -> ShowS #

show :: ByteString n a -> String #

showList :: [ByteString n a] -> ShowS #

NFData a => NFData (ByteString n a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

rnf :: ByteString n a -> () #

Eq a => Eq (ByteString n a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

(==) :: ByteString n a -> ByteString n a -> Bool #

(/=) :: ByteString n a -> ByteString n a -> Bool #

(Finite (Zp p), KnownNat n) => BoolType (ByteString n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

true :: ByteString n (Zp p) Source #

false :: ByteString n (Zp p) Source #

not :: ByteString n (Zp p) -> ByteString n (Zp p) Source #

(&&) :: ByteString n (Zp p) -> ByteString n (Zp p) -> ByteString n (Zp p) Source #

(||) :: ByteString n (Zp p) -> ByteString n (Zp p) -> ByteString n (Zp p) Source #

xor :: ByteString n (Zp p) -> ByteString n (Zp p) -> ByteString n (Zp p) Source #

(Arithmetic a, KnownNat n) => BoolType (ByteString n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(Finite (Zp p), KnownNat n) => ShiftBits (ByteString n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(Arithmetic a, KnownNat n) => ShiftBits (ByteString n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

ToConstant a Natural => ToConstant (ByteString n a) Natural Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(KnownNat n, KnownNat m, m <= n, Mod n m ~ 0, Finite (Zp p)) => Concat (ByteString m (Zp p)) (ByteString n (Zp p)) Source #

Unfortunately, Haskell does not support dependent types yet, so we have no possibility to infer the exact type of the result (the list can contain an arbitrary number of words). We can only impose some restrictions on n and m.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

concat :: [ByteString m (Zp p)] -> ByteString n (Zp p) Source #

Mod n m ~ 0 => Concat (ByteString m (ArithmeticCircuit a)) (ByteString n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(KnownNat wordSize, KnownNat n, Finite (Zp p), wordSize <= n, 1 <= wordSize, 1 <= n, Mod n wordSize ~ 0) => ToWords (ByteString n (Zp p)) (ByteString wordSize (Zp p)) Source #

A ByteString of length n can only be split into words of length wordSize if all of the following conditions are met: 1. wordSize is not greater than n; 2. wordSize is not zero; 3. The bytestring is not empty; 4. wordSize divides n.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

toWords :: ByteString n (Zp p) -> [ByteString wordSize (Zp p)] Source #

(KnownNat wordSize, 1 <= wordSize, 1 <= n, Mod n wordSize ~ 0) => ToWords (ByteString n (ArithmeticCircuit a)) (ByteString wordSize (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(KnownNat m, KnownNat n, n <= m, Finite (Zp p)) => Truncate (ByteString m (Zp p)) (ByteString n (Zp p)) Source #

Only a bigger ByteString can be truncated into a smaller one.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

truncate :: ByteString m (Zp p) -> ByteString n (Zp p) Source #

(KnownNat n, n <= m) => Truncate (ByteString m (ArithmeticCircuit a)) (ByteString n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(KnownNat n, m <= n, Finite (Zp p)) => Extend (ByteString m (Zp p)) (ByteString n (Zp p)) Source #

Only a smaller ByteString can be extended into a bigger one.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

extend :: ByteString m (Zp p) -> ByteString n (Zp p) Source #

(KnownNat m, KnownNat n, m <= n, Arithmetic a) => Extend (ByteString m (ArithmeticCircuit a)) (ByteString n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(Finite (Zp p), KnownNat n) => Iso (ByteString n (Zp p)) (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

from :: ByteString n (Zp p) -> UInt n (Zp p) Source #

(Arithmetic a, KnownNat n) => Iso (ByteString n (ArithmeticCircuit a)) (UInt n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(Finite (Zp p), KnownNat n) => Iso (UInt n (Zp p)) (ByteString n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

from :: UInt n (Zp p) -> ByteString n (Zp p) Source #

(Arithmetic a, KnownNat n) => Iso (UInt n (ArithmeticCircuit a)) (ByteString n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

type Rep (ByteString n a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

type Rep (ByteString n a) = D1 ('MetaData "ByteString" "ZkFold.Symbolic.Data.ByteString" "zkfold-base-0.1.0.0-inplace" 'True) (C1 ('MetaCons "ByteString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])))

class ShiftBits a where Source #

A class for data types that support bit shift and bit cyclic shift (rotation) operations.

Minimal complete definition

(shiftBits | shiftBitsL, shiftBitsR), (rotateBits | rotateBitsL, rotateBitsR)

Methods

shiftBits :: a -> Integer -> a Source #

shiftBits performs a left shift when its agrument is greater than zero and a right shift otherwise.

shiftBitsL :: a -> Natural -> a Source #

shiftBitsR :: a -> Natural -> a Source #

rotateBits :: a -> Integer -> a Source #

rotateBits performs a left cyclic shift when its agrument is greater than zero and a right cyclic shift otherwise.

rotateBitsL :: a -> Natural -> a Source #

rotateBitsR :: a -> Natural -> a Source #

class ToWords a b where Source #

Describes types which can be split into words of equal size. Parameters have to be of different types as ByteString store their lengths on type level and hence after splitting they chagne types.

Methods

toWords :: a -> [b] Source #

Instances

Instances details
(KnownNat n, FromConstant Natural a) => ToWords Natural (ByteString n a) Source #

This allows us to calculate hash of a bytestring represented by a Natural number. This is only useful for testing when the length of the test string is unknown at compile time. This should not be exposed to users (and they probably won't find it useful anyway).

Instance details

Defined in ZkFold.Symbolic.Algorithms.Hash.SHA2

Methods

toWords :: Natural -> [ByteString n a] Source #

(KnownNat wordSize, KnownNat n, Finite (Zp p), wordSize <= n, 1 <= wordSize, 1 <= n, Mod n wordSize ~ 0) => ToWords (ByteString n (Zp p)) (ByteString wordSize (Zp p)) Source #

A ByteString of length n can only be split into words of length wordSize if all of the following conditions are met: 1. wordSize is not greater than n; 2. wordSize is not zero; 3. The bytestring is not empty; 4. wordSize divides n.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

toWords :: ByteString n (Zp p) -> [ByteString wordSize (Zp p)] Source #

(KnownNat wordSize, 1 <= wordSize, 1 <= n, Mod n wordSize ~ 0) => ToWords (ByteString n (ArithmeticCircuit a)) (ByteString wordSize (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

class Concat a b where Source #

Describes types which can be made by concatenating several words of equal length.

Methods

concat :: [a] -> b Source #

Instances

Instances details
(KnownNat n, KnownNat m, m <= n, Mod n m ~ 0, Finite (Zp p)) => Concat (ByteString m (Zp p)) (ByteString n (Zp p)) Source #

Unfortunately, Haskell does not support dependent types yet, so we have no possibility to infer the exact type of the result (the list can contain an arbitrary number of words). We can only impose some restrictions on n and m.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

concat :: [ByteString m (Zp p)] -> ByteString n (Zp p) Source #

Mod n m ~ 0 => Concat (ByteString m (ArithmeticCircuit a)) (ByteString n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

class Truncate a b where Source #

Describes types that can be truncated by dropping several bits from the end (i.e. stored in the lower registers)

Methods

truncate :: a -> b Source #

Instances

Instances details
(KnownNat m, KnownNat n, n <= m, Finite (Zp p)) => Truncate (ByteString m (Zp p)) (ByteString n (Zp p)) Source #

Only a bigger ByteString can be truncated into a smaller one.

Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

truncate :: ByteString m (Zp p) -> ByteString n (Zp p) Source #

(KnownNat n, n <= m) => Truncate (ByteString m (ArithmeticCircuit a)) (ByteString n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString