Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Referenced-by-type versions of some instructions.
They allow to "dip" into stack or copy elements of stack referring them
by type. Their use is justified, because in most cases there is only
one element of each type of stack, and in cases when this does not hold
(e.g. entrypoint with multiple parameters of the same type), it might be
a good idea to wrap those types into a newtype or to use primitives from
named
package.
This module is experimental, i.e. everything here should work but may be removed in favor of better development practices.
Each instruction is followed with usage example.
Synopsis
- class st ~ (Head st ': Tail st) => DupT (a :: Type) (st :: [Type]) where
- class dipInp ~ (a ': Tail dipInp) => DipT a inp dipInp dipOut out | inp a -> dipInp, dipOut inp a -> out, inp out a -> dipOut where
- dropT :: forall a inp dinp dout out. (DipT a inp dinp dout out, dinp ~ (a ': dout)) => inp :-> out
Documentation
class st ~ (Head st ': Tail st) => DupT (a :: Type) (st :: [Type]) where Source #
Allows duplicating stack elements referring them by type.
>>>
:{
dupSample1 :: [Integer, MText, ()] :-> [MText, Integer, MText, ()] dupSample1 = dupT @MText :}
>>>
pretty $ dupSample1 # zipInstr -$ 123 ::: [mt|Hello|] ::: ()
Hello : 123 : Hello : ()
>>>
:{
dupSample2 :: [Integer, MText, ()] :-> [MText, Integer, MText, ()] dupSample2 = dupT :}
>>>
pretty $ dupSample2 # zipInstr -$ 123 ::: [mt|Hello|] ::: ()
Hello : 123 : Hello : ()
>>>
:{
dupSampleErr1 :: '[] :-> a dupSampleErr1 = dupT @Bool :} ... ... • Element of type 'Bool' is not present on stack ... '[] ...
>>>
:{
-- Should fully infer both wildcards dupSampleErr2 :: _ :-> [Bool, Integer, _, ()] dupSampleErr2 = dupT :} ... ... • Found type wildcard ‘_’ ... standing for ‘'[Integer, Bool, ()] :: [*]’ ... ... • Found type wildcard ‘_’ standing for ‘Bool’ ... To use the inferred type, enable PartialTypeSignatures ...
>>>
:{
-- Should fully infer both wildcards _dupSampleErr3 :: [Integer, _, ()] :-> (Bool ': _) _dupSampleErr3 = dupT :} ... ... • Found type wildcard ‘_’ standing for ‘Bool’ ... ... • Found type wildcard ‘_’ ... standing for ‘'[Integer, Bool, ()] :: [*]’ ...
dupT :: st :-> (a ': st) Source #
Duplicate an element of stack referring it by type.
If stack contains multiple entries of this type, compile error is raised.
Instances
(EnsureElem a st, TheOnlyC (StackElemNotFound st a) (StackElemAmbiguous st a) (FindIndices (DefaultEqSym1 a) st) indexGHC, succ_index ~ 'S (ToPeano indexGHC), ConstraintDUPNLorentz succ_index st (a ': st) a, Dupable a) => DupT a st Source # | |
Defined in Lorentz.Referenced |
class dipInp ~ (a ': Tail dipInp) => DipT a inp dipInp dipOut out | inp a -> dipInp, dipOut inp a -> out, inp out a -> dipOut where Source #
Allows diving into stack referring expected new tip by type.
>>>
:{
dipSample1 :: [Natural, ()] :-> '[()] -> [Integer, MText, Natural, ()] :-> [Integer, MText, ()] dipSample1 = dipT @Natural :}
>>>
pretty $ dipSample1 drop # zipInstr -$ 123 ::: [mt|Hello|] ::: 321 ::: ()
123 : Hello : ()
>>>
:{
dipSample2 :: [Natural, ()] :-> '[()] -> [Integer, MText, Natural, ()] :-> [Integer, MText, ()] dipSample2 = dipT -- No type application needed :}
>>>
pretty $ dipSample2 drop # zipInstr -$ 123 ::: [mt|Hello|] ::: 321 ::: ()
123 : Hello : ()
>>>
:{
-- An implementation of dropT that demands a bit more from inference. dipSample3 :: forall a inp dinp dout out. ( DipT a inp dinp dout out , dinp ~ (a ': dout) ) => inp :-> out dipSample3 = dipT (drop @a) :}
>>>
:{
pretty $ dipSample3 @Natural @'[Integer, MText, Natural, ()] # zipInstr -$ 123 ::: [mt|Hello|] ::: 321 ::: () :} 123 : Hello : ()
>>>
:{
_dipSampleErr1 :: [Natural, ()] :-> '[()] -> [Integer, MText, ()] :-> [Integer, MText, ()] _dipSampleErr1 = dipT @Natural :} ... ... • Element of type 'Natural' is not present on stack ... '[Integer, MText, ()] ...
>>>
:{
_dipSampleErr2 :: [Natural, ()] :-> '[()] -> [Integer, MText, Natural, (), Natural] :-> [Integer, MText, ()] _dipSampleErr2 = dipT @Natural :} ... ... • Ambiguous reference to element of type 'Natural' for stack ... '[Integer, MText, Natural, (), Natural] ...
>>>
:{
_dipSampleErr3 :: '[] :-> '[()] -> [Integer, MText, Natural, ()] :-> [Integer, MText, ()] _dipSampleErr3 = dipT @Natural :} ... ... • dipT requires a Lorentz instruction that takes input on the stack. ...
dipT :: (dipInp :-> dipOut) -> inp :-> out Source #
Dip down until an element of the given type is on top of the stack.
If the stack does not contain an element of this type, or contains more than one, then a compile-time error is raised.
Instances
(dipInp ~ (a ': tail_dipInp), EnsureElem a inp, RequireNonEmpty ('Text "dipT requires a Lorentz instruction that takes input on the stack.") dipInp, TheOnlyC (StackElemNotFound inp a) (StackElemAmbiguous inp a) (FindIndices (DefaultEqSym1 a) inp) indexGHC, index ~ ToPeano indexGHC, ConstraintDIPNLorentz index inp out dipInp dipOut) => DipT a inp dipInp dipOut out Source # | |
dropT :: forall a inp dinp dout out. (DipT a inp dinp dout out, dinp ~ (a ': dout)) => inp :-> out Source #
Remove element with the given type from the stack.
>>>
:{
dropSample1 :: [Integer, (), Natural] :-> [Integer, Natural] dropSample1 = dropT @() :}
>>>
pretty $ dropSample1 # zipInstr -$ 123 ::: () ::: 321
123 : 321
>>>
:{
dropSampleErr1 :: [Integer, Natural] :-> [Integer, Natural] dropSampleErr1 = dropT @() :} ... ... • Element of type '()' is not present on stack ... '[Integer, Natural] ...
>>>
:{
dropSampleErr1 :: [Integer, Integer] :-> '[Integer] dropSampleErr1 = dropT @Integer :} ... ... • Ambiguous reference to element of type 'Integer' for stack ... '[Integer, Integer] ...