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

Lorentz.ReferencedByName

Description

Referenced-by-name versions of some instructions.

They allow to "dig" into stack or copy elements of stack referring them by label.

When operating on a polymorphic stack, you'll need HasNamedVar constraint:

>>> :{
_foo :: s :-> ("bar" :! Natural) : s
_foo = dupLNamed #bar
--
_bar :: s :-> MText : s
_bar = dupL #baz
:}
...
... No instance for (HasNamedVar s "bar" Natural)
...
... No instance for (HasNamedVar s "baz" MText)
...
>>> :{
_foo :: HasNamedVar s "bar" Natural => s :-> ("bar" :! Natural) : s
_foo = dupLNamed #bar
--
_bar :: HasNamedVar s "bar" Natural => s :-> Natural : s
_bar = dupL #bar
:}

When the stack contains type variables, you may need VarIsUnnamed constraint:

>>> :{
_bar
  :: HasNamedVar s "foo" MText
  => qux : s :-> ("foo" :! MText) : qux : s
_bar = dupLNamed #foo
--
_baz
  :: HasNamedVar s "bar" MText
  => corge : s :-> MText : corge : s
_baz = dupL #bar
:}
...
... Not clear which name `qux` variable has
... Consider adding `VarIsUnnamed qux` constraint
... or carrying a named variable instead
...
... Not clear which name `corge` variable has
...
>>> :{
_bar
  :: (HasNamedVar s "foo" MText, VarIsUnnamed qux)
  => qux : s :-> ("foo" :! MText) : qux : s
_bar = dupLNamed #foo
--
_baz
  :: (HasNamedVar s "bar" MText, VarIsUnnamed corge)
  => corge : s :-> MText : corge : s
_baz = dupL #bar
:}
Synopsis

Constraints

class HasNamedVar s name var | s name -> var Source #

Indicates that stack s contains a name :! var value.

Minimal complete definition

varPosition

Instances

Instances details
(Bottom, StackElemNotFound name :: Constraint, var ~ NamedVariableNotFound name) => HasNamedVar ('[] :: [Type]) name var Source # 
Instance details

Defined in Lorentz.ReferencedByName

Methods

varPosition :: VarPosition '[] name var

ElemHasNamedVar (ty ': s) name var (VarNamePretty ty == 'VarNamed name) => HasNamedVar (ty ': s) name var Source # 
Instance details

Defined in Lorentz.ReferencedByName

Methods

varPosition :: VarPosition (ty ': s) name var

type family HasNamedVars s vs where ... Source #

Version of HasNamedVar for multiple variables.

type HasContext = HasNamedVars s ["x" := Integer, "f" := Lambda MText MText]

Equations

HasNamedVars _ '[] = () 
HasNamedVars s ((n := ty) ': vs) = (HasNamedVar s n ty, HasNamedVars s vs) 

type (:=) n ty = 'NamedField n ty infixr 0 Source #

Instructions

dupL :: forall var name s. (HasNamedVar s name var, Dupable var) => Label name -> s :-> (var ': s) Source #

Take the element with given label on stack and copy it on top.

If there are multiple variables with given label, the one closest to the top of the stack is picked.

>>> dupL #foo # pair -$ (#foo :! (123 :: Integer))
(123,fromLabel @"foo" :! 123)
>>> (dupL #bar # ppaiir) -$ (#foo :! (123 :: Integer)) ::: (#bar :! (321 :: Integer))
(321,(fromLabel @"foo" :! 123,fromLabel @"bar" :! 321))
>>> (dupL #baz # ppaiir) -$ (#foo :! (123 :: Integer)) ::: (#bar :! (321 :: Integer))
...
... Element with name "baz" is not present on stack
...

dupLNamed :: forall var name s. (HasNamedVar s name var, Dupable var) => Label name -> s :-> ((name :! var) ': s) Source #

Version of dupL that leaves a named variable on stack.

>>> dupLNamed #foo # pair -$ (#foo :! (123 :: Integer))
(fromLabel @"foo" :! 123,fromLabel @"foo" :! 123)
>>> (dupLNamed #bar # ppaiir) -$ (#foo :! (123 :: Integer)) ::: (#bar :! (321 :: Integer))
(fromLabel @"bar" :! 321,(fromLabel @"foo" :! 123,fromLabel @"bar" :! 321))
>>> (dupLNamed #baz # ppaiir) -$ (#foo :! (123 :: Integer)) ::: (#bar :! (321 :: Integer))
...
... Element with name "baz" is not present on stack
...

Other

type VarIsUnnamed x = VarName x ~ 'VarUnnamed Source #

Requires type x to be an unnamed variable.

When e.g. dupL sees a polymorphic variable, it can't judge whether is it a variable we are seeking for or not; VarIsUnnamed helps to assure the type system that given variable won't be named.