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

ZkFold.Symbolic.Data.Ord

Synopsis

Documentation

class Ord b a where Source #

Methods

(<=) :: a -> a -> b Source #

(<) :: a -> a -> b Source #

(>=) :: a -> a -> b Source #

(>) :: a -> a -> b Source #

max :: a -> a -> a Source #

min :: a -> a -> a Source #

Instances

Instances details
Ord a => Ord Bool a Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

Methods

(<=) :: a -> a -> Bool Source #

(<) :: a -> a -> Bool Source #

(>=) :: a -> a -> Bool Source #

(>) :: a -> a -> Bool Source #

max :: a -> a -> a Source #

min :: a -> a -> a Source #

Symbolic c => Ord (Bool c) (FieldElement c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.FieldElement

(Symbolic c, SymbolicOutput x, Context x ~ c) => Ord (Bool c) (Lexicographical x) Source #

Every SymbolicData type can be compared lexicographically.

Instance details

Defined in ZkFold.Symbolic.Data.Ord

(Symbolic c, KnownNat n, KnownRegisterSize r, KnownRegisters c n r, regSize ~ GetRegisterSize (BaseField c) n r, KnownNat (Ceil regSize OrdWord)) => Ord (Bool c) (UInt n r c) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

(<=) :: UInt n r c -> UInt n r c -> Bool c Source #

(<) :: UInt n r c -> UInt n r c -> Bool c Source #

(>=) :: UInt n r c -> UInt n r c -> Bool c Source #

(>) :: UInt n r c -> UInt n r c -> Bool c Source #

max :: UInt n r c -> UInt n r c -> UInt n r c Source #

min :: UInt n r c -> UInt n r c -> UInt n r c Source #

newtype Lexicographical a Source #

A newtype wrapper for easy definition of Ord instances (though not necessarily a most effective one)

Constructors

Lexicographical a 

Instances

Instances details
SymbolicData a => SymbolicData (Lexicographical a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

(Symbolic c, SymbolicOutput x, Context x ~ c) => Ord (Bool c) (Lexicographical x) Source #

Every SymbolicData type can be compared lexicographically.

Instance details

Defined in ZkFold.Symbolic.Data.Ord

type Context (Lexicographical a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

type Layout (Lexicographical a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

type Payload (Lexicographical a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

type Support (Lexicographical a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

blueprintGE :: forall r i a w m f. (Arithmetic a, MonadCircuit i a w m, Zip f, Foldable f, KnownNat r) => f i -> f i -> m i Source #

bitwiseGE :: forall r c f. (Symbolic c, Zip f, Foldable f, KnownNat r) => c f -> c f -> Bool c Source #

Given two lists of bits of equal length, compares them lexicographically.

bitwiseGT :: forall r c f. (Symbolic c, Zip f, Foldable f, KnownNat r) => c f -> c f -> Bool c Source #

Given two lists of bits of equal length, compares them lexicographically.

getBitsBE :: forall c x. (SymbolicOutput x, Context x ~ c) => x -> c List Source #

getBitsBE x returns a list of circuits computing bits of x, eldest to youngest.