Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Wrapper to write gloss
applications in Rhine, using concurrency.
Synopsis
- data GlossConcT m a
- paintIO :: MonadIO m => Picture -> GlossConcT m ()
- clearIO :: MonadIO m => GlossConcT m ()
- paintAllIO :: MonadIO m => Picture -> GlossConcT m ()
- data GlossEventClockIO = GlossEventClockIO
- data GlossSimClockIO = GlossSimClockIO
- launchInGlossThread :: MonadIO m => GlossSettings -> GlossConcT m a -> m a
- launchGlossThread :: MonadIO m => GlossSettings -> m GlossEnv
- flowGlossIO :: (MonadIO m, Clock (GlossConcT m) cl, GetClockProxy cl, Time cl ~ Time (In cl), Time cl ~ Time (Out cl)) => GlossSettings -> Rhine (GlossConcT m) cl () () -> m ()
- runGlossEnvClock :: GlossEnv -> cl -> RunGlossEnvClock m cl
- type RunGlossEnvClock m cl = HoistClock (GlossConcT m) m cl
Documentation
data GlossConcT m a Source #
Wraps the concurrent variables needed for communication with the gloss
backend.
Instances
clearIO :: MonadIO m => GlossConcT m () Source #
Clear the canvas.
paintAllIO :: MonadIO m => Picture -> GlossConcT m () Source #
Clear the canvas and then paint.
data GlossEventClockIO Source #
Concurrently block on gloss
events.
Instances
GetClockProxy GlossEventClockIO Source # | |
Defined in FRP.Rhine.Gloss.IO | |
MonadIO m => Clock (GlossConcT m) GlossEventClockIO Source # | |
Defined in FRP.Rhine.Gloss.IO type Time GlossEventClockIO # type Tag GlossEventClockIO # | |
type Tag GlossEventClockIO Source # | |
Defined in FRP.Rhine.Gloss.IO | |
type Time GlossEventClockIO Source # | |
Defined in FRP.Rhine.Gloss.IO |
data GlossSimClockIO Source #
Concurrently block on gloss
simulation ticks.
Instances
GetClockProxy GlossSimClockIO Source # | |
Defined in FRP.Rhine.Gloss.IO | |
MonadIO m => Clock (GlossConcT m) GlossSimClockIO Source # | |
Defined in FRP.Rhine.Gloss.IO type Time GlossSimClockIO # type Tag GlossSimClockIO # initClock :: GlossSimClockIO -> RunningClockInit (GlossConcT m) (Time GlossSimClockIO) (Tag GlossSimClockIO) # | |
type Tag GlossSimClockIO Source # | |
Defined in FRP.Rhine.Gloss.IO | |
type Time GlossSimClockIO Source # | |
Defined in FRP.Rhine.Gloss.IO |
launchInGlossThread :: MonadIO m => GlossSettings -> GlossConcT m a -> m a Source #
Apply this to supply the GlossConcT
effect.
Creates a new thread in which gloss
is run,
and feeds the clocks GlossEventClockIO
and GlossSimClockIO
.
Usually, this function is applied to the result of flow
,
so you can handle all occurring effects as needed.
If you only use gloss
in your whole signal network,
you can use flowGlossIO
instead.
launchGlossThread :: MonadIO m => GlossSettings -> m GlossEnv Source #
Apply this to supply the GlossConcT
effect.
Creates a new thread in which gloss
is run,
and feeds the clocks GlossEventClockIO
and GlossSimClockIO
.
Usually, this function is applied to the result of flow
,
so you can handle all occurring effects as needed.
If you only use gloss
in your whole signal network,
you can use flowGlossIO
instead.
flowGlossIO :: (MonadIO m, Clock (GlossConcT m) cl, GetClockProxy cl, Time cl ~ Time (In cl), Time cl ~ Time (Out cl)) => GlossSettings -> Rhine (GlossConcT m) cl () () -> m () Source #
Run a Rhine
in the GlossConcT
monad by launching a separate thread for the gloss
backend,
and reactimate in the foreground.
runGlossEnvClock :: GlossEnv -> cl -> RunGlossEnvClock m cl Source #
Apply to a gloss clock to remove a GlossConcT
layer.
You will have to have initialized a GlossEnv
, for example by calling launchGlossThread
.
type RunGlossEnvClock m cl = HoistClock (GlossConcT m) m cl Source #
Apply this wrapper to your clock type cl
in order to escape the GlossConcT
transformer.
The resulting clock will be in m
, not 'GlossConcT m' anymore.
Typically, m
will have the MonadIO
constraint.