netwire-input-glfw-0.0.12: GLFW instance of netwire-input
Copyright(c) Pavel Krajcevski 2018
LicenseMIT
MaintainerKrajcevski@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageHaskell2010

FRP.Netwire.Input.GLFW

Description

This module contains data types with instances needed to create wires that can be used with the netwire-input combinators. In particular, this package implements GLFWInputT which has instances of MonadKeyboard and MonadMouse

Synopsis

GLFW Input

Basic Input Monad

type GLFWInput = GLFWInputT Identity Source #

The GLFWInput monad is simply the GLFWInputT transformer around the identity monad.

runGLFWInput :: GLFWInput a -> GLFWInputState -> (a, GLFWInputState) Source #

Runs the GLFWInput computation with a current input snapshot and returns the potentially modified input.

Monad Transformer

data GLFWInputT m a Source #

The GLFWInputT monad transformer is simply a state monad transformer using GLFWInputState

Instances

Instances details
MonadTrans GLFWInputT Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

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

MonadError e m => MonadError e (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

throwError :: e -> GLFWInputT m a #

catchError :: GLFWInputT m a -> (e -> GLFWInputT m a) -> GLFWInputT m a #

MonadReader r m => MonadReader r (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

ask :: GLFWInputT m r #

local :: (r -> r) -> GLFWInputT m a -> GLFWInputT m a #

reader :: (r -> a) -> GLFWInputT m a #

MonadState s m => MonadState s (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

get :: GLFWInputT m s #

put :: s -> GLFWInputT m () #

state :: (s -> (a, s)) -> GLFWInputT m a #

MonadWriter w m => MonadWriter w (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

writer :: (a, w) -> GLFWInputT m a #

tell :: w -> GLFWInputT m () #

listen :: GLFWInputT m a -> GLFWInputT m (a, w) #

pass :: GLFWInputT m (a, w -> w) -> GLFWInputT m a #

MonadFix m => MonadFix (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

mfix :: (a -> GLFWInputT m a) -> GLFWInputT m a #

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

Defined in FRP.Netwire.Input.GLFW

Methods

liftIO :: IO a -> GLFWInputT m a #

MonadPlus m => Alternative (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

empty :: GLFWInputT m a #

(<|>) :: GLFWInputT m a -> GLFWInputT m a -> GLFWInputT m a #

some :: GLFWInputT m a -> GLFWInputT m [a] #

many :: GLFWInputT m a -> GLFWInputT m [a] #

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

Defined in FRP.Netwire.Input.GLFW

Methods

pure :: a -> GLFWInputT m a #

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

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

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

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

Functor m => Functor (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

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

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

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

Defined in FRP.Netwire.Input.GLFW

Methods

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

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

return :: a -> GLFWInputT m a #

MonadPlus m => MonadPlus (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

mzero :: GLFWInputT m a #

mplus :: GLFWInputT m a -> GLFWInputT m a -> GLFWInputT m a #

MonadCont m => MonadCont (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

callCC :: ((a -> GLFWInputT m b) -> GLFWInputT m a) -> GLFWInputT m a #

Monad m => MonadGLFWInput (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

runGLFWInputT :: GLFWInputT m a -> GLFWInputState -> m (a, GLFWInputState) Source #

To execute a computation with the current input snapshot, we need to give supply the current GLFWInputState. This comes from the GLFWInputControl associated with the given window.

Typeclass

class Monad m => MonadGLFWInput m where Source #

Describes a monad that provides stateful access to a GLFWInputState. By being able to modify the state, the context that satisfies this typeclass can decide to debounce or "take ownership" of the button presses at a specific point of the computation. This should be done via the MonadKey and MonadMouse instances.

Methods

getGLFWInput :: m GLFWInputState Source #

Retrieves the current input state

putGLFWInput :: GLFWInputState -> m () Source #

Places a modified input state back into the context. This should probably not be called directly.

Instances

Instances details
Monad m => MonadGLFWInput (GLFWInputT m) Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

State Types

data GLFWInputControl Source #

This is an STM variable that holds the current input state. It cannot be manipulated directly, but it is updated by GLFW each time pollGLFW is called.

data GLFWInputState Source #

The GLFW input state is a record that keeps track of which buttons and keys are currently pressed. Because GLFW works with callbacks, a call to pollEvents must be made in order to process any of the events. At this time, all of the appropriate callbacks are fired in order of the events received, and this record is updated to reflect the most recent input state.

Instances

Instances details
Generic GLFWInputState Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Associated Types

type Rep GLFWInputState :: Type -> Type #

Show GLFWInputState Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

NFData GLFWInputState Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

Methods

rnf :: GLFWInputState -> () #

type Rep GLFWInputState Source # 
Instance details

Defined in FRP.Netwire.Input.GLFW

emptyGLFWState :: GLFWInputState Source #

Returns the empty GLFW state. In this state, no buttons are pressed, and the mouse and scroll positions are set to zero. The cursor is also placed in the disabled state.

getInput :: GLFWInputControl -> IO GLFWInputState Source #

Returns a current snapshot of the input

mkInputControl :: Window -> IO GLFWInputControl Source #

Creates and returns an STM variable for the window that holds all of the most recent input state information

pollGLFW :: GLFWInputState -> GLFWInputControl -> IO GLFWInputState Source #

Allows GLFW to interact with the windowing system to update the current state. The old state must be passed in order to properly reset certain properties such as the scroll wheel. The returned input state is identical to a subsequent call to getInput right after a call to pollEvents

Orphan instances

Key Key Source # 
Instance details

MouseButton MouseButton Source # 
Instance details

MonadGLFWInput m => MonadKeyboard Key m Source # 
Instance details

Methods

keyIsPressed :: Key -> m Bool #

releaseKey :: Key -> m () #

MonadGLFWInput m => MonadMouse MouseButton m Source # 
Instance details