symbolic-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) (context :: (Type -> Type) -> Type) 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 (context (Vector n)) 

Instances

Instances details
(Symbolic c, (m * 8) ~ n) => FromConstant ByteString (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(Symbolic c, KnownNat n) => FromConstant Integer (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

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

Defined in ZkFold.Symbolic.Data.ByteString

(Symbolic c, NumberOfBits (BaseField c) ~ n) => Iso (FieldElement c) (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

from :: FieldElement c -> ByteString n c Source #

(Symbolic c, KnownNat n) => Eq (Bool c) (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

(==) :: ByteString n c -> ByteString n c -> Bool c Source #

(/=) :: ByteString n c -> ByteString n c -> Bool c Source #

(Symbolic c, KnownNat n) => Arbitrary (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

arbitrary :: Gen (ByteString n c) #

shrink :: ByteString n c -> [ByteString n c] #

(Symbolic c, KnownNat n) => FromJSON (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

ToJSON (ByteString n (Interpreter (Zp p))) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(Symbolic c, (m * 8) ~ n) => IsString (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

fromString :: String -> ByteString n c #

Generic (ByteString n context) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Associated Types

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

Methods

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

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

Show (c (Vector n)) => Show (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

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

show :: ByteString n c -> String #

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

NFData (c (Vector n)) => NFData (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

rnf :: ByteString n c -> () #

Eq (c (Vector n)) => Eq (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

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

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

ToConstant (ByteString n (Interpreter (Zp p))) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Associated Types

type Const (ByteString n (Interpreter (Zp p))) Source #

(Symbolic c, KnownNat n) => BoolType (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

(Symbolic c, KnownNat n) => ShiftBits (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

SymbolicData (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Associated Types

type Context (ByteString n c) :: (Type -> Type) -> Type Source #

type Support (ByteString n c) Source #

type Layout (ByteString n c) :: Type -> Type Source #

(Symbolic c, KnownNat n) => SymbolicInput (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

isValid :: ByteString n c -> Bool (Context (ByteString n c)) Source #

(Symbolic c, NumberOfBits (BaseField c) ~ n) => Iso (ByteString n c) (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

from :: ByteString n c -> FieldElement c Source #

(Symbolic c, KnownNat k, KnownNat n) => Resize (ByteString k c) (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

resize :: ByteString k c -> ByteString n c Source #

(Symbolic c, KnownNat n, KnownRegisterSize r) => Iso (ByteString n c) (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

from :: ByteString n c -> UInt n r c Source #

(Symbolic c, KnownNat n, KnownRegisterSize r) => Iso (UInt n r c) (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

from :: UInt n r c -> ByteString n c Source #

type Rep (ByteString n context) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

type Rep (ByteString n context) = D1 ('MetaData "ByteString" "ZkFold.Symbolic.Data.ByteString" "symbolic-base-0.1.0.0-inplace" 'True) (C1 ('MetaCons "ByteString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (context (Vector n)))))
type Const (ByteString n (Interpreter (Zp p))) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

type Context (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

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

Defined in ZkFold.Symbolic.Data.ByteString

type Layout (ByteString n c) = Layout (c (Vector n))
type Support (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

type Support (ByteString n c) = Support (c (Vector n))

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 Resize a b where Source #

Describes types that can increase or shrink their capacity by adding zero bits to the beginning (i.e. before the higher register) or removing higher bits.

Methods

resize :: a -> b Source #

Instances

Instances details
(Symbolic c, KnownNat k, KnownNat n) => Resize (ByteString k c) (ByteString n c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.ByteString

Methods

resize :: ByteString k c -> ByteString n c Source #

(Symbolic c, KnownNat n, KnownNat k, KnownRegisterSize r) => Resize (UInt n r c) (UInt k r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

resize :: UInt n r c -> UInt k r c Source #

reverseEndianness :: forall wordSize k c m {n}. (Symbolic c, KnownNat wordSize, n ~ (k * wordSize), (m * 8) ~ wordSize) => ByteString n c -> ByteString n c Source #

isSet :: forall c n. Symbolic c => ByteString n c -> Natural -> Bool c Source #

isUnset :: forall c n. Symbolic c => ByteString n c -> Natural -> Bool c Source #

toWords :: forall m wordSize c. (Symbolic c, KnownNat wordSize) => ByteString (m * wordSize) c -> Vector m (ByteString wordSize c) 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.

concat :: forall k m c. Symbolic c => Vector k (ByteString m c) -> ByteString (k * m) c Source #

truncate :: forall m n c. (Symbolic c, KnownNat n, n <= m) => ByteString m c -> ByteString n c Source #

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

append :: forall m n c. Symbolic c => KnownNat m => KnownNat n => ByteString m c -> ByteString n c -> ByteString (m + n) c Source #