reflex-sdl2-0.2.0.0: SDL2 and reflex FRP

Safe HaskellNone
LanguageHaskell2010

Reflex.SDL2

Contents

Description

This module contains a minimum yet convenient API needed to get started writing reflex apps with sdl2.

For an example see app/Main.hs

Synopsis

Running an app

host Source #

Arguments

:: r

A user data value of type r. Use getUserData to access this value within your app network.

-> ConcreteReflexSDL2 r ()

A concrete reflex-sdl2 network to run.

-> IO void 

Host a reflex-sdl2 app. This function is your application's main loop and will not terminate.

The reflex-sdl2 base type and constraints

type ReflexSDL2 r t m = (Reflex t, MonadHold t m, MonadSample t m, MonadAdjust t m, PostBuild t m, PerformEvent t m, MonadFix m, MonadIO m, MonadIO (Performable m), MonadReader (SystemEvents r t) m) Source #

A collection of constraints that represent the default reflex-sdl2 network.

data ReflexSDL2T r t m a Source #

Provides a basic implementation of ReflexSDL2 constraints.

Instances

(ReflexHost t, PerformEvent t m) => PerformEvent t (ReflexSDL2T r t m) Source #

ReflexSDL2T is an instance of PerformEvent.

Associated Types

type Performable (ReflexSDL2T r t m :: * -> *) :: * -> * #

Methods

performEvent :: Event t (Performable (ReflexSDL2T r t m) a) -> ReflexSDL2T r t m (Event t a) #

performEvent_ :: Event t (Performable (ReflexSDL2T r t m) ()) -> ReflexSDL2T r t m () #

(Reflex t, PostBuild t m, ReflexHost t, Monad m) => PostBuild t (ReflexSDL2T r t m) Source #

ReflexSDL2T is an instance of PostBuild.

Methods

getPostBuild :: ReflexSDL2T r t m (Event t ()) #

(ReflexHost t, Applicative m, Monad m, MonadSample t m) => MonadSample t (ReflexSDL2T r t m) Source #

ReflexSDL2T is an instance of MonadHold.

Methods

sample :: Behavior t a -> ReflexSDL2T r t m a #

(ReflexHost t, MonadHold t m) => MonadHold t (ReflexSDL2T r t m) Source #

ReflexSDL2T is an instance of MonadHold.

Methods

hold :: a -> Event t a -> ReflexSDL2T r t m (Behavior t a) #

holdDyn :: a -> Event t a -> ReflexSDL2T r t m (Dynamic t a) #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> ReflexSDL2T r t m (Incremental t p) #

buildDynamic :: PullM t a -> Event t a -> ReflexSDL2T r t m (Dynamic t a) #

(Reflex t, ReflexHost t, MonadAdjust t m, Monad m) => MonadAdjust t (ReflexSDL2T r t m) Source #

ReflexSDL2T is an instance of MonadAdjust.

Methods

runWithReplace :: ReflexSDL2T r t m a -> Event t (ReflexSDL2T r t m b) -> ReflexSDL2T r t m (a, Event t b) #

traverseDMapWithKeyWithAdjust :: GCompare * k => (forall a. k a -> v a -> ReflexSDL2T r t m (v' a)) -> DMap * k v -> Event t (PatchDMap k v) -> ReflexSDL2T r t m (DMap * k v', Event t (PatchDMap k v')) #

traverseDMapWithKeyWithAdjustWithMove :: GCompare * k => (forall a. k a -> v a -> ReflexSDL2T r t m (v' a)) -> DMap * k v -> Event t (PatchDMapWithMove k v) -> ReflexSDL2T r t m (DMap * k v', Event t (PatchDMapWithMove k v')) #

ReflexHost t => MonadTrans (ReflexSDL2T r t) Source # 

Methods

lift :: Monad m => m a -> ReflexSDL2T r t m a #

(ReflexHost t, Monad m) => MonadReader (SystemEvents r t) (ReflexSDL2T r t m) Source # 

Methods

ask :: ReflexSDL2T r t m (SystemEvents r t) #

local :: (SystemEvents r t -> SystemEvents r t) -> ReflexSDL2T r t m a -> ReflexSDL2T r t m a #

reader :: (SystemEvents r t -> a) -> ReflexSDL2T r t m a #

(ReflexHost t, Monad m) => Monad (ReflexSDL2T r t m) Source # 

Methods

(>>=) :: ReflexSDL2T r t m a -> (a -> ReflexSDL2T r t m b) -> ReflexSDL2T r t m b #

(>>) :: ReflexSDL2T r t m a -> ReflexSDL2T r t m b -> ReflexSDL2T r t m b #

return :: a -> ReflexSDL2T r t m a #

fail :: String -> ReflexSDL2T r t m a #

(ReflexHost t, Functor m) => Functor (ReflexSDL2T r t m) Source # 

Methods

fmap :: (a -> b) -> ReflexSDL2T r t m a -> ReflexSDL2T r t m b #

(<$) :: a -> ReflexSDL2T r t m b -> ReflexSDL2T r t m a #

(ReflexHost t, MonadFix m) => MonadFix (ReflexSDL2T r t m) Source # 

Methods

mfix :: (a -> ReflexSDL2T r t m a) -> ReflexSDL2T r t m a #

(ReflexHost t, Applicative m) => Applicative (ReflexSDL2T r t m) Source # 

Methods

pure :: a -> ReflexSDL2T r t m a #

(<*>) :: ReflexSDL2T r t m (a -> b) -> ReflexSDL2T r t m a -> ReflexSDL2T r t m b #

(*>) :: ReflexSDL2T r t m a -> ReflexSDL2T r t m b -> ReflexSDL2T r t m b #

(<*) :: ReflexSDL2T r t m a -> ReflexSDL2T r t m b -> ReflexSDL2T r t m a #

(ReflexHost t, MonadIO m) => MonadIO (ReflexSDL2T r t m) Source # 

Methods

liftIO :: IO a -> ReflexSDL2T r t m a #

(ReflexHost t, MonadException m) => MonadException (ReflexSDL2T r t m) Source # 

Methods

throw :: Exception e => e -> ReflexSDL2T r t m a #

catch :: Exception e => ReflexSDL2T r t m a -> (e -> ReflexSDL2T r t m a) -> ReflexSDL2T r t m a #

finally :: ReflexSDL2T r t m a -> ReflexSDL2T r t m b -> ReflexSDL2T r t m a #

type Performable (ReflexSDL2T r t m) Source # 

type ConcreteReflexSDL2 r = ReflexSDL2T r Spider (PostBuildT Spider (PerformEventT Spider (SpiderHost Global))) Source #

The concrete/specialized type used to run reflex-sdl2 apps.

Higher order switching

holdView :: ReflexSDL2 r t m => m a -> Event t (m a) -> m (Dynamic t a) Source #

Run a placeholder network until the given Event fires, then replace it with the network of the Events value. This process is repeated each time the Event fires a new network. Returns a Dynamic of the inner network's result that updates any time the Event fires.

dynView :: ReflexSDL2 r t m => Dynamic t (m a) -> m (Event t a) Source #

Run a Dynamically changing network, replacing the current one with the new one every time the Dynamic updates. Returns an Event of the inner network's result value that fires every time the Dynamic changes.

Time delta events

getDeltaTickEvent :: ReflexSDL2 r t m => m (Event t Word32) Source #

Returns an event that fires each frame with the number of milliseconds since the last frame. Be aware that subscribing to this Event (by using it in a monadic action) will result in your app running sdl2's event loop every frame.

performEventDelta :: ReflexSDL2 r t m => Event t a -> m (Event t Word32) Source #

Populate the event value with the time in milliseconds since the last time the event fired.

*WithEventCode events

The *WithEventCode flavor of events use sdl2's user events system. Each function evaluates on the current thread, returning an Event that will fire on the main thread and can be used to drive GL updates. It uses sdl2's user event machinery, requiring a special single use event code to identify the event on the other side of sdl2's FFI. This is a great use case for a Fresh effect in your app.

getRecurringTimerEventWithEventCode Source #

Arguments

:: ReflexSDL2 r t m 
=> Int32

Single use event code.

-> Int

Number of milliseconds.

-> m (Event t ()) 

Retrieves an event that fires every n milliseconds.

getAsyncEventWithEventCode :: (ReflexSDL2 r t m, Storable a) => Int32 -> IO a -> m (Event t a) Source #

Executes the given IO action in a separate thread asynchronously and returns an Event that fires on the main thread with the result value of that action. This uses sdl2's user events system, which requires that the action result have an instance of Storable.

Your a type gets marshalled to C FFI and back, hence the Storable requirement.

delayEventWithEventCode :: (ReflexSDL2 r t m, Storable a) => Int32 -> Int -> Event t a -> m (Event t a) Source #

Delays the given event by the given number of milliseconds.

User data

userLocal :: MonadReader (SystemEvents r t) m => (r -> r) -> m a -> m a Source #

Run a (Reader SystemEvents r t) computation with a modified sysUserData r.

Debugging

putDebugLnE Source #

Arguments

:: (PerformEvent t m, Reflex t, MonadIO (Performable m)) 
=> Event t a

The Event to trigger the print.

-> (a -> String)

A function to show the Events value.

-> m () 

Like putStrLn, but for Events.

SDL2 events

getQuitEvent :: ReflexSDL2 r t m => m (Event t ()) Source #

getUserData :: ReflexSDL2 r t m => m r Source #

Re-exports

module Reflex

module SDL

class Monad m => MonadIO m where #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Minimal complete definition

liftIO

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances

MonadIO IO 

Methods

liftIO :: IO a -> IO a #

MonadIO m => MonadIO (ExceptionT m) 

Methods

liftIO :: IO a -> ExceptionT m a #

MonadIO m => MonadIO (CatchT m) 

Methods

liftIO :: IO a -> CatchT m a #

MonadIO m => MonadIO (IterT m) 

Methods

liftIO :: IO a -> IterT m a #

MonadIO m => MonadIO (ListT m) 

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (MaybeT m) 

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO (BehaviorM x) 

Methods

liftIO :: IO a -> BehaviorM x a #

MonadIO (EventM x) 

Methods

liftIO :: IO a -> EventM x a #

MonadIO (ComputeM x) 

Methods

liftIO :: IO a -> ComputeM x a #

MonadIO (SpiderPullM x) 

Methods

liftIO :: IO a -> SpiderPullM x a #

MonadIO (SpiderPushM x) 

Methods

liftIO :: IO a -> SpiderPushM x a #

MonadIO (SpiderHost x) 

Methods

liftIO :: IO a -> SpiderHost x a #

MonadIO (SpiderHostFrame x) 

Methods

liftIO :: IO a -> SpiderHostFrame x a #

MonadIO m => MonadIO (IdentityT * m) 

Methods

liftIO :: IO a -> IdentityT * m a #

(Functor f, MonadIO m) => MonadIO (FreeT f m) 

Methods

liftIO :: IO a -> FreeT f m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 

Methods

liftIO :: IO a -> ErrorT e m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (ExceptT e m) 

Methods

liftIO :: IO a -> ExceptT e m a #

MonadIO m => MonadIO (StateT s m) 

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (TriggerEventT t m) 

Methods

liftIO :: IO a -> TriggerEventT t m a #

MonadIO m => MonadIO (PostBuildT t m) 

Methods

liftIO :: IO a -> PostBuildT t m a #

MonadIO m => MonadIO (ReaderT * r m) 

Methods

liftIO :: IO a -> ReaderT * r m a #

MonadIO m => MonadIO (ContT * r m) 

Methods

liftIO :: IO a -> ContT * r m a #

(ReflexHost t, MonadIO (HostFrame t)) => MonadIO (PerformEventT k t m) 

Methods

liftIO :: IO a -> PerformEventT k t m a #

MonadIO m => MonadIO (QueryT t q m) 

Methods

liftIO :: IO a -> QueryT t q m a #

MonadIO m => MonadIO (EventWriterT t w m) 

Methods

liftIO :: IO a -> EventWriterT t w m a #

MonadIO m => MonadIO (DynamicWriterT t w m) 

Methods

liftIO :: IO a -> DynamicWriterT t w m a #

(ReflexHost t, MonadIO m) => MonadIO (ReflexSDL2T r t m) # 

Methods

liftIO :: IO a -> ReflexSDL2T r t m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 

Methods

liftIO :: IO a -> RWST r w s m a #

MonadIO m => MonadIO (RequesterT t request response m) 

Methods

liftIO :: IO a -> RequesterT t request response m a #

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.