reflex-sdl2-0.3.0.0: SDL2 and reflex FRP

Safe HaskellNone
LanguageHaskell2010

Reflex.SDL2.Base

Synopsis

Documentation

newtype ReflexSDL2T t (m :: * -> *) a Source #

Provides an implementation of the HasSDL2Events type class.

Constructors

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

ReflexSDL2T is an instance of PerformEvent.

Instance details

Defined in Reflex.SDL2.Base

Associated Types

type Performable (ReflexSDL2T t m) :: Type -> Type #

Methods

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

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

(ReflexHost t, TriggerEvent t m) => TriggerEvent t (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

newTriggerEvent :: ReflexSDL2T t m (Event t a, a -> IO ()) #

newTriggerEventWithOnComplete :: ReflexSDL2T t m (Event t a, a -> IO () -> IO ()) #

newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ())) -> ReflexSDL2T t m (Event t a) #

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

ReflexSDL2T is an instance of PostBuild.

Instance details

Defined in Reflex.SDL2.Base

Methods

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

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

ReflexSDL2T is an instance of Adjustable.

Instance details

Defined in Reflex.SDL2.Base

Methods

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

traverseIntMapWithKeyWithAdjust :: (Key -> v -> ReflexSDL2T t m v') -> IntMap v -> Event t (PatchIntMap v) -> ReflexSDL2T t m (IntMap v', Event t (PatchIntMap v')) #

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

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

(ReflexHost t, Monad m) => HasSDL2Events t (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

getTicksEvent :: ReflexSDL2T t m (Event t Word32) Source #

getAnySDLEvent :: ReflexSDL2T t m (Event t EventPayload) Source #

getWindowShownEvent :: ReflexSDL2T t m (Event t WindowShownEventData) Source #

getWindowHiddenEvent :: ReflexSDL2T t m (Event t WindowHiddenEventData) Source #

getWindowExposedEvent :: ReflexSDL2T t m (Event t WindowExposedEventData) Source #

getWindowMovedEvent :: ReflexSDL2T t m (Event t WindowMovedEventData) Source #

getWindowResizedEvent :: ReflexSDL2T t m (Event t WindowResizedEventData) Source #

getWindowSizeChangedEvent :: ReflexSDL2T t m (Event t WindowSizeChangedEventData) Source #

getWindowMinimizedEvent :: ReflexSDL2T t m (Event t WindowMinimizedEventData) Source #

getWindowMaximizedEvent :: ReflexSDL2T t m (Event t WindowMaximizedEventData) Source #

getWindowRestoredEvent :: ReflexSDL2T t m (Event t WindowRestoredEventData) Source #

getWindowGainedMouseFocusEvent :: ReflexSDL2T t m (Event t WindowGainedMouseFocusEventData) Source #

getWindowLostMouseFocusEvent :: ReflexSDL2T t m (Event t WindowLostMouseFocusEventData) Source #

getWindowGainedKeyboardFocusEvent :: ReflexSDL2T t m (Event t WindowGainedKeyboardFocusEventData) Source #

getWindowLostKeyboardFocusEvent :: ReflexSDL2T t m (Event t WindowLostKeyboardFocusEventData) Source #

getWindowClosedEvent :: ReflexSDL2T t m (Event t WindowClosedEventData) Source #

getKeyboardEvent :: ReflexSDL2T t m (Event t KeyboardEventData) Source #

getTextEditingEvent :: ReflexSDL2T t m (Event t TextEditingEventData) Source #

getTextInputEvent :: ReflexSDL2T t m (Event t TextInputEventData) Source #

getKeymapChangedEvent :: ReflexSDL2T t m (Event t ()) Source #

getMouseMotionEvent :: ReflexSDL2T t m (Event t MouseMotionEventData) Source #

getMouseButtonEvent :: ReflexSDL2T t m (Event t MouseButtonEventData) Source #

getMouseWheelEvent :: ReflexSDL2T t m (Event t MouseWheelEventData) Source #

getJoyAxisEvent :: ReflexSDL2T t m (Event t JoyAxisEventData) Source #

getJoyBallEvent :: ReflexSDL2T t m (Event t JoyBallEventData) Source #

getJoyHatEvent :: ReflexSDL2T t m (Event t JoyHatEventData) Source #

getJoyButtonEvent :: ReflexSDL2T t m (Event t JoyButtonEventData) Source #

getJoyDeviceEvent :: ReflexSDL2T t m (Event t JoyDeviceEventData) Source #

getControllerAxisEvent :: ReflexSDL2T t m (Event t ControllerAxisEventData) Source #

getControllerButtonEvent :: ReflexSDL2T t m (Event t ControllerButtonEventData) Source #

getControllerDeviceEvent :: ReflexSDL2T t m (Event t ControllerDeviceEventData) Source #

getAudioDeviceEvent :: ReflexSDL2T t m (Event t AudioDeviceEventData) Source #

getQuitEvent :: ReflexSDL2T t m (Event t ()) Source #

getUserEvent :: ReflexSDL2T t m (Event t UserEventData) Source #

getSysWMEvent :: ReflexSDL2T t m (Event t SysWMEventData) Source #

getTouchFingerEvent :: ReflexSDL2T t m (Event t TouchFingerEventData) Source #

getMultiGestureEvent :: ReflexSDL2T t m (Event t MultiGestureEventData) Source #

getDollarGestureEvent :: ReflexSDL2T t m (Event t DollarGestureEventData) Source #

getDropEvent :: ReflexSDL2T t m (Event t DropEventData) Source #

getClipboardUpdateEvent :: ReflexSDL2T t m (Event t ()) Source #

getUnknownEvent :: ReflexSDL2T t m (Event t UnknownEventData) Source #

getQuitVar :: ReflexSDL2T t m (MVar ()) Source #

ReflexHost t => MonadTrans (ReflexSDL2T t) Source # 
Instance details

Defined in Reflex.SDL2.Base

Methods

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

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

ReflexSDL2T is an instance of MonadHold.

Instance details

Defined in Reflex.SDL2.Base

Methods

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

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

ReflexSDL2T is an instance of MonadHold.

Instance details

Defined in Reflex.SDL2.Base

Methods

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

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

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

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

headE :: Event t a -> ReflexSDL2T t m (Event t a) #

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

Defined in Reflex.SDL2.Base

Methods

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

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

return :: a -> ReflexSDL2T t m a #

fail :: String -> ReflexSDL2T t m a #

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

Defined in Reflex.SDL2.Base

Methods

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

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

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

Defined in Reflex.SDL2.Base

Methods

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

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

Defined in Reflex.SDL2.Base

Methods

pure :: a -> ReflexSDL2T t m a #

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

liftA2 :: (a -> b -> c) -> ReflexSDL2T t m a -> ReflexSDL2T t m b -> ReflexSDL2T t m c #

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

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

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

Defined in Reflex.SDL2.Base

Methods

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

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

Defined in Reflex.SDL2.Base

Methods

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

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

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

type Performable (ReflexSDL2T t m) Source # 
Instance details

Defined in Reflex.SDL2.Base