| Portability | portable |
|---|---|
| Stability | provisional |
| Safe Haskell | None |
Sindre.Runtime
Description
Definitions for the Sindre runtime environment.
- data Sindre m a
- execSindre :: MonadBackend m => SindreEnv m -> Sindre m a -> m ExitCode
- quitSindre :: MonadBackend m => ExitCode -> Sindre m ()
- class (MonadBackend im, Monad (m im)) => MonadSindre im m where
- broadcast :: MonadBackend im => Event -> ObjectM o im ()
- changed :: MonadBackend im => Identifier -> Value -> Value -> ObjectM o im ()
- redraw :: MonadBackend im => ObjectM s im ()
- fullRedraw :: MonadSindre im m => m im ()
- setRootPosition :: MonadBackend m => Value -> Sindre m ()
- class (MonadIO m, Functor m, Applicative m, Mold (RootPosition m)) => MonadBackend m where
- type BackEvent m :: *
- type RootPosition m :: *
- redrawRoot :: Sindre m ()
- redrawRegion :: [Rectangle] -> Sindre m ()
- getBackEvent :: Sindre m (Maybe Event)
- waitForBackEvent :: Sindre m Event
- printVal :: String -> m ()
- data NewObject im
- newObject :: s -> Map Identifier (Method s im) -> [Field s im] -> (Event -> ObjectM s im ()) -> NewObject im
- data NewWidget im
- 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
- data DataSlot im
- instWidget :: NewWidget im -> Constraints -> DataSlot im
- instObject :: NewObject im -> DataSlot im
- data FieldDesc s im v
- = ReadWriteField Identifier (ObjectM s im v) (v -> ObjectM s im ())
- | ReadOnlyField Identifier (ObjectM s im v)
- fieldName :: FieldDesc s im v -> Identifier
- getField :: FieldDesc s im v -> ObjectM s im v
- field :: Mold v => FieldDesc s im v -> Field s im
- data Field s im
- type Method s im = [Value] -> ObjectM s im Value
- data ObjectM s im a
- setFieldByRef :: MonadBackend im => ObjectRef -> Identifier -> Value -> Execution im Value
- getFieldByRef :: MonadBackend im => ObjectRef -> Identifier -> Execution im Value
- callMethodByRef :: MonadBackend im => ObjectRef -> Identifier -> [Value] -> Execution im Value
- recvEventByRef :: MonadBackend im => WidgetRef -> Event -> Execution im ()
- draw :: MonadSindre im m => WidgetRef -> Maybe Rectangle -> m im SpaceUse
- compose :: MonadSindre im m => WidgetRef -> m im SpaceNeed
- data SindreEnv m = SindreEnv {}
- newEnv :: WidgetRef -> Arguments -> SindreEnv m
- globalVal :: MonadBackend m => Key -> Sindre m Value
- setGlobal :: MonadBackend m => Key -> Value -> Sindre m ()
- data Execution m a
- execute :: MonadBackend m => Execution m Value -> Sindre m Value
- execute_ :: MonadBackend m => Execution m a -> Sindre m ()
- returnHere :: MonadBackend m => Execution m Value -> Execution m Value
- doReturn :: MonadBackend m => Value -> Execution m ()
- nextHere :: MonadBackend m => Execution m () -> Execution m ()
- doNext :: MonadBackend m => Execution m ()
- breakHere :: MonadBackend m => Execution m () -> Execution m ()
- doBreak :: MonadBackend m => Execution m ()
- contHere :: MonadBackend m => Execution m () -> Execution m ()
- doCont :: MonadBackend m => Execution m ()
- setScope :: MonadBackend m => [Value] -> Execution m a -> Execution m a
- enterScope :: MonadBackend m => [Value] -> Execution m a -> Execution m a
- lexicalVal :: MonadBackend m => Key -> Execution m Value
- setLexical :: MonadBackend m => Key -> Value -> Execution m ()
- eventLoop :: MonadBackend m => EventHandler m -> Sindre m ()
- type EventHandler m = Event -> Execution m ()
- class Mold a where
Documentation
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
| MonadTrans Sindre | |
| MonadBackend im => MonadSindre im Sindre | |
| Monad (Sindre m) | |
| Functor (Sindre m) | |
| Applicative (Sindre m) | |
| MonadIO m => MonadIO (Sindre m) | |
| MonadCont (Sindre m) | |
| MonadReader (QuitFun m) (Sindre m) | |
| MonadState (SindreEnv m) (Sindre m) | |
| Monoid (Sindre m ()) |
execSindre :: MonadBackend m => SindreEnv m -> Sindre m a -> m ExitCodeSource
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, Monad (m im)) => MonadSindre im m whereSource
MonadSindre im m is the class of monads m that run on top of
Sindre with backend im, and can thus access Sindre
functionality.
Methods
sindre :: Sindre im a -> m im aSource
Lift a Sindre operation into this monad.
Lift a backend operation into this monad.
Instances
| MonadBackend im => MonadSindre im Execution | |
| MonadBackend im => MonadSindre im Sindre | |
| MonadBackend im => MonadSindre im ConstructorM | |
| MonadBackend im => MonadSindre im (ObjectM o) |
changed :: MonadBackend im => Identifier -> Value -> Value -> ObjectM o im ()Source
redraw :: MonadBackend im => ObjectM s im ()Source
fullRedraw :: MonadSindre im m => m im ()Source
setRootPosition :: MonadBackend m => Value -> Sindre m ()Source
class (MonadIO m, Functor m, Applicative m, Mold (RootPosition m)) => MonadBackend m whereSource
A monad that can be used as the layer beneath Sindre.
Methods
redrawRoot :: Sindre m ()Source
redrawRegion :: [Rectangle] -> Sindre m ()Source
getBackEvent :: Sindre m (Maybe Event)Source
Instances
newObject :: s -> Map Identifier (Method s im) -> [Field s im] -> (Event -> ObjectM s im ()) -> NewObject imSource
newWidget :: s -> Map Identifier (Method s im) -> [Field s im] -> (Event -> ObjectM s im ()) -> ObjectM s im SpaceNeed -> (Rectangle -> ObjectM s im SpaceUse) -> NewWidget imSource
instWidget :: NewWidget im -> Constraints -> DataSlot imSource
instObject :: NewObject im -> DataSlot imSource
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) |
fieldName :: FieldDesc s im v -> IdentifierSource
field :: Mold v => FieldDesc s im v -> Field s imSource
Turn a Haskell-typed high-level field description into a
Value-typed field.
An opaque notion of a field. These are for internal use in the Sindre runtime.
Instances
| MonadBackend im => MonadSindre im (ObjectM o) | |
| MonadReader ObjectRef (ObjectM s im) | |
| MonadState s (ObjectM s im) | |
| Monad (ObjectM s im) | |
| Functor (ObjectM s im) | |
| Applicative (ObjectM s im) | |
| (MonadIO m, MonadBackend m) => MonadIO (ObjectM o m) |
setFieldByRef :: MonadBackend im => ObjectRef -> Identifier -> Value -> Execution im ValueSource
getFieldByRef :: MonadBackend im => ObjectRef -> Identifier -> Execution im ValueSource
callMethodByRef :: MonadBackend im => ObjectRef -> Identifier -> [Value] -> Execution im ValueSource
recvEventByRef :: MonadBackend im => WidgetRef -> Event -> Execution im ()Source
compose :: MonadSindre im m => WidgetRef -> m im SpaceNeedSource
Constructors
| SindreEnv | |
Instances
| MonadState (SindreEnv m) (Sindre m) |
Instances
| MonadBackend im => MonadSindre im Execution | |
| Monad (Execution m) | |
| Functor (Execution m) | |
| Applicative (Execution m) | |
| MonadCont (Execution m) | |
| MonadReader (ExecutionEnv m) (Execution m) |
returnHere :: MonadBackend m => Execution m Value -> Execution m ValueSource
doNext :: MonadBackend m => Execution m ()Source
doBreak :: MonadBackend m => Execution m ()Source
doCont :: MonadBackend m => Execution m ()Source
enterScope :: MonadBackend m => [Value] -> Execution m a -> Execution m aSource
lexicalVal :: MonadBackend m => Key -> Execution m ValueSource
setLexical :: MonadBackend m => Key -> Value -> Execution m ()Source
eventLoop :: MonadBackend m => EventHandler m -> Sindre m ()Source
type EventHandler m = Event -> Execution m ()Source