lorentz-0.14.1: EDSL for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lorentz.Rebinded

Description

Reimplementation of some syntax sugar.

You need the following module pragmas to make it work smoothly:

Synopsis

Documentation

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

Aliases for (#) used by do-blocks.

pure :: Applicative f => a -> f a #

Lift a value.

return :: Monad m => a -> m a #

Inject a value into the monadic type.

class IsCondition cond arg argl argr outb out where Source #

Everything that can be put after if keyword.

The first type argument stands for the condition type, and all other type arguments define stack types around/within the if then else construction. For semantics of each type argument see Condition.

Methods

ifThenElse :: cond -> (argl :-> outb) -> (argr :-> outb) -> arg :-> out Source #

Defines semantics of if ... then ... else ... construction.

Instances

Instances details
(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

Defined in Lorentz.Expr

Methods

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

(arg ~ arg0, argl ~ argl0, argr ~ argr0, outb ~ outb0, out ~ out0) => IsCondition (Condition arg argl argr outb out) arg0 argl0 argr0 outb0 out0 Source # 
Instance details

Defined in Lorentz.Rebinded

Methods

ifThenElse :: Condition arg argl argr outb out -> (argl0 :-> outb0) -> (argr0 :-> outb0) -> arg0 :-> out0 Source #

data Condition arg argl argr outb out where Source #

The most basic predicate for if ... then .. else ... construction, defines a kind of operation applied to the top elements of the current stack.

Type arguments mean: 1. Input of if 2. Left branch input 3. Right branch input 4. Output of branches 5. Output of if

Constructors

Holds :: Condition (Bool ': s) s s o o 
IsSome :: Condition (Maybe a ': s) (a ': s) s o o 
IsNone :: Condition (Maybe a ': s) s (a ': s) o o 
IsLeft :: Condition (Either l r ': s) (l ': s) (r ': s) o o 
IsRight :: Condition (Either l r ': s) (r ': s) (l ': s) o o 
IsCons :: Condition ([a] ': s) (a ': ([a] ': s)) s o o 
IsNil :: Condition ([a] ': s) s (a ': ([a] ': s)) o o 
Not :: Condition s s1 s2 ob o -> Condition s s2 s1 ob o 
IsZero :: (UnaryArithOpHs Eq' a, UnaryArithResHs Eq' a ~ Bool) => Condition (a ': s) s s o o 
IsEq :: NiceComparable a => Condition (a ': (a ': s)) s s o o 
IsNeq :: NiceComparable a => Condition (a ': (a ': s)) s s o o 
IsLt :: NiceComparable a => Condition (a ': (a ': s)) s s o o 
IsGt :: NiceComparable a => Condition (a ': (a ': s)) s s o o 
IsLe :: NiceComparable a => Condition (a ': (a ': s)) s s o o 
IsGe :: NiceComparable a => Condition (a ': (a ': s)) s s o o 
NamedBinCondition :: Condition (a ': (a ': s)) s s o o -> Label n1 -> Label n2 -> Condition ((n1 :! a) ': ((n2 :! a) ': s)) s s o o

Explicitly named binary condition, to ensure proper order of stack arguments.

PreserveArgsBinCondition :: (Dupable a, Dupable b) => (forall st o. Condition (a ': (b ': st)) st st o o) -> Condition (a ': (b ': s)) (a ': (b ': s)) (a ': (b ': s)) (a ': (b ': s)) s

Provide the compared arguments to if branches.

Instances

Instances details
(arg ~ arg0, argl ~ argl0, argr ~ argr0, outb ~ outb0, out ~ out0) => IsCondition (Condition arg argl argr outb out) arg0 argl0 argr0 outb0 out0 Source # 
Instance details

Defined in Lorentz.Rebinded

Methods

ifThenElse :: Condition arg argl argr outb out -> (argl0 :-> outb0) -> (argr0 :-> outb0) -> arg0 :-> out0 Source #

(<.) :: NiceComparable a => Label n1 -> Label n2 -> Condition ((n1 :! a) ': ((n2 :! a) ': s)) s s o o infix 4 Source #

Named version of IsLt.

In this and similar operators you provide names of accepted stack operands as a safety measure of that they go in the expected order.

(>.) :: NiceComparable a => Label n1 -> Label n2 -> Condition ((n1 :! a) ': ((n2 :! a) ': s)) s s o o infix 4 Source #

Named version of IsGt.

(<=.) :: NiceComparable a => Label n1 -> Label n2 -> Condition ((n1 :! a) ': ((n2 :! a) ': s)) s s o o infix 4 Source #

Named version of IsLe.

(>=.) :: NiceComparable a => Label n1 -> Label n2 -> Condition ((n1 :! a) ': ((n2 :! a) ': s)) s s o o infix 4 Source #

Named version of IsGe.

(==.) :: NiceComparable a => Label n1 -> Label n2 -> Condition ((n1 :! a) ': ((n2 :! a) ': s)) s s o o infix 4 Source #

Named version of IsEq.

(/=.) :: NiceComparable a => Label n1 -> Label n2 -> Condition ((n1 :! a) ': ((n2 :! a) ': s)) s s o o infix 4 Source #

Named version of IsNeq.

keepIfArgs :: (Dupable a, Dupable b) => (forall st o. Condition (a ': (b ': st)) st st o o) -> Condition (a ': (b ': s)) (a ': (b ': s)) (a ': (b ': s)) (a ': (b ': s)) s Source #

Condition modifier, makes stack operands of binary comparison to be available within if branches.

Re-exports required for RebindableSyntax

fromLabel :: IsLabel x a => a #

negate :: Num a => a -> a #

Unary negation.