indigo-0.6.0: Convenient imperative eDSL over Lorentz.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Indigo.Common.State

Contents

Description

This module contains the core of Indigo language: IndigoState, a datatype that represents its state. It also includes some convenient functions to work with it, to provide rebindable syntax.

IndigoState implements the functionality of a symbolic interpreter. During its execution Lorentz code is being generated.

Functionally, it's the same as having Lorentz instruction that can access and modify a StackVars, referring to values on the stack with a RefId.

Synopsis

Indigo State

newtype IndigoState inp out Source #

IndigoState data type.

It takes as input a StackVars (for the initial state) and returns a GenCode (for the resulting state and the generated Lorentz code).

IndigoState has to be used to write backend typed Lorentz code from the corresponding frontend constructions.

It has no return type, IndigoState instruction may take one or more "return variables", that they assign to values produced during their execution.

Constructors

IndigoState 

Fields

usingIndigoState :: MetaData inp -> IndigoState inp out -> GenCode inp out Source #

Inverse of runIndigoState for utility.

(>>) :: IndigoState inp out -> IndigoState out out1 -> IndigoState inp out1 Source #

Then for rebindable syntax.

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

 ($)  ::              (a -> b) ->   a ->   b
(<$>) :: Functor f => (a -> b) -> f a -> f b

Whereas $ is function application, <$> is function application lifted over a Functor.

Examples

Expand

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

iput :: GenCode inp out -> IndigoState inp out Source #

Put new GenCode.

nopState :: IndigoState inp inp Source #

The simplest IndigoState, it does not modify the stack, nor the produced code.

assignTopVar :: KnownValue x => Var x -> IndigoState (x ': inp) (x ': inp) Source #

Assigns a variable to reference the element on top of the stack.

withObject :: forall a r. KnownValue a => DecomposedObjects -> Var a -> (Object a -> r) -> r Source #

withObjectState :: forall a inp out. KnownValue a => Var a -> (Object a -> IndigoState inp out) -> IndigoState inp out Source #

withStackVars :: (StackVars inp -> IndigoState inp out) -> IndigoState inp out Source #

Utility function to create IndigoState that need access to the current StackVars.

data GenCodeHooks Source #

Constructors

GenCodeHooks 

Fields

stmtHook :: forall inp out any. MetaData any -> Text -> (inp :-> out) -> inp :-> out Source #

auxiliaryHook :: forall inp out any. MetaData any -> Text -> (inp :-> out) -> inp :-> out Source #

exprHook :: forall inp out any. MetaData any -> Text -> (inp :-> out) -> inp :-> out Source #

replStkMd :: MetaData inp -> StackVars inp1 -> MetaData inp1 Source #

alterStkMd :: MetaData inp -> (StackVars inp -> StackVars inp1) -> MetaData inp1 Source #

pushRefMd :: KnownValue a => Var a -> MetaData inp -> MetaData (a ': inp) Source #

pushRef version for MetaData

pushNoRefMd :: KnownValue a => MetaData inp -> MetaData (a ': inp) Source #

pushNoRef version for MetaData

popNoRefMd :: MetaData (a ': inp) -> MetaData inp Source #

popNoRef version for MetaData

data GenCode inp out Source #

Resulting state of IndigoM.

Constructors

GenCode 

Fields

cleanGenCode :: GenCode inp out -> inp :-> inp Source #

Produces the generated Lorentz code that cleans after itself, leaving the same stack as the input one

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

Version of # which performs some optimizations immediately.

In particular, this avoids glueing Nops.