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

ZkFold.Symbolic.Data.Bool

Documentation

class BoolType b where Source #

Methods

true :: b Source #

false :: b Source #

not :: b -> b Source #

(&&) :: b -> b -> b infixr 3 Source #

(||) :: b -> b -> b infixr 2 Source #

xor :: b -> b -> b Source #

Instances

Instances details
BoolType Bool Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Bool

Ring x => BoolType (Bool x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Bool

Methods

true :: Bool x Source #

false :: Bool x Source #

not :: Bool x -> Bool x Source #

(&&) :: Bool x -> Bool x -> Bool x Source #

(||) :: Bool x -> Bool x -> Bool x Source #

xor :: Bool x -> Bool x -> Bool x Source #

(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

newtype Bool x Source #

Constructors

Bool x 

Instances

Instances details
Arithmetic a => SymbolicData a (Bool (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Instance

(Field x, Eq x) => Show (Bool x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Bool

Methods

showsPrec :: Int -> Bool x -> ShowS #

show :: Bool x -> String #

showList :: [Bool x] -> ShowS #

Eq x => Eq (Bool x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Bool

Methods

(==) :: Bool x -> Bool x -> Bool0 #

(/=) :: Bool x -> Bool x -> Bool0 #

Ring x => BoolType (Bool x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Bool

Methods

true :: Bool x Source #

false :: Bool x Source #

not :: Bool x -> Bool x Source #

(&&) :: Bool x -> Bool x -> Bool x Source #

(||) :: Bool x -> Bool x -> Bool x Source #

xor :: Bool x -> Bool x -> Bool x Source #

SymbolicData a x => Conditional (Bool (ArithmeticCircuit a)) x Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Instance

Methods

bool :: x -> x -> Bool (ArithmeticCircuit a) -> x Source #

gif :: Bool (ArithmeticCircuit a) -> x -> x -> x Source #

(?) :: Bool (ArithmeticCircuit a) -> x -> x -> x Source #

(Prime p, Field x, Eq x) => DiscreteField (Bool (Zp p)) x Source # 
Instance details

Defined in ZkFold.Symbolic.Data.DiscreteField

Methods

isZero :: x -> Bool (Zp p) Source #

(Prime p, Ord x) => Ord (Bool (Zp p)) x Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

Methods

(<=) :: x -> x -> Bool (Zp p) Source #

(<) :: x -> x -> Bool (Zp p) Source #

(>=) :: x -> x -> Bool (Zp p) Source #

(>) :: x -> x -> Bool (Zp p) Source #

max :: x -> x -> x Source #

min :: x -> x -> x Source #

(Finite a, Ord i) => Conditional (Bool (Sources a i)) (Bool (Sources a i)) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MonadBlueprint

Methods

bool :: Bool (Sources a i) -> Bool (Sources a i) -> Bool (Sources a i) -> Bool (Sources a i) Source #

gif :: Bool (Sources a i) -> Bool (Sources a i) -> Bool (Sources a i) -> Bool (Sources a i) Source #

(?) :: Bool (Sources a i) -> Bool (Sources a i) -> Bool (Sources a i) -> Bool (Sources a i) Source #

Arithmetic a => DiscreteField (Bool (ArithmeticCircuit a)) (ArithmeticCircuit a) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Instance

Arithmetic a => Eq (Bool (ArithmeticCircuit a)) (ArithmeticCircuit a) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.Instance

SymbolicData a x => Eq (Bool (ArithmeticCircuit a)) (Structural x) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Eq.Structural

Arithmetic a => Ord (Bool (ArithmeticCircuit a)) (ArithmeticCircuit a) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ord

SymbolicData a x => Ord (Bool (ArithmeticCircuit a)) (Lexicographical x) Source #

Every SymbolicData type can be compared lexicographically.

Instance details

Defined in ZkFold.Symbolic.Data.Ord

(Finite (Zp p), KnownNat n) => Eq (Bool (Zp p)) (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

(==) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

(/=) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

(Arithmetic a, KnownNat n) => Eq (Bool (ArithmeticCircuit a)) (UInt n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

(Ring a, Eq (Bool a) (BaseField (Ed25519 a))) => Eq (Bool a) (Point (Ed25519 a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.Ed25519

Methods

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

(/=) :: Point (Ed25519 a) -> Point (Ed25519 a) -> Bool a Source #

(Finite (Zp p), KnownNat n) => Ord (Bool (Zp p)) (UInt n (Zp p)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

Methods

(<=) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

(<) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

(>=) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

(>) :: UInt n (Zp p) -> UInt n (Zp p) -> Bool (Zp p) Source #

max :: UInt n (Zp p) -> UInt n (Zp p) -> UInt n (Zp p) Source #

min :: UInt n (Zp p) -> UInt n (Zp p) -> UInt n (Zp p) Source #

(Arithmetic a, KnownNat n) => Ord (Bool (ArithmeticCircuit a)) (UInt n (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Data.UInt

(Finite a, Ord i) => Conditional (Bool (Sources a i)) (Sources a i) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MonadBlueprint

Methods

bool :: Sources a i -> Sources a i -> Bool (Sources a i) -> Sources a i Source #

gif :: Bool (Sources a i) -> Sources a i -> Sources a i -> Sources a i Source #

(?) :: Bool (Sources a i) -> Sources a i -> Sources a i -> Sources a i Source #

Ord i => Eq (Bool (Sources a i)) (Sources a i) Source # 
Instance details

Defined in ZkFold.Symbolic.Compiler.ArithmeticCircuit.MonadBlueprint

Methods

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

(/=) :: Sources a i -> Sources a i -> Bool (Sources a i) Source #

(Arithmetic a, KnownNat tokens) => Eq (Bool (ArithmeticCircuit a)) (Output tokens datum (ArithmeticCircuit a)) Source # 
Instance details

Defined in ZkFold.Symbolic.Cardano.Types

Methods

(==) :: Output tokens datum (ArithmeticCircuit a) -> Output tokens datum (ArithmeticCircuit a) -> Bool (ArithmeticCircuit a) Source #

(/=) :: Output tokens datum (ArithmeticCircuit a) -> Output tokens datum (ArithmeticCircuit a) -> Bool (ArithmeticCircuit a) Source #

all :: (BoolType b, Foldable t) => (x -> b) -> t x -> b Source #

all1 :: (BoolType b, Functor t, Foldable t) => (x -> b) -> t x -> b Source #

any :: (BoolType b, Foldable t) => (x -> b) -> t x -> b Source #