lorentz-0.12.1: EDSL for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Lorentz.Expr

Description

Evaluation of expressions.

Stack-based languages allow convenient expressions evaluation, for that we just need binary instructions in infix notation, not in Polish postfix notation that add and other primitives provide. Compare:

>>> push 1; push 2; push 3; push 4; mul; rsub; add

vs

>>> push 1 |+| push 2 |-| push 3 |*| push 4

In these expressions each atom is some instruction providing a single value on top of the stack, for example:

nthOdd :: Lambda Natural Natural
nthOdd = take |*| push Natural 2 |+| push Natural 1

For binary operations we provide the respective operators. Unary operations can be lifted with unaryExpr:

implication :: [Bool, Bool] :-> '[Bool]
implication = unaryExpr not take |.|.| take

or with its alias in form of an operator:

implication :: [Bool, Bool] :-> '[Bool]
implication = not $: take |.|.| take

Stack changes are propagated from left to right. If an atom consumes an element at the top of the stack, the next atom will accept only the remainder of the stack.

In most cases you should prefer providing named variables to the formulas in order to avoid messing up with the arguments:

f :: ("a" :! Natural) : ("b" :! Natural) : ("c" :! Natural) : s :-> Integer : s
f = fromNamed b |-| fromNamed #c

Instead of putting all the elements on the stack upon applying the formula, you may find it more convenient to evaluate most of the arguments right within the formula:

withinRange
  :: Natural : a : b : c : ("config" :! Config) : s
  :-> Bool : a : b : c : ("config" :! Config) : s
withinRange =
  dup  |>=| do{ dupL minBound } |&|
  take |<=| do{ dupL maxBound }
Synopsis

Documentation

type Expr inp out res = inp :-> (res ': out) Source #

Expression is just an instruction accepting stack inp and producing stack out with evaluation result res at the top.

take :: Expr (a ': s) s a Source #

Consume an element at the top of stack. This is just an alias for nop.

unaryExpr :: (forall s. (a ': s) :-> (r ': s)) -> Expr s0 s1 a -> Expr s0 s1 r Source #

Lift an instruction to an unary operation on expressions.

($:) :: (forall s. (a ': s) :-> (r ': s)) -> Expr s0 s1 a -> Expr s0 s1 r infixr 9 Source #

An alias for unaryExpr.

binaryExpr :: (forall s. (a ': (b ': s)) :-> (r ': s)) -> Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r Source #

Lift an instruction to a binary operation on expressions.

(|+|) :: ArithOpHs Add a b => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (ArithResHs Add a b) infixl 6 Source #

Expressions addition.

(|-|) :: ArithOpHs Sub a b => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (ArithResHs Sub a b) infixl 6 Source #

Expressions subtraction.

(|*|) :: ArithOpHs Mul a b => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (ArithResHs Mul a b) infixl 7 Source #

Expressions multiplication.

(|==|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool infix 4 Source #

Expressions comparison.

(|/=|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool infix 4 Source #

Expressions comparison.

(|<|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool infix 4 Source #

Expressions comparison.

(|>|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool infix 4 Source #

Expressions comparison.

(|<=|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool infix 4 Source #

Expressions comparison.

(|>=|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool infix 4 Source #

Expressions comparison.

(|&|) :: ArithOpHs And a b => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (ArithResHs And a b) infixl 2 Source #

Bitwise/logical AND on expressions.

(|||) :: ArithOpHs Or a b => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (ArithResHs Or a b) infixl 1 Source #

Bitwise/logical OR on expressions.

In case you find this operator looking weird, see |.|.|

(|.|.|) :: ArithOpHs Or a b => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (ArithResHs Or a b) infixl 1 Source #

An alias for |||.

(|^|) :: ArithOpHs Xor a b => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (ArithResHs Xor a b) infixl 3 Source #

Bitwise/logical XOR on expressions.

(|<<|) :: ArithOpHs Lsl a b => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (ArithResHs Lsl a b) infix 8 Source #

Left shift on expressions.

(|>>|) :: ArithOpHs Lsr a b => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (ArithResHs Lsr a b) infix 8 Source #

Right shift on expressions.

(|:|) :: Expr s0 s1 a -> Expr s1 s2 [a] -> Expr s0 s2 [a] infix 1 Source #

cons on expressions.

one :: a : s :-> [a] : s
one = take |:| nil

(|@|) :: Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (a, b) infix 0 Source #

Construct a simple pair.

trivialContract :: ((), storage) :-> ([Operation], Storage)
trivialContract = nil |@| cdr

This is useful as pair appears even in simple contracts. For more advanced types, use constructT.

listE :: KnownValue a => [Expr s s a] -> Expr s s [a] Source #

Construct a list given the constructor for each element.

Orphan instances

(i ~ arg, o ~ argl, o ~ argr, r ~ Bool, outb ~ out) => IsCondition (Expr i o r) arg argl argr outb out Source #

An expression producing Bool can be placed as condition to 'if'.

Instance details

Methods

ifThenElse :: Expr i o r -> (argl :-> outb) -> (argr :-> outb) -> arg :-> out Source #