GPipe-GLFW-1.3.0: GLFW OpenGL context creation for GPipe

Safe HaskellNone
LanguageHaskell2010

Graphics.GPipe.Context.GLFW.Input

Contents

Description

This module exposes much of the functionality that GLFW the Input guide documents: http://www.glfw.org/docs/latest/input_guide.html. Actions are in the GPipe ContextT monad when a window handle is required, otherwise they are bare IO actions. It is recommended to read about GLFW input handling as it pertains to your domain, especially the Event processing section: http://www.glfw.org/docs/latest/input_guide.html#events.

Synopsis

Event processing

Process received events and return; for applications which continually render.

Sleep until an event is received; for applications which update in response to user input.

Force wake from waitEvents with a dummy event.

Keyboard input

Key input

setKeyCallback :: MonadIO m => Maybe (Key -> Int -> KeyState -> ModifierKeys -> IO ()) -> ContextT GLFWWindow os f m () Source #

Register or unregister a callback to receive KeyState changes to any Key.

getKey :: MonadIO m => Key -> ContextT GLFWWindow os f m KeyState Source #

Poll for the KeyState of a Key.

setStickyKeysInputMode :: MonadIO m => StickyKeysInputMode -> ContextT GLFWWindow os f m () Source #

Polling a Key for KeyState may sometimes miss state transitions. If you use cannot use a callback to receive KeyState changes, use getKey in combination with GLFW's sticky-keys feature: http://www.glfw.org/docs/latest/input_guide.html#input_key.

Text input

setCharCallback :: MonadIO m => Maybe (Char -> IO ()) -> ContextT GLFWWindow os f m () Source #

Register or unregister a callback to receive character input obeying keyboard layouts and modifier effects.

Mouse input

Cursor position

setCursorPosCallback :: MonadIO m => Maybe (Double -> Double -> IO ()) -> ContextT GLFWWindow os f m () Source #

Register or unregister a callback to receive mouse location changes. Callback receives x and y position measured in screen-coordinates relative to the top left of the GLFW window.

getCursorPos :: MonadIO m => ContextT GLFWWindow os f m (Double, Double) Source #

Poll for the location of the mouse.

Cursor modes

setCursorInputMode :: MonadIO m => CursorInputMode -> ContextT GLFWWindow os f m () Source #

GLFW supports setting cursor mode to support mouselook and other advanced uses of the mouse: http://www.glfw.org/docs/latest/input_guide.html#cursor_mode.

Cursor objects

Custom cursor creation

createCursor #

Arguments

:: Image

The desired cursor image.

-> Int

The desired x-coordinate, in pixels, of the cursor hotspot.

-> Int

The desired y-coordinate, in pixels, of the cursor hotspot.

-> IO Cursor 

Creates a new cursor.

Standard cursor creation

createStandardCursor :: StandardCursorShape -> IO Cursor #

Creates a cursor with a standard shape that can be set for a window with setCursor.

Cursor destruction

destroyCursor :: Cursor -> IO () #

Destroys a cursor previously created with createCursor. Any remaining cursors will be destroyed by terminate.

Cursor setting

setCursor :: MonadIO m => Cursor -> ContextT GLFWWindow os f m () Source #

Set the cursor to be displayed over the window while CursorInputMode is Normal.

Cursor enter/leave events

setCursorEnterCallback :: MonadIO m => Maybe (CursorState -> IO ()) -> ContextT GLFWWindow os f m () Source #

Register or unregister a callback to receive CursorState changes when the cursor enters or exits the window.

Mouse button input

setMouseButtonCallback :: MonadIO m => Maybe (MouseButton -> MouseButtonState -> ModifierKeys -> IO ()) -> ContextT GLFWWindow os f m () Source #

Register or unregister a callback to receive MouseButtonState changes to a MouseButton.

setStickyMouseButtonsInputMode :: MonadIO m => StickyMouseButtonsInputMode -> ContextT GLFWWindow os f m () Source #

Polling a MouseButton for MouseButtonState may sometimes miss state transitions. If you use cannot use a callback to receive MouseButtonState changes, use getMouseButton in combination with GLFW's sticky-mouse-buttons feature: http://www.glfw.org/docs/latest/input_guide.html#input_mouse_button.

Scroll input

setScrollCallback :: MonadIO m => Maybe (Double -> Double -> IO ()) -> ContextT GLFWWindow os f m () Source #

Register or unregister a callback to receive scroll offset changes.

Joystick input

Is the specified Joystick currently connected?

Joystick axis states

Poll for the positions of each axis on the Joystick. Positions are on the range `-1.0..1.0`.

Joystick button states

Poll for the JoystickButtonState of each button on the Joystick.

Joystick name

Retrieve a non-unique string identifier for the Joystick. This might be the make & model name of the device.

Time input

Poll for the number of seconds since GLFW was initialized by GPipe.

setTime :: Double -> IO () #

Manually set the timer to a specified value.

Clipboard input and output

getClipboardString :: MonadIO m => ContextT GLFWWindow os f m (Maybe String) Source #

Poll the system clipboard for a UTF-8 encoded string, if one can be extracted.

setClipboardString :: MonadIO m => String -> ContextT GLFWWindow os f m () Source #

Store a UTF-8 encoded string in the system clipboard.

Path drop input

setDropCallback :: MonadIO m => Maybe ([String] -> IO ()) -> ContextT GLFWWindow os f m () Source #

Register or unregister a callback to receive file paths when files are dropped onto the window.

Reexported datatypes

Keyboard

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 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)))))

data StickyKeysInputMode :: * #

Instances

Enum StickyKeysInputMode 
Eq StickyKeysInputMode 
Data StickyKeysInputMode 

Methods

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

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

toConstr :: StickyKeysInputMode -> Constr #

dataTypeOf :: StickyKeysInputMode -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Mouse

data CursorInputMode :: * #

Instances

Enum CursorInputMode 
Eq CursorInputMode 
Data CursorInputMode 

Methods

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

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

toConstr :: CursorInputMode -> Constr #

dataTypeOf :: CursorInputMode -> DataType #

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

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

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

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

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

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

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

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

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

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

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

data StandardCursorShape :: * #

Instances

Enum StandardCursorShape 
Eq StandardCursorShape 
Data StandardCursorShape 

Methods

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

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

toConstr :: StandardCursorShape -> Constr #

dataTypeOf :: StandardCursorShape -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StandardCursorShape 
Read StandardCursorShape 
Show StandardCursorShape 
Generic StandardCursorShape 
type Rep StandardCursorShape 
type Rep StandardCursorShape = D1 (MetaData "StandardCursorShape" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) ((:+:) ((:+:) (C1 (MetaCons "StandardCursorShape'Arrow" PrefixI False) U1) ((:+:) (C1 (MetaCons "StandardCursorShape'IBeam" PrefixI False) U1) (C1 (MetaCons "StandardCursorShape'Crosshair" PrefixI False) U1))) ((:+:) (C1 (MetaCons "StandardCursorShape'Hand" PrefixI False) U1) ((:+:) (C1 (MetaCons "StandardCursorShape'HResize" PrefixI False) U1) (C1 (MetaCons "StandardCursorShape'VResize" PrefixI False) U1))))

data CursorState :: * #

Instances

Enum CursorState 
Eq CursorState 
Data CursorState 

Methods

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

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

toConstr :: CursorState -> Constr #

dataTypeOf :: CursorState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CursorState 
Read CursorState 
Show CursorState 
Generic CursorState 

Associated Types

type Rep CursorState :: * -> * #

type Rep CursorState 
type Rep CursorState = D1 (MetaData "CursorState" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) ((:+:) (C1 (MetaCons "CursorState'InWindow" PrefixI False) U1) (C1 (MetaCons "CursorState'NotInWindow" PrefixI False) U1))

data StickyMouseButtonsInputMode :: * #

Instances

Enum StickyMouseButtonsInputMode 
Eq StickyMouseButtonsInputMode 
Data StickyMouseButtonsInputMode 

Methods

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

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

toConstr :: StickyMouseButtonsInputMode -> Constr #

dataTypeOf :: StickyMouseButtonsInputMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StickyMouseButtonsInputMode 
Read StickyMouseButtonsInputMode 
Show StickyMouseButtonsInputMode 
Generic StickyMouseButtonsInputMode 
type Rep StickyMouseButtonsInputMode 
type Rep StickyMouseButtonsInputMode = D1 (MetaData "StickyMouseButtonsInputMode" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) ((:+:) (C1 (MetaCons "StickyMouseButtonsInputMode'Enabled" PrefixI False) U1) (C1 (MetaCons "StickyMouseButtonsInputMode'Disabled" 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))

Joystick

data Joystick :: * #

Instances

Enum Joystick 
Eq Joystick 
Data Joystick 

Methods

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

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

toConstr :: Joystick -> Constr #

dataTypeOf :: Joystick -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Joystick 
Read Joystick 
Show Joystick 
Generic Joystick 

Associated Types

type Rep Joystick :: * -> * #

Methods

from :: Joystick -> Rep Joystick x #

to :: Rep Joystick x -> Joystick #

type Rep Joystick 
type Rep Joystick = D1 (MetaData "Joystick" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Joystick'1" PrefixI False) U1) (C1 (MetaCons "Joystick'2" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Joystick'3" PrefixI False) U1) (C1 (MetaCons "Joystick'4" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Joystick'5" PrefixI False) U1) (C1 (MetaCons "Joystick'6" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Joystick'7" PrefixI False) U1) (C1 (MetaCons "Joystick'8" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Joystick'9" PrefixI False) U1) (C1 (MetaCons "Joystick'10" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Joystick'11" PrefixI False) U1) (C1 (MetaCons "Joystick'12" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Joystick'13" PrefixI False) U1) (C1 (MetaCons "Joystick'14" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Joystick'15" PrefixI False) U1) (C1 (MetaCons "Joystick'16" PrefixI False) U1)))))

data JoystickButtonState :: * #

Instances

Enum JoystickButtonState 
Eq JoystickButtonState 
Data JoystickButtonState 

Methods

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

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

toConstr :: JoystickButtonState -> Constr #

dataTypeOf :: JoystickButtonState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Not supported

Some GLFW functionality isn't currently exposed by GLFW-b.

  • glfwWaitEventsTimeout
  • glfwSetCharModsCallback
  • glfwGetKeyName
  • glfwSetJoystickCallback
  • glfwGetTimerValue
  • glfwGetTimerFrequency

Deprecated

type ScrollCallback = Window -> Double -> Double -> IO () #

registerScrollCallback :: MonadIO m => Maybe ScrollCallback -> ContextT GLFWWindow os f m () Source #

Register or unregister a ScrollCallback to receive scroll events. Deprecated and will be removed. Prefer to use setScrollCallback.

windowShouldClose :: MonadIO m => ContextT GLFWWindow os f m Bool Source #

Returns True if the window should close (e.g. because the user pressed the 'x' button). Deprecated and will be moved to a different module.