arithmetic-circuits-0.2.0: Arithmetic circuits for zkSNARKs

Safe HaskellNone
LanguageHaskell2010

Circuit.Expr

Synopsis

Documentation

data UnOp f a where Source #

Constructors

UNeg :: UnOp f f 
UNot :: UnOp f Bool 
URot :: Int -> Int -> UnOp f f

rotate bits

Instances
Show f => Show (UnOp f a) Source # 
Instance details

Defined in Circuit.Expr

Methods

showsPrec :: Int -> UnOp f a -> ShowS #

show :: UnOp f a -> String #

showList :: [UnOp f a] -> ShowS #

Pretty (UnOp f a) Source # 
Instance details

Defined in Circuit.Expr

Methods

pretty :: UnOp f a -> Doc #

prettyList :: [UnOp f a] -> Doc #

data BinOp f a where Source #

Constructors

BAdd :: BinOp f f 
BSub :: BinOp f f 
BMul :: BinOp f f 
BAnd :: BinOp f Bool 
BOr :: BinOp f Bool 
BXor :: BinOp f Bool 
Instances
Show f => Show (BinOp f a) Source # 
Instance details

Defined in Circuit.Expr

Methods

showsPrec :: Int -> BinOp f a -> ShowS #

show :: BinOp f a -> String #

showList :: [BinOp f a] -> ShowS #

Pretty (BinOp f a) Source # 
Instance details

Defined in Circuit.Expr

Methods

pretty :: BinOp f a -> Doc #

prettyList :: [BinOp f a] -> Doc #

data Expr i f ty where Source #

Expression data type of (arithmetic) expressions over a field f with variable names/indices coming from i.

Constructors

EConst :: f -> Expr i f f 
EConstBool :: Bool -> Expr i f Bool 
EVar :: i -> Expr i f f 
EVarBool :: i -> Expr i f Bool 
EUnOp :: UnOp f ty -> Expr i f ty -> Expr i f ty 
EBinOp :: BinOp f ty -> Expr i f ty -> Expr i f ty -> Expr i f ty 
EIf :: Expr i f Bool -> Expr i f ty -> Expr i f ty -> Expr i f ty 
EEq :: Expr i f f -> Expr i f f -> Expr i f Bool 
Instances
(Show i, Show f) => Show (Expr i f ty) Source # 
Instance details

Defined in Circuit.Expr

Methods

showsPrec :: Int -> Expr i f ty -> ShowS #

show :: Expr i f ty -> String #

showList :: [Expr i f ty] -> ShowS #

(Pretty f, Pretty i, Pretty ty) => Pretty (Expr i f ty) Source # 
Instance details

Defined in Circuit.Expr

Methods

pretty :: Expr i f ty -> Doc #

prettyList :: [Expr i f ty] -> Doc #

type ExprM f a = State (ArithCircuit f, Int) a Source #

emit :: Gate Wire f -> ExprM f () Source #

Add a Mul and its output to the ArithCircuit

imm :: ExprM f Wire Source #

Fresh intermediate variables

addVar :: Either Wire (AffineCircuit Wire f) -> AffineCircuit Wire f Source #

Turn a wire into an affine circuit, or leave it be

addWire :: Num f => Either Wire (AffineCircuit Wire f) -> ExprM f Wire Source #

Turn an affine circuit into a wire, or leave it be

freshInput :: ExprM f Wire Source #

Fresh input variables

freshOutput :: ExprM f Wire Source #

Fresh output variables

rotateList :: Int -> [a] -> [a] Source #

Rotate a list to the right

exprToArithCircuit Source #

Arguments

:: Num f 
=> Expr Int f ty

expression to compile

-> Wire

Wire to assign the output of the expression to

-> ExprM f () 

Translate an arithmetic expression to an arithmetic circuit

evalExpr Source #

Arguments

:: (Bits f, Num f) 
=> (i -> vars -> Maybe f)

variable lookup

-> Expr i f ty

expression to evaluate

-> vars

input values

-> ty

resulting value

Evaluate arithmetic expressions directly, given an environment

truncRotate Source #

Arguments

:: Bits f 
=> Int

number of bits to truncate to

-> Int

number of bits to rotate by

-> f 
-> f 

Truncate a number to the given number of bits and perform a right rotation (assuming small-endianness) within the truncation.