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

Safe HaskellNone
LanguageHaskell2010

Graphics.GPipe.Context.GLFW.Input

Contents

Description

User input functions covering much of the GLFW Input guide: 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 reexported IO actions which can be lifted into the ContextT monad. The Window taken by many of these functions is the window resource from GPipe.

Synopsis

Event processing

Learn more: http://www.glfw.org/docs/latest/input_guide.html#events

  • glfwPollEvents
  • glfwWaitEvents

GLFW Events are processed after each buffer swap by default. To change event processing construct a HandleConfig for runContextT. For greater control use the mainloop and mainstep functions provided by Graphics.GPipe.Context.GLFW.

postEmptyEvent :: IO () #

Creates an empty event within the event queue. Can be called from any thread, so you can use this to wake up the main thread that's using waitEvents from a secondary thread. See the Event Processing Guide

Force wake from waitEvents with a dummy event.

Keyboard input

Key input

setKeyCallback :: MonadIO m => Window os c ds -> Maybe (Key -> Int -> KeyState -> ModifierKeys -> IO ()) -> ContextT Handle os m (Maybe ()) Source #

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

getKey :: MonadIO m => Window os c ds -> Key -> ContextT Handle os m (Maybe KeyState) Source #

Poll for the KeyState of a Key.

setStickyKeysInputMode :: MonadIO m => Window os c ds -> StickyKeysInputMode -> ContextT Handle os m (Maybe ()) 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 => Window os c ds -> Maybe (Char -> IO ()) -> ContextT Handle os m (Maybe ()) Source #

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

Mouse input

Cursor position

setCursorPosCallback :: MonadIO m => Window os c ds -> Maybe (Double -> Double -> IO ()) -> ContextT Handle os m (Maybe ()) 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 => Window os c ds -> ContextT Handle os m (Maybe (Double, Double)) Source #

Poll for the location of the mouse.

Cursor modes

setCursorInputMode :: MonadIO m => Window os c ds -> CursorInputMode -> ContextT Handle os m (Maybe ()) 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. This function is not reentrant.

Cursor setting

setCursor :: MonadIO m => Window os c ds -> Cursor -> ContextT Handle os m (Maybe ()) Source #

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

Cursor enter/leave events

setCursorEnterCallback :: MonadIO m => Window os c ds -> Maybe (CursorState -> IO ()) -> ContextT Handle os m (Maybe ()) Source #

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

Mouse button input

setMouseButtonCallback :: MonadIO m => Window os c ds -> Maybe (MouseButton -> MouseButtonState -> ModifierKeys -> IO ()) -> ContextT Handle os m (Maybe ()) Source #

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

setStickyMouseButtonsInputMode :: MonadIO m => Window os c ds -> StickyMouseButtonsInputMode -> ContextT Handle os m (Maybe ()) 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 => Window os c ds -> Maybe (Double -> Double -> IO ()) -> ContextT Handle os m (Maybe ()) Source #

Register or unregister a callback to receive scroll offset changes.

Joystick input

joystickPresent :: Joystick -> IO Bool #

Tests if the joystick is present at all See glfwJoystickPresent

Is the specified Joystick currently connected?

Joystick axis states

getJoystickAxes :: Joystick -> IO (Maybe [Double]) #

Returns the values of all axes of the specified joystick, normalized to between -1.0 and 1.0 See glfwGetJoystickAxes

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

Joystick button states

getJoystickButtons :: Joystick -> IO (Maybe [JoystickButtonState]) #

Returns a list of all joystick button states for the specified joystick. See glfwGetJoystickButtons

Poll for the JoystickButtonState of each button on the Joystick.

Joystick name

getJoystickName :: Joystick -> IO (Maybe String) #

A human-readable name for a Joystick. Not guranteed to be unique. See glfwGetJoystickName

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

Time input

getTime :: IO (Maybe Double) #

Returns the time (in seconds) of the GLFW timer. This is the amount of time since GLFW was initialized, unless setTime was used. The exact resolution is system dependent. See glfwGetTime

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

setTime :: Double -> IO () #

Sets the GLFW timer to the specified value, which is measured in seconds, and must be positive. The value must also be less than ~584 years in seconds (18446744073.0). After this the timer begins to count upward at the normal rate. See glfwSetTime

Manually set the timer to a specified value.

Clipboard input and output

getClipboardString :: MonadIO m => Window os c ds -> ContextT Handle os m (Maybe (Maybe String)) Source #

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

setClipboardString :: MonadIO m => Window os c ds -> String -> ContextT Handle os m (Maybe ()) Source #

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

Path drop input

setDropCallback :: MonadIO m => Window os c ds -> Maybe ([String] -> IO ()) -> ContextT Handle os m (Maybe ()) Source #

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

Reexported datatypes

Keyboard

data Key #

Part of the Keyboard Input system.

Instances
Bounded Key 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

minBound :: Key #

maxBound :: Key #

Enum Key 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

Data Key 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Show Key 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

NFData Key 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: Key -> () #

type Rep Key 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data KeyState #

The state of an individual key when getKey is called.

Instances
Bounded KeyState 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum KeyState 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq KeyState 
Instance details

Defined in Graphics.UI.GLFW.Types

Data KeyState 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read KeyState 
Instance details

Defined in Graphics.UI.GLFW.Types

Show KeyState 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic KeyState 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep KeyState :: Type -> Type #

Methods

from :: KeyState -> Rep KeyState x #

to :: Rep KeyState x -> KeyState #

NFData KeyState 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: KeyState -> () #

type Rep KeyState 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data ModifierKeys #

Modifier keys that were pressed as part of another keypress event.

Instances
Eq ModifierKeys 
Instance details

Defined in Graphics.UI.GLFW.Types

Data ModifierKeys 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read ModifierKeys 
Instance details

Defined in Graphics.UI.GLFW.Types

Show ModifierKeys 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic ModifierKeys 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep ModifierKeys :: Type -> Type #

NFData ModifierKeys 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: ModifierKeys -> () #

type Rep ModifierKeys 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep ModifierKeys = D1 (MetaData "ModifierKeys" "Graphics.UI.GLFW.Types" "GLFW-b-3.2.1.1-IHbryowQKBk7dJKopeFt9g" False) (C1 (MetaCons "ModifierKeys" PrefixI True) ((S1 (MetaSel (Just "modifierKeysShift") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "modifierKeysControl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) :*: (S1 (MetaSel (Just "modifierKeysAlt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "modifierKeysSuper") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))))

data StickyKeysInputMode #

When sticky keys is enabled, once a key is pressed it will remain pressed at least until the state is polled with getKey. After that, if the key has been released it will switch back to released. This helps prevent problems with low-resolution polling missing key pressed. Note that use of the callbacks to avoid this problem the the recommended route, and this is just for a fallback.

Instances
Bounded StickyKeysInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum StickyKeysInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq StickyKeysInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Data StickyKeysInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read StickyKeysInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Show StickyKeysInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic StickyKeysInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep StickyKeysInputMode :: Type -> Type #

NFData StickyKeysInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: StickyKeysInputMode -> () #

type Rep StickyKeysInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep StickyKeysInputMode = D1 (MetaData "StickyKeysInputMode" "Graphics.UI.GLFW.Types" "GLFW-b-3.2.1.1-IHbryowQKBk7dJKopeFt9g" False) (C1 (MetaCons "StickyKeysInputMode'Enabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StickyKeysInputMode'Disabled" PrefixI False) (U1 :: Type -> Type))

Mouse

data CursorInputMode #

Allows for special forms of mouse input. See Cursor Modes

Instances
Bounded CursorInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum CursorInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq CursorInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Data CursorInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read CursorInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Show CursorInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic CursorInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep CursorInputMode :: Type -> Type #

NFData CursorInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: CursorInputMode -> () #

type Rep CursorInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep CursorInputMode = D1 (MetaData "CursorInputMode" "Graphics.UI.GLFW.Types" "GLFW-b-3.2.1.1-IHbryowQKBk7dJKopeFt9g" False) (C1 (MetaCons "CursorInputMode'Normal" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CursorInputMode'Hidden" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CursorInputMode'Disabled" PrefixI False) (U1 :: Type -> Type)))

data StandardCursorShape #

Lets you use one of the standard cursor appearnaces that the local system theme provides for. See Standard Cursor Creation.

Instances
Bounded StandardCursorShape 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum StandardCursorShape 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq StandardCursorShape 
Instance details

Defined in Graphics.UI.GLFW.Types

Data StandardCursorShape 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read StandardCursorShape 
Instance details

Defined in Graphics.UI.GLFW.Types

Show StandardCursorShape 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic StandardCursorShape 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep StandardCursorShape :: Type -> Type #

NFData StandardCursorShape 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: StandardCursorShape -> () #

type Rep StandardCursorShape 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep StandardCursorShape = D1 (MetaData "StandardCursorShape" "Graphics.UI.GLFW.Types" "GLFW-b-3.2.1.1-IHbryowQKBk7dJKopeFt9g" False) ((C1 (MetaCons "StandardCursorShape'Arrow" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StandardCursorShape'IBeam" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StandardCursorShape'Crosshair" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "StandardCursorShape'Hand" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StandardCursorShape'HResize" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StandardCursorShape'VResize" PrefixI False) (U1 :: Type -> Type))))

data CursorState #

If the mouse's cursor is in the window or not.

Instances
Bounded CursorState 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum CursorState 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq CursorState 
Instance details

Defined in Graphics.UI.GLFW.Types

Data CursorState 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read CursorState 
Instance details

Defined in Graphics.UI.GLFW.Types

Show CursorState 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic CursorState 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep CursorState :: Type -> Type #

NFData CursorState 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: CursorState -> () #

type Rep CursorState 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data StickyMouseButtonsInputMode #

This is the mouse version of StickyKeysInputMode.

Instances
Bounded StickyMouseButtonsInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum StickyMouseButtonsInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq StickyMouseButtonsInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Data StickyMouseButtonsInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read StickyMouseButtonsInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Show StickyMouseButtonsInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic StickyMouseButtonsInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep StickyMouseButtonsInputMode :: Type -> Type #

NFData StickyMouseButtonsInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep StickyMouseButtonsInputMode 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep StickyMouseButtonsInputMode = D1 (MetaData "StickyMouseButtonsInputMode" "Graphics.UI.GLFW.Types" "GLFW-b-3.2.1.1-IHbryowQKBk7dJKopeFt9g" False) (C1 (MetaCons "StickyMouseButtonsInputMode'Enabled" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StickyMouseButtonsInputMode'Disabled" PrefixI False) (U1 :: Type -> Type))

data MouseButton #

Part of the Mouse Input system.

Instances
Bounded MouseButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum MouseButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq MouseButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Data MouseButton 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read MouseButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Show MouseButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic MouseButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep MouseButton :: Type -> Type #

NFData MouseButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: MouseButton -> () #

type Rep MouseButton 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data MouseButtonState #

If the mouse button is pressed or not when getMouseButton is called.

Instances
Bounded MouseButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum MouseButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq MouseButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Data MouseButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read MouseButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Show MouseButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic MouseButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep MouseButtonState :: Type -> Type #

NFData MouseButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: MouseButtonState -> () #

type Rep MouseButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep MouseButtonState = D1 (MetaData "MouseButtonState" "Graphics.UI.GLFW.Types" "GLFW-b-3.2.1.1-IHbryowQKBk7dJKopeFt9g" False) (C1 (MetaCons "MouseButtonState'Pressed" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MouseButtonState'Released" PrefixI False) (U1 :: Type -> Type))

Joystick

data Joystick #

For use with the Joystick Input system.

Instances
Bounded Joystick 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum Joystick 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq Joystick 
Instance details

Defined in Graphics.UI.GLFW.Types

Data Joystick 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read Joystick 
Instance details

Defined in Graphics.UI.GLFW.Types

Show Joystick 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic Joystick 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep Joystick :: Type -> Type #

Methods

from :: Joystick -> Rep Joystick x #

to :: Rep Joystick x -> Joystick #

NFData Joystick 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: Joystick -> () #

type Rep Joystick 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data JoystickButtonState #

If a given joystick button is pressed or not when getJoystickButtons is called.

Instances
Bounded JoystickButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum JoystickButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq JoystickButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Data JoystickButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

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 
Instance details

Defined in Graphics.UI.GLFW.Types

Read JoystickButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Show JoystickButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic JoystickButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep JoystickButtonState :: Type -> Type #

NFData JoystickButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: JoystickButtonState -> () #

type Rep JoystickButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep JoystickButtonState = D1 (MetaData "JoystickButtonState" "Graphics.UI.GLFW.Types" "GLFW-b-3.2.1.1-IHbryowQKBk7dJKopeFt9g" False) (C1 (MetaCons "JoystickButtonState'Pressed" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "JoystickButtonState'Released" PrefixI False) (U1 :: Type -> Type))

Not supported

Some GLFW functionality isn't currently exposed by Graphics.UI.GLFW.

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