rhine-gloss-1.5: Gloss backend for Rhine
Safe HaskellSafe-Inferred
LanguageHaskell2010

FRP.Rhine.Gloss.IO

Description

Wrapper to write gloss applications in Rhine, using concurrency.

Synopsis

Documentation

data GlossEnv Source #

Concurrent variables needed to communicate with the gloss backend.

newtype GlossConcT m a Source #

Effects in the gloss backend

  • Wraps the concurrent variables needed for communication with the gloss backend.
  • Adds the FreeAsyncT concurrency layer for fairer scheduling

Constructors

GlossConcT 

Instances

Instances details
MonadTrans GlossConcT Source # 
Instance details

Defined in FRP.Rhine.Gloss.IO

Methods

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

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

Defined in FRP.Rhine.Gloss.IO

Methods

liftIO :: IO a -> GlossConcT m a #

Monad m => Applicative (GlossConcT m) Source # 
Instance details

Defined in FRP.Rhine.Gloss.IO

Methods

pure :: a -> GlossConcT m a #

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

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

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

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

Monad m => Functor (GlossConcT m) Source # 
Instance details

Defined in FRP.Rhine.Gloss.IO

Methods

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

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

Monad m => Monad (GlossConcT m) Source # 
Instance details

Defined in FRP.Rhine.Gloss.IO

Methods

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

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

return :: a -> GlossConcT m a #

MonadIO m => MonadSchedule (GlossConcT m) Source #

Disregards scheduling capabilities of m, as it uses FreeAsync.

Instance details

Defined in FRP.Rhine.Gloss.IO

Methods

schedule :: NonEmpty (GlossConcT m a) -> GlossConcT m (NonEmpty a, [GlossConcT m a]) #

MonadIO m => Clock (GlossConcT m) GlossEventClockIO Source # 
Instance details

Defined in FRP.Rhine.Gloss.IO

Associated Types

type Time GlossEventClockIO #

type Tag GlossEventClockIO #

MonadIO m => Clock (GlossConcT m) GlossSimClockIO Source # 
Instance details

Defined in FRP.Rhine.Gloss.IO

Associated Types

type Time GlossSimClockIO #

type Tag GlossSimClockIO #

type GlossConc = GlossConcT IO Source #

When gloss is the only effect you are using, use this monad to simplify your type signatures.

runGlossConcT :: MonadIO m => GlossConcT m a -> GlossEnv -> m a Source #

Remove the GlossConcT transformer by explicitly providing an environment.

paintIO :: MonadIO m => Picture -> GlossConcT m () Source #

Add a picture to the canvas.

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.

Caution: Currently, you should only add one such clock in a Rhine. If you add several GlossEventClockIO, only one will be chosen at random and receive the event. See https://github.com/turion/rhine/issues/330.

Constructors

GlossEventClockIO 

data GlossSimClockIO Source #

Concurrently block on gloss simulation ticks.

Caution: Currently, you should only add one such clock in a Rhine. If you add several GlossSimClockIO, only one will be chosen at random and receive the event. See https://github.com/turion/rhine/issues/330.

Constructors

GlossSimClockIO 

Instances

Instances details
GetClockProxy GlossSimClockIO Source # 
Instance details

Defined in FRP.Rhine.Gloss.IO

MonadIO m => Clock (GlossConcT m) GlossSimClockIO Source # 
Instance details

Defined in FRP.Rhine.Gloss.IO

Associated Types

type Time GlossSimClockIO #

type Tag GlossSimClockIO #

type Tag GlossSimClockIO Source # 
Instance details

Defined in FRP.Rhine.Gloss.IO

type Time GlossSimClockIO Source # 
Instance details

Defined in FRP.Rhine.Gloss.IO

makeGlossEnv :: MonadIO m => m GlossEnv Source #

Create the concurrent variables to communicate with the gloss backend.

You will usually not need this function, have a look at launchInGlossThread and flowGlossIO instead.

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 #

Helper function for launchInGlossThread.

Creates concurrent variables and launches the gloss backend in a separate thread.

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 :: MonadIO m => 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.

type GlossClockUTC m cl = UTCClock (GlossConcT m) cl Source #

Rescale a gloss clock like GlossSimClockIO or GlossEventClockIO to UTCTime.

This is needed for compatibility with other realtime clocks like Millisecond.

glossClockUTC :: (MonadIO m, Real (Time cl)) => cl -> GlossClockUTC m cl Source #

Rescale a gloss clock like GlossSimClockIO or GlossEventClockIO to UTCTime.

Uses addUTC. For other strategies to rescale a gloss clock to UTCTime, see FRP.Rhine.Clock.Realtime.

type GlossConcTClock m = HoistClock IO (GlossConcT m) Source #

Lift a MonadIO clock to GlossConcT.

You should use this instead of IOClock, otherwise scheduling will probably not work. (This is because GlossConcT uses FreeAsyncT, but liftIO is not asynchronous.)

glossConcTClock :: MonadIO m => cl -> GlossConcTClock m cl Source #

A MonadIO clock lifted to GlossConcT.

glossConcClock :: cl -> GlossConcClock cl Source #

An IO clock lifted to GlossConc.