gore-and-ash-glfw-1.1.2.0: Core module for Gore&Ash engine for GLFW input events

Copyright(c) Anton Gushcha, 2015-2016
LicenseBSD3
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Game.GoreAndAsh.GLFW

Contents

Description

The core module contains API for GLFW library integration. The module doesn't depends on others core modules and could be place in any place in game monad stack.

The module is NOT pure within first phase (see ModuleStack docs), therefore currently only IO end monad can handler the module.

Example of embedding:

-- | Application monad is monad stack build from given list of modules over base monad (IO)
type AppStack = ModuleStack [GLFWT, ... other modules ... ] IO
newtype AppState = AppState (ModuleState AppStack)
  deriving (Generic)

instance NFData AppState 

-- | Wrapper around type family
newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, MonadThrow, MonadCatch, MonadGLFW, ... other modules monads ... )
  
instance GameModule AppMonad AppState where 
  type ModuleState AppMonad = AppState
  runModule (AppMonad m) (AppState s) = do 
    (a, s') <- runModule m s 
    return (a, AppState s')
  newModuleState = AppState $ newModuleState
  withModule _ = withModule (Proxy :: Proxy AppStack)
  cleanupModule (AppState s) = cleanupModule s 

-- | Arrow that is build over the monad stack
type AppWire a b = GameWire AppMonad a b
-- | Action that makes indexed app wire
type AppActor i a b = GameActor AppMonad i a b

Synopsis

Low-level API

data GLFWState s Source #

Module inner state

s
- State of next module, the states are chained via nesting.

Instances

Generic (GLFWState s) Source # 

Associated Types

type Rep (GLFWState s) :: * -> * #

Methods

from :: GLFWState s -> Rep (GLFWState s) x #

to :: Rep (GLFWState s) x -> GLFWState s #

NFData s => NFData (GLFWState s) Source # 

Methods

rnf :: GLFWState s -> () #

Monad m => MonadState (GLFWState s) (GLFWT s m) 

Methods

get :: GLFWT s m (GLFWState s)

put :: GLFWState s -> GLFWT s m ()

state :: (GLFWState s -> (a, GLFWState s)) -> GLFWT s m a

type Rep (GLFWState s) Source # 
type Rep (GLFWState s) = D1 (MetaData "GLFWState" "Game.GoreAndAsh.GLFW.State" "gore-and-ash-glfw-1.1.2.0-A24f2sdDXdx1sN23WBbBFN" False) (C1 (MetaCons "GLFWState" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "glfwNextState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 s)) (S1 (MetaSel (Just Symbol "glfwKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Key (KeyState, ModifierKeys))))) ((:*:) (S1 (MetaSel (Just Symbol "glfwKeyChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 KeyChannel)) (S1 (MetaSel (Just Symbol "glfwMouseButtons") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap MouseButton (MouseButtonState, ModifierKeys)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "glfwMouseButtonChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 ButtonChannel)) (S1 (MetaSel (Just Symbol "glfwMousePos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Double, Double)))) ((:*:) (S1 (MetaSel (Just Symbol "glfwMousePosChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 MouseChannel)) (S1 (MetaSel (Just Symbol "glfwWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Window)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "glfwPrevWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Window))) (S1 (MetaSel (Just Symbol "glfwWindowSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Double, Double))))) ((:*:) (S1 (MetaSel (Just Symbol "glfwWindowSizeChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowSizeChannel)) (S1 (MetaSel (Just Symbol "glfwScroll") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [(Double, Double)])))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "glfwScrollChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 ScrollChannel)) (S1 (MetaSel (Just Symbol "glfwClose") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "glfwCloseChannel") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 CloseChannel)) (S1 (MetaSel (Just Symbol "glfwBufferSize") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)))))))

data GLFWT s m a Source #

Monad transformer that handles GLFW specific API

s
- State of next core module in modules chain;
m
- Next monad in modules monad stack;
a
- Type of result value;

How to embed module:

type AppStack = ModuleStack [GLFWT, ... other modules ... ] IO

newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, MonadThrow, MonadCatch, MonadSDL)

The module is NOT pure within first phase (see ModuleStack docs), therefore currently only IO end monad can handler the module.

Instances

MonadTrans (GLFWT s) Source # 

Methods

lift :: Monad m => m a -> GLFWT s m a #

Monad m => MonadState (GLFWState s) (GLFWT s m) Source # 

Methods

get :: GLFWT s m (GLFWState s)

put :: GLFWState s -> GLFWT s m ()

state :: (GLFWState s -> (a, GLFWState s)) -> GLFWT s m a

Monad m => Monad (GLFWT s m) Source # 

Methods

(>>=) :: GLFWT s m a -> (a -> GLFWT s m b) -> GLFWT s m b #

(>>) :: GLFWT s m a -> GLFWT s m b -> GLFWT s m b #

return :: a -> GLFWT s m a #

fail :: String -> GLFWT s m a #

Functor m => Functor (GLFWT s m) Source # 

Methods

fmap :: (a -> b) -> GLFWT s m a -> GLFWT s m b #

(<$) :: a -> GLFWT s m b -> GLFWT s m a #

MonadFix m => MonadFix (GLFWT s m) Source # 

Methods

mfix :: (a -> GLFWT s m a) -> GLFWT s m a #

Monad m => Applicative (GLFWT s m) Source # 

Methods

pure :: a -> GLFWT s m a #

(<*>) :: GLFWT s m (a -> b) -> GLFWT s m a -> GLFWT s m b #

(*>) :: GLFWT s m a -> GLFWT s m b -> GLFWT s m b #

(<*) :: GLFWT s m a -> GLFWT s m b -> GLFWT s m a #

MonadIO m => MonadIO (GLFWT s m) Source # 

Methods

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

MonadThrow m => MonadThrow (GLFWT s m) Source # 

Methods

throwM :: Exception e => e -> GLFWT s m a

MonadMask m => MonadMask (GLFWT s m) Source # 

Methods

mask :: ((forall a. GLFWT s m a -> GLFWT s m a) -> GLFWT s m b) -> GLFWT s m b

uninterruptibleMask :: ((forall a. GLFWT s m a -> GLFWT s m a) -> GLFWT s m b) -> GLFWT s m b

MonadCatch m => MonadCatch (GLFWT s m) Source # 

Methods

catch :: Exception e => GLFWT s m a -> (e -> GLFWT s m a) -> GLFWT s m a

Monad m => MonadGLFW (GLFWT s m) Source # 
type ModuleState (GLFWT s m) Source # 
type ModuleState (GLFWT s m) = GLFWState s

class Monad m => MonadGLFW m where Source #

Module low-level API

Methods

keyStatusM :: Key -> m (Maybe (KeyState, ModifierKeys)) Source #

Returns state of given keyboard's key

mouseButtonM :: MouseButton -> m (Maybe (MouseButtonState, ModifierKeys)) Source #

Returns state of given mouse button

mousePosM :: m (Double, Double) Source #

Returns current position of mouse cursor

mouseScrollM :: m [(Double, Double)] Source #

Returns current scroll values of mouse

windowSizeM :: m (Maybe (Double, Double)) Source #

Returns current size of window

windowClosingM :: m Bool Source #

Returns True when close button is pushed

setCurrentWindowM :: Maybe Window -> m () Source #

Setups current window for input catch

getCurrentWindowM :: m (Maybe Window) Source #

Returns current window

setBufferSizeM :: Int -> m () Source #

Setup maximum size of inner buffers for keys, mouse buttons

Arrow API

Keyboard API

keyStatus :: MonadGLFW m => Key -> GameWire m a (Event (KeyState, ModifierKeys)) Source #

Produces event when key state changes

keyStatusDyn :: MonadGLFW m => GameWire m Key (Event (KeyState, ModifierKeys)) Source #

Produces event when key state changes, get key as arrow argument

keyPressed :: MonadGLFW m => Key -> GameWire m a (Event ModifierKeys) Source #

Fires when keyboard key is pressed

keyPressedDyn :: MonadGLFW m => GameWire m Key (Event ModifierKeys) Source #

Version of keyPressed that takes key at runtime

keyReleased :: MonadGLFW m => Key -> GameWire m a (Event ModifierKeys) Source #

Fires when keyboard key is released

keyReleasedDyn :: MonadGLFW m => GameWire m Key (Event ModifierKeys) Source #

Version of keyReleased that takes key at runtime

keyRepeating :: MonadGLFW m => Key -> GameWire m a (Event ModifierKeys) Source #

Fires when keyboard key is entered into repeating mode

keyRepeatingDyn :: MonadGLFW m => GameWire m Key (Event ModifierKeys) Source #

Version of keyRepeating that takes key at runtime

keyPressing :: MonadGLFW m => Key -> GameWire m a (Event ModifierKeys) Source #

Fires event from moment of press until release of given key

keyPressingDyn :: MonadGLFW m => GameWire m Key (Event ModifierKeys) Source #

Version of keyPressing that takes key at runtime

Mouse buttons API

mouseButton :: MonadGLFW m => MouseButton -> GameWire m a (Event (MouseButtonState, ModifierKeys)) Source #

Produces event when mouse button state changes

mouseButtonDyn :: MonadGLFW m => GameWire m MouseButton (Event (MouseButtonState, ModifierKeys)) Source #

Produces event when key state changes, get key as arrow argument

mouseButtonPressed :: MonadGLFW m => MouseButton -> GameWire m a (Event ModifierKeys) Source #

Fires when mouse button is pressed

mouseButtonPressedDyn :: MonadGLFW m => GameWire m MouseButton (Event ModifierKeys) Source #

Version of mouseButtonPressed that takes button at runtime

mouseButtonReleased :: MonadGLFW m => MouseButton -> GameWire m a (Event ModifierKeys) Source #

Fires when mouse button is released

mouseButtonReleasedDyn :: MonadGLFW m => GameWire m MouseButton (Event ModifierKeys) Source #

Version of mouseButtonReleased that takes button at runtime

Cursor position

mousePosition :: MonadGLFW m => GameWire m a (Double, Double) Source #

Returns current position of mouse

mousePositionChange :: MonadGLFW m => GameWire m a (Event (Double, Double)) Source #

Fires event when mouse position changes

mouseXChange :: MonadGLFW m => GameWire m a (Event Double) Source #

Fires event when mouse X axis changes

mouseYChange :: MonadGLFW m => GameWire m a (Event Double) Source #

Fires event when mouse Y axis changes

mouseDelta :: MonadGLFW m => GameWire m a (Double, Double) Source #

Returns mouse delta moves

mouseDeltaChange :: MonadGLFW m => GameWire m a (Event (Double, Double)) Source #

Fires when mouse moves, holds delta move

mouseDeltaXChange :: MonadGLFW m => GameWire m a (Event Double) Source #

Fires when mouse X axis changes, holds delta move

mouseDeltaYChange :: MonadGLFW m => GameWire m a (Event Double) Source #

Fires when mouse Y axis changes, holds delta move

Mouse scroll

mouseScroll :: MonadGLFW m => GameWire m a (Event (Double, Double)) Source #

Fires when user scrolls

mouseScrollX :: MonadGLFW m => GameWire m a (Event Double) Source #

Fires when user scrolls X axis

mouseScrollY :: MonadGLFW m => GameWire m a (Event Double) Source #

Fires when user scrolls Y axis

Window API

windowSize :: MonadGLFW m => GameWire m a (Event (Double, Double)) Source #

Fires when windows size is changed

windowClosing :: MonadGLFW m => GameWire m a (Event ()) Source #

Fires when user hits close button of window

Reexports

data Key :: * #

Instances

Enum Key 

Methods

succ :: Key -> Key #

pred :: Key -> Key #

toEnum :: Int -> Key #

fromEnum :: Key -> Int #

enumFrom :: Key -> [Key] #

enumFromThen :: Key -> Key -> [Key] #

enumFromTo :: Key -> Key -> [Key] #

enumFromThenTo :: Key -> Key -> Key -> [Key] #

Eq Key 

Methods

(==) :: Key -> Key -> Bool #

(/=) :: Key -> Key -> Bool #

Data Key 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Key -> c Key #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Key #

toConstr :: Key -> Constr #

dataTypeOf :: Key -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Key) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key) #

gmapT :: (forall b. Data b => b -> b) -> Key -> Key #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r #

gmapQ :: (forall d. Data d => d -> u) -> Key -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Key -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Key -> m Key #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Key -> m Key #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Key -> m Key #

Ord Key 

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

(>=) :: Key -> Key -> Bool #

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Read Key 
Show Key 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

type Rep Key 
type Rep Key = D1 (MetaData "Key" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'Unknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "Key'Space" PrefixI False) U1) (C1 (MetaCons "Key'Apostrophe" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'Comma" PrefixI False) U1) (C1 (MetaCons "Key'Minus" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'Period" PrefixI False) U1) (C1 (MetaCons "Key'Slash" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'0" PrefixI False) U1) (C1 (MetaCons "Key'1" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'2" PrefixI False) U1) (C1 (MetaCons "Key'3" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'4" PrefixI False) U1) (C1 (MetaCons "Key'5" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'6" PrefixI False) U1) (C1 (MetaCons "Key'7" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'8" PrefixI False) U1) ((:+:) (C1 (MetaCons "Key'9" PrefixI False) U1) (C1 (MetaCons "Key'Semicolon" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'Equal" PrefixI False) U1) (C1 (MetaCons "Key'A" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'B" PrefixI False) U1) (C1 (MetaCons "Key'C" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'D" PrefixI False) U1) (C1 (MetaCons "Key'E" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'F" PrefixI False) U1) (C1 (MetaCons "Key'G" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'H" PrefixI False) U1) (C1 (MetaCons "Key'I" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'J" PrefixI False) U1) (C1 (MetaCons "Key'K" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'L" PrefixI False) U1) ((:+:) (C1 (MetaCons "Key'M" PrefixI False) U1) (C1 (MetaCons "Key'N" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'O" PrefixI False) U1) (C1 (MetaCons "Key'P" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'Q" PrefixI False) U1) (C1 (MetaCons "Key'R" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'S" PrefixI False) U1) (C1 (MetaCons "Key'T" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'U" PrefixI False) U1) (C1 (MetaCons "Key'V" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'W" PrefixI False) U1) (C1 (MetaCons "Key'X" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'Y" PrefixI False) U1) (C1 (MetaCons "Key'Z" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'LeftBracket" PrefixI False) U1) ((:+:) (C1 (MetaCons "Key'Backslash" PrefixI False) U1) (C1 (MetaCons "Key'RightBracket" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'GraveAccent" PrefixI False) U1) (C1 (MetaCons "Key'World1" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'World2" PrefixI False) U1) (C1 (MetaCons "Key'Escape" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'Enter" PrefixI False) U1) (C1 (MetaCons "Key'Tab" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'Backspace" PrefixI False) U1) (C1 (MetaCons "Key'Insert" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'Delete" PrefixI False) U1) (C1 (MetaCons "Key'Right" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'Left" PrefixI False) U1) (C1 (MetaCons "Key'Down" PrefixI False) U1))))))) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'Up" PrefixI False) U1) ((:+:) (C1 (MetaCons "Key'PageUp" PrefixI False) U1) (C1 (MetaCons "Key'PageDown" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'Home" PrefixI False) U1) (C1 (MetaCons "Key'End" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'CapsLock" PrefixI False) U1) (C1 (MetaCons "Key'ScrollLock" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'NumLock" PrefixI False) U1) (C1 (MetaCons "Key'PrintScreen" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'Pause" PrefixI False) U1) (C1 (MetaCons "Key'F1" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'F2" PrefixI False) U1) (C1 (MetaCons "Key'F3" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'F4" PrefixI False) U1) (C1 (MetaCons "Key'F5" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'F6" PrefixI False) U1) ((:+:) (C1 (MetaCons "Key'F7" PrefixI False) U1) (C1 (MetaCons "Key'F8" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'F9" PrefixI False) U1) (C1 (MetaCons "Key'F10" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'F11" PrefixI False) U1) (C1 (MetaCons "Key'F12" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'F13" PrefixI False) U1) (C1 (MetaCons "Key'F14" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'F15" PrefixI False) U1) (C1 (MetaCons "Key'F16" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'F17" PrefixI False) U1) (C1 (MetaCons "Key'F18" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'F19" PrefixI False) U1) (C1 (MetaCons "Key'F20" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'F21" PrefixI False) U1) ((:+:) (C1 (MetaCons "Key'F22" PrefixI False) U1) (C1 (MetaCons "Key'F23" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'F24" PrefixI False) U1) (C1 (MetaCons "Key'F25" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'Pad0" PrefixI False) U1) (C1 (MetaCons "Key'Pad1" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'Pad2" PrefixI False) U1) (C1 (MetaCons "Key'Pad3" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'Pad4" PrefixI False) U1) (C1 (MetaCons "Key'Pad5" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'Pad6" PrefixI False) U1) (C1 (MetaCons "Key'Pad7" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'Pad8" PrefixI False) U1) (C1 (MetaCons "Key'Pad9" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'PadDecimal" PrefixI False) U1) (C1 (MetaCons "Key'PadDivide" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'PadMultiply" PrefixI False) U1) (C1 (MetaCons "Key'PadSubtract" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'PadAdd" PrefixI False) U1) (C1 (MetaCons "Key'PadEnter" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'PadEqual" PrefixI False) U1) (C1 (MetaCons "Key'LeftShift" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Key'LeftControl" PrefixI False) U1) (C1 (MetaCons "Key'LeftAlt" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'LeftSuper" PrefixI False) U1) (C1 (MetaCons "Key'RightShift" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Key'RightControl" PrefixI False) U1) (C1 (MetaCons "Key'RightAlt" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Key'RightSuper" PrefixI False) U1) (C1 (MetaCons "Key'Menu" PrefixI False) U1))))))))

data KeyState :: * #

Instances

Enum KeyState 
Eq KeyState 
Data KeyState 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeyState -> c KeyState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeyState #

toConstr :: KeyState -> Constr #

dataTypeOf :: KeyState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c KeyState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeyState) #

gmapT :: (forall b. Data b => b -> b) -> KeyState -> KeyState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeyState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeyState -> r #

gmapQ :: (forall d. Data d => d -> u) -> KeyState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> KeyState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeyState -> m KeyState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyState -> m KeyState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyState -> m KeyState #

Ord KeyState 
Read KeyState 
Show KeyState 
Generic KeyState 

Associated Types

type Rep KeyState :: * -> * #

Methods

from :: KeyState -> Rep KeyState x #

to :: Rep KeyState x -> KeyState #

type Rep KeyState 
type Rep KeyState = D1 (MetaData "KeyState" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) ((:+:) (C1 (MetaCons "KeyState'Pressed" PrefixI False) U1) ((:+:) (C1 (MetaCons "KeyState'Released" PrefixI False) U1) (C1 (MetaCons "KeyState'Repeating" PrefixI False) U1)))

data MouseButton :: * #

Instances

Enum MouseButton 
Eq MouseButton 
Data MouseButton 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseButton -> c MouseButton #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseButton #

toConstr :: MouseButton -> Constr #

dataTypeOf :: MouseButton -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MouseButton) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseButton) #

gmapT :: (forall b. Data b => b -> b) -> MouseButton -> MouseButton #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseButton -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseButton -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseButton -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseButton -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseButton -> m MouseButton #

Ord MouseButton 
Read MouseButton 
Show MouseButton 
Generic MouseButton 

Associated Types

type Rep MouseButton :: * -> * #

type Rep MouseButton 
type Rep MouseButton = D1 (MetaData "MouseButton" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "MouseButton'1" PrefixI False) U1) (C1 (MetaCons "MouseButton'2" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MouseButton'3" PrefixI False) U1) (C1 (MetaCons "MouseButton'4" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "MouseButton'5" PrefixI False) U1) (C1 (MetaCons "MouseButton'6" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MouseButton'7" PrefixI False) U1) (C1 (MetaCons "MouseButton'8" PrefixI False) U1))))

data MouseButtonState :: * #

Instances

Enum MouseButtonState 
Eq MouseButtonState 
Data MouseButtonState 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MouseButtonState -> c MouseButtonState #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MouseButtonState #

toConstr :: MouseButtonState -> Constr #

dataTypeOf :: MouseButtonState -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MouseButtonState) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MouseButtonState) #

gmapT :: (forall b. Data b => b -> b) -> MouseButtonState -> MouseButtonState #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MouseButtonState -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MouseButtonState -> r #

gmapQ :: (forall d. Data d => d -> u) -> MouseButtonState -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MouseButtonState -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MouseButtonState -> m MouseButtonState #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseButtonState -> m MouseButtonState #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MouseButtonState -> m MouseButtonState #

Ord MouseButtonState 
Read MouseButtonState 
Show MouseButtonState 
Generic MouseButtonState 
type Rep MouseButtonState 
type Rep MouseButtonState = D1 (MetaData "MouseButtonState" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) ((:+:) (C1 (MetaCons "MouseButtonState'Pressed" PrefixI False) U1) (C1 (MetaCons "MouseButtonState'Released" PrefixI False) U1))

data ModifierKeys :: * #

Instances

Eq ModifierKeys 
Data ModifierKeys 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModifierKeys -> c ModifierKeys #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModifierKeys #

toConstr :: ModifierKeys -> Constr #

dataTypeOf :: ModifierKeys -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ModifierKeys) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModifierKeys) #

gmapT :: (forall b. Data b => b -> b) -> ModifierKeys -> ModifierKeys #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModifierKeys -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModifierKeys -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModifierKeys -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModifierKeys -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModifierKeys -> m ModifierKeys #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModifierKeys -> m ModifierKeys #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModifierKeys -> m ModifierKeys #

Ord ModifierKeys 
Read ModifierKeys 
Show ModifierKeys 
Generic ModifierKeys 

Associated Types

type Rep ModifierKeys :: * -> * #

type Rep ModifierKeys 
type Rep ModifierKeys = D1 (MetaData "ModifierKeys" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) (C1 (MetaCons "ModifierKeys" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "modifierKeysShift") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "modifierKeysControl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "modifierKeysAlt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "modifierKeysSuper") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))