Safe Haskell | None |
---|---|
Language | Haskell2010 |
Referenced-by-name versions of some instructions.
They allow to "dig" into stack or copy elements of stack referring them by label.
Synopsis
- class HasNamedVar (s :: [Type]) (name :: Symbol) (var :: Type) | s name -> var
- type family HasNamedVars (s :: [Type]) (vs :: [NamedField]) :: Constraint where ...
- type (:=) n ty = 'NamedField n ty
- dupL :: forall var name s. (HasNamedVar s name var, Dupable var) => Label name -> s :-> (var ': s)
- dupLNamed :: forall var name s. (HasNamedVar s name var, Dupable var) => Label name -> s :-> ((name :! var) ': s)
- type VarIsUnnamed x = VarName x ~ 'VarUnnamed
Constraints
class HasNamedVar (s :: [Type]) (name :: Symbol) (var :: Type) | s name -> var Source #
Indicates that stack s
contains a name :! var
or name :? var
value.
varPosition
Instances
(TypeError (StackElemNotFound name) :: Constraint, var ~ NamedVariableNotFound name) => HasNamedVar ('[] :: [Type]) name var Source # | |
Defined in Lorentz.ReferencedByName varPosition :: VarPosition '[] name var | |
ElemHasNamedVar (ty ': s) name var (VarNamePretty ty == 'VarNamed name) => HasNamedVar (ty ': s) name var Source # | |
Defined in Lorentz.ReferencedByName varPosition :: VarPosition (ty ': s) name var |
type family HasNamedVars (s :: [Type]) (vs :: [NamedField]) :: Constraint where ... Source #
Version of HasNamedVar
for multiple variables.
type HasContext = HasNamedVars s ["x" := Integer, "f" := Lambda MText MText]
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.
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.
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.