License | MIT-style (see LICENSE) |
---|---|
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Definitions for the Sindre runtime environment.
Synopsis
- data Sindre m a
- execSindre :: MonadBackend m => SindreEnv m -> Sindre m a -> m ExitCode
- quitSindre :: MonadBackend m => ExitCode -> Sindre m ()
- class (MonadBackend im, MonadFail (m im), MonadFail 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, MonadFail 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 :: (MonadFail im, 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 Source # | |
Defined in Sindre.Runtime | |
MonadBackend im => MonadSindre im Sindre Source # | |
Monad (Sindre m) Source # | |
Functor (Sindre m) Source # | |
MonadFail m => MonadFail (Sindre m) Source # | |
Defined in Sindre.Runtime | |
Applicative (Sindre m) Source # | |
MonadIO m => MonadIO (Sindre m) Source # | |
Defined in Sindre.Runtime | |
MonadCont (Sindre m) Source # | |
MonadState (SindreEnv m) (Sindre m) Source # | |
Semigroup (Sindre m ()) Source # | |
Monoid (Sindre m ()) Source # | |
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.
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
MonadBackend im => MonadSindre im Execution Source # | |
MonadBackend im => MonadSindre im Sindre Source # | |
MonadBackend im => MonadSindre im ConstructorM Source # | |
Defined in Sindre.Compiler sindre :: Sindre im a -> ConstructorM im a Source # back :: im a -> ConstructorM im a Source # | |
MonadBackend im => MonadSindre im (ObjectM o) Source # | |
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, MonadFail m, Mold (RootPosition m)) => MonadBackend m where Source #
A monad that can be used as the layer beneath Sindre
.
redrawRoot :: Sindre m () Source #
redrawRegion :: [Rectangle] -> Sindre m () Source #
getBackEvent :: Sindre m (Maybe Event) Source #
waitForBackEvent :: Sindre m Event Source #
Instances
MonadBackend SindreX11M Source # | |
Defined in Sindre.X11 type BackEvent SindreX11M Source # type RootPosition SindreX11M Source # redrawRoot :: Sindre SindreX11M () Source # redrawRegion :: [Rectangle] -> Sindre SindreX11M () Source # getBackEvent :: Sindre SindreX11M (Maybe Event) Source # waitForBackEvent :: Sindre SindreX11M Event Source # printVal :: String -> SindreX11M () Source # |
newObject :: s -> Map Identifier (Method s im) -> [Field s im] -> (Event -> ObjectM s im ()) -> NewObject im Source #
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 #
instWidget :: NewWidget im -> Constraints -> DataSlot im Source #
instObject :: NewObject im -> 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 Field
s 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.
ReadWriteField Identifier (ObjectM s im v) (v -> ObjectM s im ()) | |
ReadOnlyField Identifier (ObjectM s im v) |
fieldName :: FieldDesc s im v -> Identifier 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.
An opaque notion of a field. These are for internal use in the Sindre runtime.
Instances
MonadBackend im => MonadSindre im (ObjectM o) Source # | |
MonadState s (ObjectM s im) Source # | |
MonadReader ObjectRef (ObjectM s im) Source # | |
Monad (ObjectM s im) Source # | |
Functor (ObjectM s im) Source # | |
MonadFail im => MonadFail (ObjectM s im) Source # | |
Defined in Sindre.Runtime | |
Applicative (ObjectM s im) Source # | |
Defined in Sindre.Runtime | |
(MonadIO m, MonadBackend m) => MonadIO (ObjectM o m) Source # | |
Defined in Sindre.Runtime |
setFieldByRef :: MonadBackend im => ObjectRef -> Identifier -> Value -> Execution im Value Source #
getFieldByRef :: MonadBackend im => ObjectRef -> Identifier -> Execution im Value Source #
callMethodByRef :: MonadBackend im => ObjectRef -> Identifier -> [Value] -> Execution im Value Source #
recvEventByRef :: MonadBackend im => WidgetRef -> Event -> Execution im () Source #
returnHere :: MonadBackend m => Execution m Value -> Execution m Value Source #
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 a Source #
lexicalVal :: MonadBackend m => Key -> Execution m Value Source #
setLexical :: MonadBackend m => Key -> Value -> Execution m () Source #
eventLoop :: MonadBackend m => EventHandler m -> Sindre m () Source #
type EventHandler m = Event -> Execution m () Source #