sindre-0.2: A programming language for simple GUIs

Portabilityportable
Stabilityprovisional

Sindre.Compiler

Contents

Description

Transforming a Sindre program into a callable function.

Synopsis

Main Entry Point

compileSindre :: MonadBackend m => Program -> ClassMap m -> ObjectMap m -> FuncMap m -> GlobMap m -> ([SindreOption], Arguments -> m ExitCode)Source

Given a Sindre program and its environment, compile the program and return a pair of command-line options accepted by the program, and a startup function. The program can be executed by calling the startup function with the command-like arguments and an initial value for the root widget. If compilation fails, an IO exception is raised.

type ClassMap m = Map Identifier (Constructor m)Source

Mapping from class names to constructors.

type ObjectMap m = Map Identifier (ObjectRef -> m (NewObject m))Source

Mapping from object names to object constructor functions.

type FuncMap m = Map Identifier (Compiler m ([Value] -> Sindre m Value))Source

Mapping from function names to built-in functions. These must first be executed in the Compiler monad as they may have specific requirements of the environment.

type GlobMap m = Map Identifier (m Value)Source

Mapping from names of global variables to computations that yield their initial values.

Object Construction

data NewWidget m Source

Container wrapping a newly created widget.

Constructors

forall s . Widget m s => NewWidget s 

data NewObject m Source

Container wrapping a newly created object.

Constructors

forall s . Object m s => NewObject s 

type Constructor m = WidgetRef -> [(Maybe Value, ObjectRef)] -> ConstructorM m (NewWidget m)Source

Function that, given an initial value, the name of itself if any, and a list of children, yields a computation that constructs a new widget.

data ConstructorM m a Source

The monad in which widget construction takes place. You can only execute this by defining a Constructor that is then used in a Sindre program (see also ClassMap). An example usage could be:

 myWidget :: Constructor MyBackEnd
 myWidget w k cs : do
   -- ConstructorM is an instance of Alternative, so we can provide
   -- defaults or fallbacks for missing parameters.
   arg - 'param' \"myParam\" <| return 12
   rest of construction

class MonadBackend m => Param m a whereSource

Class of types that a given backend can convert to from Values. In effect, a monadic version of Mold.

Methods

moldM :: Value -> m (Maybe a)Source

Attempt to convert the given Sindre value to the relevant Haskell value.

paramM :: (Param m a, MonadBackend m) => Identifier -> ConstructorM m aSource

As paramM, but moldM is always used for conversion.

paramAs :: MonadBackend m => Identifier -> (Value -> Maybe a) -> ConstructorM m aSource

k paramAs f yields the value of the widget parameter k, using f to convert it to the proper Haskell type. If f returns Nothing, badValue k is called. If k does not exist, noParam k is called.

param :: (Mold a, MonadBackend m) => Identifier -> ConstructorM m aSource

As param, but mold is always used for conversion.

noParam :: String -> ConstructorM m aSource

noParam k signals that parameter k is missing.

badValue :: String -> Value -> ConstructorM m aSource

badValue k v signals that parameter k is present with value v, but that v is an invalid value.

Compiler Interface

These definitions can be used in builtin functions that may need to change global variables.

type Compiler m a = RWS (CompilerEnv m) (Initialisation m) (CompilerState m) aSource

Monad inside which compilation takes place.

value :: MonadBackend m => Identifier -> Compiler m (Execution m Value)Source

Given a variable name, return a computation that will yield the value of the variable when executed.

setValue :: MonadBackend m => Identifier -> Compiler m (Value -> Execution m ())Source

Given a variable name, return a computation that can be used to set the value of the variable when executed.