sindre-0.6: A programming language for simple GUIs
LicenseMIT-style (see LICENSE)
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Sindre.Runtime

Description

Definitions for the Sindre runtime environment.

Synopsis

Documentation

data Sindre m a Source #

The main monad in which a Sindre program executes. More specialised monads, such as Execution are used for specific purposes, but they all run on top of the Sindre monad.

Instances

Instances details
MonadTrans Sindre Source # 
Instance details

Defined in Sindre.Runtime

Methods

lift :: Monad m => m a -> Sindre m a #

MonadBackend im => MonadSindre im Sindre Source # 
Instance details

Defined in Sindre.Runtime

Methods

sindre :: Sindre im a -> Sindre im a Source #

back :: im a -> Sindre im a Source #

Monad (Sindre m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

(>>=) :: Sindre m a -> (a -> Sindre m b) -> Sindre m b #

(>>) :: Sindre m a -> Sindre m b -> Sindre m b #

return :: a -> Sindre m a #

Functor (Sindre m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

fmap :: (a -> b) -> Sindre m a -> Sindre m b #

(<$) :: a -> Sindre m b -> Sindre m a #

MonadFail m => MonadFail (Sindre m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

fail :: String -> Sindre m a #

Applicative (Sindre m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

pure :: a -> Sindre m a #

(<*>) :: Sindre m (a -> b) -> Sindre m a -> Sindre m b #

liftA2 :: (a -> b -> c) -> Sindre m a -> Sindre m b -> Sindre m c #

(*>) :: Sindre m a -> Sindre m b -> Sindre m b #

(<*) :: Sindre m a -> Sindre m b -> Sindre m a #

MonadIO m => MonadIO (Sindre m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

liftIO :: IO a -> Sindre m a #

MonadCont (Sindre m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

callCC :: ((a -> Sindre m b) -> Sindre m a) -> Sindre m a #

MonadState (SindreEnv m) (Sindre m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

get :: Sindre m (SindreEnv m) #

put :: SindreEnv m -> Sindre m () #

state :: (SindreEnv m -> (a, SindreEnv m)) -> Sindre m a #

Semigroup (Sindre m ()) Source # 
Instance details

Defined in Sindre.Runtime

Methods

(<>) :: Sindre m () -> Sindre m () -> Sindre m () #

sconcat :: NonEmpty (Sindre m ()) -> Sindre m () #

stimes :: Integral b => b -> Sindre m () -> Sindre m () #

Monoid (Sindre m ()) Source # 
Instance details

Defined in Sindre.Runtime

Methods

mempty :: Sindre m () #

mappend :: Sindre m () -> Sindre m () -> Sindre m () #

mconcat :: [Sindre m ()] -> Sindre m () #

execSindre :: MonadBackend m => SindreEnv m -> Sindre m a -> m ExitCode Source #

execSindre e m executes the action m in environment e, returning the exit code of m.

quitSindre :: MonadBackend m => ExitCode -> Sindre m () Source #

Immediately return from execSindre, returning the given exit code.

class (MonadBackend im, MonadFail (m im), MonadFail im) => MonadSindre im m where Source #

MonadSindre im m is the class of monads m that run on top of Sindre with backend im, and can thus access Sindre functionality.

Minimal complete definition

sindre

Methods

sindre :: Sindre im a -> m im a Source #

Lift a Sindre operation into this monad.

back :: im a -> m im a Source #

Lift a backend operation into this monad.

Instances

Instances details
MonadBackend im => MonadSindre im Execution Source # 
Instance details

Defined in Sindre.Runtime

Methods

sindre :: Sindre im a -> Execution im a Source #

back :: im a -> Execution im a Source #

MonadBackend im => MonadSindre im Sindre Source # 
Instance details

Defined in Sindre.Runtime

Methods

sindre :: Sindre im a -> Sindre im a Source #

back :: im a -> Sindre im a Source #

MonadBackend im => MonadSindre im ConstructorM Source # 
Instance details

Defined in Sindre.Compiler

Methods

sindre :: Sindre im a -> ConstructorM im a Source #

back :: im a -> ConstructorM im a Source #

MonadBackend im => MonadSindre im (ObjectM o) Source # 
Instance details

Defined in Sindre.Runtime

Methods

sindre :: Sindre im a -> ObjectM o im a Source #

back :: im a -> ObjectM o im a Source #

fullRedraw :: MonadSindre im m => m im () Source #

class (MonadIO m, MonadFail m, Mold (RootPosition m)) => MonadBackend m where Source #

A monad that can be used as the layer beneath Sindre.

Associated Types

type BackEvent m :: * Source #

type RootPosition m :: * Source #

data NewObject im Source #

Container describing a newly created object.

newObject :: s -> Map Identifier (Method s im) -> [Field s im] -> (Event -> ObjectM s im ()) -> NewObject im Source #

data NewWidget im Source #

Container describing a newly created widget.

newWidget :: s -> Map Identifier (Method s im) -> [Field s im] -> (Event -> ObjectM s im ()) -> ObjectM s im SpaceNeed -> (Rectangle -> ObjectM s im SpaceUse) -> NewWidget im Source #

data DataSlot im Source #

data FieldDesc s im v Source #

A typed description of a field, which may be read-write or read-only. When constructing the actual widget, you must turn these into real Fields by using the field function. A description of a field consists of a name and monadic actions for reading and optionally writing to the field.

Constructors

ReadWriteField Identifier (ObjectM s im v) (v -> ObjectM s im ()) 
ReadOnlyField Identifier (ObjectM s im v) 

getField :: FieldDesc s im v -> ObjectM s im v Source #

field :: (MonadFail im, Mold v) => FieldDesc s im v -> Field s im Source #

Turn a Haskell-typed high-level field description into a Value-typed field.

data Field s im Source #

An opaque notion of a field. These are for internal use in the Sindre runtime.

type Method s im = [Value] -> ObjectM s im Value Source #

A method takes as arguments a list of Values and returns another Value. You probably do not want to call these directly from Haskell code, as they are dynamically typed. See function for a convenient way to turn a Haskell function into a suitable method.

data ObjectM s im a Source #

Instances

Instances details
MonadBackend im => MonadSindre im (ObjectM o) Source # 
Instance details

Defined in Sindre.Runtime

Methods

sindre :: Sindre im a -> ObjectM o im a Source #

back :: im a -> ObjectM o im a Source #

MonadState s (ObjectM s im) Source # 
Instance details

Defined in Sindre.Runtime

Methods

get :: ObjectM s im s #

put :: s -> ObjectM s im () #

state :: (s -> (a, s)) -> ObjectM s im a #

MonadReader ObjectRef (ObjectM s im) Source # 
Instance details

Defined in Sindre.Runtime

Methods

ask :: ObjectM s im ObjectRef #

local :: (ObjectRef -> ObjectRef) -> ObjectM s im a -> ObjectM s im a #

reader :: (ObjectRef -> a) -> ObjectM s im a #

Monad (ObjectM s im) Source # 
Instance details

Defined in Sindre.Runtime

Methods

(>>=) :: ObjectM s im a -> (a -> ObjectM s im b) -> ObjectM s im b #

(>>) :: ObjectM s im a -> ObjectM s im b -> ObjectM s im b #

return :: a -> ObjectM s im a #

Functor (ObjectM s im) Source # 
Instance details

Defined in Sindre.Runtime

Methods

fmap :: (a -> b) -> ObjectM s im a -> ObjectM s im b #

(<$) :: a -> ObjectM s im b -> ObjectM s im a #

MonadFail im => MonadFail (ObjectM s im) Source # 
Instance details

Defined in Sindre.Runtime

Methods

fail :: String -> ObjectM s im a #

Applicative (ObjectM s im) Source # 
Instance details

Defined in Sindre.Runtime

Methods

pure :: a -> ObjectM s im a #

(<*>) :: ObjectM s im (a -> b) -> ObjectM s im a -> ObjectM s im b #

liftA2 :: (a -> b -> c) -> ObjectM s im a -> ObjectM s im b -> ObjectM s im c #

(*>) :: ObjectM s im a -> ObjectM s im b -> ObjectM s im b #

(<*) :: ObjectM s im a -> ObjectM s im b -> ObjectM s im a #

(MonadIO m, MonadBackend m) => MonadIO (ObjectM o m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

liftIO :: IO a -> ObjectM o m a #

data SindreEnv m Source #

Instances

Instances details
MonadState (SindreEnv m) (Sindre m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

get :: Sindre m (SindreEnv m) #

put :: SindreEnv m -> Sindre m () #

state :: (SindreEnv m -> (a, SindreEnv m)) -> Sindre m a #

data Execution m a Source #

Instances

Instances details
MonadBackend im => MonadSindre im Execution Source # 
Instance details

Defined in Sindre.Runtime

Methods

sindre :: Sindre im a -> Execution im a Source #

back :: im a -> Execution im a Source #

Monad (Execution m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

(>>=) :: Execution m a -> (a -> Execution m b) -> Execution m b #

(>>) :: Execution m a -> Execution m b -> Execution m b #

return :: a -> Execution m a #

Functor (Execution m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

fmap :: (a -> b) -> Execution m a -> Execution m b #

(<$) :: a -> Execution m b -> Execution m a #

MonadFail m => MonadFail (Execution m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

fail :: String -> Execution m a #

Applicative (Execution m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

pure :: a -> Execution m a #

(<*>) :: Execution m (a -> b) -> Execution m a -> Execution m b #

liftA2 :: (a -> b -> c) -> Execution m a -> Execution m b -> Execution m c #

(*>) :: Execution m a -> Execution m b -> Execution m b #

(<*) :: Execution m a -> Execution m b -> Execution m a #

MonadCont (Execution m) Source # 
Instance details

Defined in Sindre.Runtime

Methods

callCC :: ((a -> Execution m b) -> Execution m a) -> Execution m a #

class Mold a where Source #

Methods

mold :: Value -> Maybe a Source #

unmold :: a -> Value Source #

Instances

Instances details
Mold Bool Source # 
Instance details

Defined in Sindre.Runtime

Mold Double Source # 
Instance details

Defined in Sindre.Runtime

Mold Int Source # 
Instance details

Defined in Sindre.Runtime

Mold Integer Source # 
Instance details

Defined in Sindre.Runtime

Mold () Source # 
Instance details

Defined in Sindre.Runtime

Methods

mold :: Value -> Maybe () Source #

unmold :: () -> Value Source #

Mold Text Source # 
Instance details

Defined in Sindre.Runtime

Mold String Source # 
Instance details

Defined in Sindre.Runtime

Mold Value Source # 
Instance details

Defined in Sindre.Runtime

Mold FormatString Source # 
Instance details

Defined in Sindre.Formatting

Mold a => Mold (Maybe a) Source # 
Instance details

Defined in Sindre.Runtime

Methods

mold :: Value -> Maybe (Maybe a) Source #

unmold :: Maybe a -> Value Source #

Mold (Align, Align) Source # 
Instance details

Defined in Sindre.Runtime