lorentz-0.4.0: EDSL for the Michelson Language
Safe HaskellNone
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.

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

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

data Condition arg argl argr outb out where Source #

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 
IsZero :: (UnaryArithOpHs Eq' a, UnaryArithResHs Eq' a ~ Bool) => Condition (a ': s) s s o o 
IsNotZero :: (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 :: (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.

(<.) :: 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 :: (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

fromInteger :: Num a => Integer -> a #

Conversion from an Integer. An integer literal represents the application of the function fromInteger to the appropriate value of type Integer, so such literals have type (Num a) => a.

fromLabel :: IsLabel x a => a #