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

Lorentz.Zip

Description

Stack zipping.

This module provides functions for flattening stacks into tuples.

Also here we define an instance which turns any instruction, not only lambdas, into a valid value.

Synopsis

Documentation

class KnownIsoT (ZippedStack s) => ZipInstr (s :: [Type]) where Source #

Zipping stack into tuple and back.

Associated Types

type ZippedStack s :: Type Source #

A type which contains the whole stack zipped.

Methods

zipInstrTyped :: Instr (ToTs s) '[ToT (ZippedStack s)] Source #

Fold given stack into single value in typed Michelson.

unzipInstrTyped :: Instr '[ToT (ZippedStack s)] (ToTs s) Source #

Unfold given stack from a single value in typed Michelson.

Instances

Instances details
ZipInstr ('[] :: [Type]) Source # 
Instance details

Defined in Lorentz.Zip

Associated Types

type ZippedStack '[] Source #

Methods

zipInstrTyped :: Instr (ToTs '[]) '[ToT (ZippedStack '[])] Source #

unzipInstrTyped :: Instr '[ToT (ZippedStack '[])] (ToTs '[]) Source #

(ZipInstr (b ': s), KnownIsoT a) => ZipInstr (a ': (b ': s)) Source #

Such definition seems the only possible one we can support efficiently.

Instance details

Defined in Lorentz.Zip

Associated Types

type ZippedStack (a ': (b ': s)) Source #

Methods

zipInstrTyped :: Instr (ToTs (a ': (b ': s))) '[ToT (ZippedStack (a ': (b ': s)))] Source #

unzipInstrTyped :: Instr '[ToT (ZippedStack (a ': (b ': s)))] (ToTs (a ': (b ': s))) Source #

KnownIsoT a => ZipInstr '[a] Source # 
Instance details

Defined in Lorentz.Zip

Associated Types

type ZippedStack '[a] Source #

Methods

zipInstrTyped :: Instr (ToTs '[a]) '[ToT (ZippedStack '[a])] Source #

unzipInstrTyped :: Instr '[ToT (ZippedStack '[a])] (ToTs '[a]) Source #

zipInstr :: forall s. ZipInstr s => s :-> '[ZippedStack s] Source #

Fold given stack into single value.

unzipInstr :: forall s. ZipInstr s => '[ZippedStack s] :-> s Source #

Unfold given stack from a single value.

type ZipInstrs ss = Each '[ZipInstr] ss Source #

Require several stacks to comply ZipInstr constraint.

zippingStack :: ZipInstrs [inp, out] => (inp :-> out) -> Fn (ZippedStack inp) (ZippedStack out) Source #

Flatten both ends of instruction stack.

unzippingStack :: ZipInstrs [inp, out] => Fn (ZippedStack inp) (ZippedStack out) -> inp :-> out Source #

Unflatten both ends of instruction stack.

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.1-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)

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

Version of # which performs some optimizations immediately.

In particular, this avoids glueing Nops and DIP Nops.