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

Lorentz.Run.Simple

Description

Running Lorentz code easily.

For testing and demonstration purposes.

Synopsis

Documentation

(-$?) :: (ZipInstr inps, IsoValue out) => (IsNotInView => inps :-> '[out]) -> ZippedStack inps -> Either (MichelsonFailureWithStack Void) out infixr 2 Source #

Run a lambda with given input.

Note that this always returns one value, but can accept multiple input values (in such case they are grouped into nested pairs).

For testing and demonstration purposes.

(-$) :: (ZipInstr inps, IsoValue out, HasCallStack) => (IsNotInView => inps :-> '[out]) -> ZippedStack inps -> out infixr 2 Source #

Like -$?, assumes that no failure is possible.

For testing and demonstration purposes. Note, that we specify the result type of polymorphic operations to avoid ambiguity arising from polymorphic literals.

Use ZippedStackRepr to represent stack of two or more elements, and ZSNil for empty stacks. Stacks of one element are represented by the element itself.

>>> nop -$ 5
5
>>> sub -$ 3 ::: 2 :: Integer
1
>>> push 9 -$ ZSNil
9
>>> add # add -$ 1 ::: 2 ::: 3 :: Integer
6

(&?-) :: (ZipInstr inps, IsoValue out) => ZippedStack inps -> (IsNotInView => inps :-> '[out]) -> Either (MichelsonFailureWithStack Void) out infixl 2 Source #

Version of (-$?) with arguments flipped.

(&-) :: (ZipInstr inps, IsoValue out, HasCallStack) => ZippedStack inps -> (IsNotInView => inps :-> '[out]) -> out infixl 2 Source #

Version of (-$) with arguments flipped.

(<-$>) :: (ZipInstr inps, IsoValue out, HasCallStack) => (inps :-> '[out]) -> [ZippedStack inps] -> [out] infixl 2 Source #

Version of (-$) applicable to a series of values.

data ZippedStackRepr a b Source #

A type used to represent a zipped stack of at least two elements, isomorphic to a pair and represented as such in Michelson.

Constructors

a ::: b infixr 5 

Instances

Instances details
(CanCastTo a1 a2, CanCastTo b1 b2) => CanCastTo (ZippedStackRepr a1 b1 :: Type) (ZippedStackRepr a2 b2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (ZippedStackRepr a1 b1) -> Proxy (ZippedStackRepr a2 b2) -> () Source #

Generic (ZippedStackRepr a b) Source # 
Instance details

Defined in Lorentz.Zip

Associated Types

type Rep (ZippedStackRepr a b) :: Type -> Type #

Methods

from :: ZippedStackRepr a b -> Rep (ZippedStackRepr a b) x #

to :: Rep (ZippedStackRepr a b) x -> ZippedStackRepr a b #

(Show a, Show b) => Show (ZippedStackRepr a b) Source # 
Instance details

Defined in Lorentz.Zip

(Buildable a, Buildable b) => Buildable (ZippedStackRepr a b) Source # 
Instance details

Defined in Lorentz.Zip

Methods

build :: ZippedStackRepr a b -> Builder #

(Eq a, Eq b) => Eq (ZippedStackRepr a b) Source # 
Instance details

Defined in Lorentz.Zip

(HasAnnotation a, HasAnnotation b) => HasAnnotation (ZippedStackRepr a b) Source # 
Instance details

Defined in Lorentz.Zip

(IsoValue a, IsoValue b) => IsoValue (ZippedStackRepr a b) Source # 
Instance details

Defined in Lorentz.Zip

Associated Types

type ToT (ZippedStackRepr a b) :: T #

type Rep (ZippedStackRepr a b) Source # 
Instance details

Defined in Lorentz.Zip

type ToT (ZippedStackRepr a b) Source # 
Instance details

Defined in Lorentz.Zip

type ToT (ZippedStackRepr a b) = GValueType (Rep (ZippedStackRepr a b))

data ZSNil Source #

A type used to represent an empty zipped stack, isomorphic to a unit and represented as such in Michelson.

Constructors

ZSNil 

Instances

Instances details
Generic ZSNil Source # 
Instance details

Defined in Lorentz.Zip

Associated Types

type Rep ZSNil :: Type -> Type #

Methods

from :: ZSNil -> Rep ZSNil x #

to :: Rep ZSNil x -> ZSNil #

Show ZSNil Source # 
Instance details

Defined in Lorentz.Zip

Methods

showsPrec :: Int -> ZSNil -> ShowS #

show :: ZSNil -> String #

showList :: [ZSNil] -> ShowS #

Buildable ZSNil Source # 
Instance details

Defined in Lorentz.Zip

Methods

build :: ZSNil -> Builder #

Eq ZSNil Source # 
Instance details

Defined in Lorentz.Zip

Methods

(==) :: ZSNil -> ZSNil -> Bool #

(/=) :: ZSNil -> ZSNil -> Bool #

HasAnnotation ZSNil Source # 
Instance details

Defined in Lorentz.Zip

IsoValue ZSNil Source # 
Instance details

Defined in Lorentz.Zip

Associated Types

type ToT ZSNil :: T #

type Rep ZSNil Source # 
Instance details

Defined in Lorentz.Zip

type Rep ZSNil = D1 ('MetaData "ZSNil" "Lorentz.Zip" "lorentz-0.15.0-inplace" 'False) (C1 ('MetaCons "ZSNil" 'PrefixI 'False) (U1 :: Type -> Type))
type ToT ZSNil Source # 
Instance details

Defined in Lorentz.Zip

type ToT ZSNil = GValueType (Rep ZSNil)