| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Lorentz.Expr
Contents
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 #a |+| 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 #config; toField #minBound } |&|
take |<=| do{ dupL #config; toField #maxBound }
Synopsis
- type Expr inp out res = inp :-> (res ': out)
- take :: Expr (a ': s) s a
- unaryExpr :: (forall s. (a ': s) :-> (r ': s)) -> Expr s0 s1 a -> Expr s0 s1 r
- ($:) :: (forall s. (a ': s) :-> (r ': s)) -> Expr s0 s1 a -> Expr s0 s1 r
- binaryExpr :: (forall s. (a ': (b ': s)) :-> (r ': s)) -> Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r
- (|+|) :: ArithOpHs Add a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r
- (|-|) :: ArithOpHs Sub a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r
- (|*|) :: ArithOpHs Mul a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r
- (|==|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool
- (|/=|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool
- (|<|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool
- (|>|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool
- (|<=|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool
- (|>=|) :: NiceComparable a => Expr s0 s1 a -> Expr s1 s2 a -> Expr s0 s2 Bool
- (|&|) :: ArithOpHs And a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r
- (|||) :: ArithOpHs Or a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r
- (|.|.|) :: ArithOpHs Or a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r
- (|^|) :: ArithOpHs Xor a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r
- (|<<|) :: ArithOpHs Lsl a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r
- (|>>|) :: ArithOpHs Lsr a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r
- (|:|) :: Expr s0 s1 a -> Expr s1 s2 [a] -> Expr s0 s2 [a]
- pairE :: (Expr s0 s1 a, Expr s1 s2 b) -> Expr s0 s2 (a, b)
- (|@|) :: Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (a, b)
- (|%!|) :: Expr s0 s1 Integer -> Expr s1 s2 Natural -> Expr s0 s2 Rational
- listE :: KnownValue a => [Expr s s a] -> Expr s s [a]
- transferTokensE :: (NiceParameter p, IsNotInView) => ("arg" :! Expr s0 s1 p) -> ("amount" :! Expr s1 s2 Mutez) -> ("contract" :! Expr s2 s3 (ContractRef p)) -> Expr s0 s3 Operation
- createContractE :: IsNotInView => ("delegate" :! Expr s0 s1 (Maybe KeyHash)) -> ("balance" :! Expr s1 s2 Mutez) -> ("storage" :! Expr s2 s3 st) -> ("contract" :! Contract p st vd) -> Expr s0 (TAddress p vd ': s3) Operation
- viewE :: forall name arg ret p vd s0 s1 s2. (HasCallStack, KnownSymbol name, KnownValue arg, NiceViewable ret, HasView vd name arg ret) => ("arg" :! Expr s0 s1 arg) -> ("address" :! Expr s1 s2 (TAddress p vd)) -> Expr s0 s2 ret
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 r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r infixl 6 Source #
Expressions addition.
(|-|) :: ArithOpHs Sub a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r infixl 6 Source #
Expressions subtraction.
(|*|) :: ArithOpHs Mul a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r 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 r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r infixl 2 Source #
Bitwise/logical AND on expressions.
(|||) :: ArithOpHs Or a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r infixl 1 Source #
Bitwise/logical OR on expressions.
In case you find this operator looking weird, see |.|.|
(|.|.|) :: ArithOpHs Or a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r infixl 1 Source #
An alias for |||.
(|^|) :: ArithOpHs Xor a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r infixl 3 Source #
Bitwise/logical XOR on expressions.
(|<<|) :: ArithOpHs Lsl a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r infix 8 Source #
Left shift on expressions.
(|>>|) :: ArithOpHs Lsr a b r => Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 r infix 8 Source #
Right shift on expressions.
(|:|) :: Expr s0 s1 a -> Expr s1 s2 [a] -> Expr s0 s2 [a] infixr 1 Source #
cons on expressions.
one :: a : s :-> [a] : s one = take |:| nil
pairE :: (Expr s0 s1 a, Expr s1 s2 b) -> Expr s0 s2 (a, b) Source #
An alias for |@|.
trivialContract :: ((), storage) :-> ([Operation], Storage)
trivialContract =
pairE
( nil
, cdr
)
(|@|) :: Expr s0 s1 a -> Expr s1 s2 b -> Expr s0 s2 (a, b) infixr 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.
(|%!|) :: Expr s0 s1 Integer -> Expr s1 s2 Natural -> Expr s0 s2 Rational infixl 7 Source #
Construct a Rational value from a given nominator and denominator.
In case denominator is 0, fails with custom exception.
listE :: KnownValue a => [Expr s s a] -> Expr s s [a] Source #
Construct a list given the constructor for each element.
transferTokensE :: (NiceParameter p, IsNotInView) => ("arg" :! Expr s0 s1 p) -> ("amount" :! Expr s1 s2 Mutez) -> ("contract" :! Expr s2 s3 (ContractRef p)) -> Expr s0 s3 Operation Source #
Version of transferTokens instruction that accepts
all the arguments as expressions.
transferTokensE ! #arg L.unit ! #amount (push zeroMutez) ! #contract take |:| nil
You can provide arguments in arbitrary order, but direction of stack changes
flow is fixed: stack change in arg expression affects stack available in
amount expression, and stack changes in amount expression affect
stack changes in contract expression.
createContractE :: IsNotInView => ("delegate" :! Expr s0 s1 (Maybe KeyHash)) -> ("balance" :! Expr s1 s2 Mutez) -> ("storage" :! Expr s2 s3 st) -> ("contract" :! Contract p st vd) -> Expr s0 (TAddress p vd ': s3) Operation Source #
Version of createContract instruction that accepts
all the arguments as expressions.
createContractE ! #delegate none ! #balance (push zeroMutez) ! #storage unit ! #contract myContract
Note that this returns an operation, and pushes the address of the newly created contract as a side-effect.
viewE :: forall name arg ret p vd s0 s1 s2. (HasCallStack, KnownSymbol name, KnownValue arg, NiceViewable ret, HasView vd name arg ret) => ("arg" :! Expr s0 s1 arg) -> ("address" :! Expr s1 s2 (TAddress p vd)) -> Expr s0 s2 ret Source #
Version of view instruction that accepts all the arguments as expressions.
viewE @"myview" ! #arg (push zeroMutez) ! #address (push addr)