Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Threading restrictions which apply to the C version of GLFW still apply when
writing GLFW-b
programs. See
GLFW thread safety documentation
(applies here).
Current context restructions which apply to the C version of GLFW still apply. See GLFW current context documentation (applies here).
GLFW-b
wraps callbacks and schedules them to be run after pollEvents
and
waitEvents
in the normal GHC runtime where they aren't subject to the usual
GLFW reentrancy restrictions. See
GLFW reentrancy documentation
(does not apply here).
Synopsis
- data Error
- setErrorCallback :: Maybe ErrorCallback -> IO ()
- type ErrorCallback = Error -> String -> IO ()
- data Version = Version {
- versionMajor :: !Int
- versionMinor :: !Int
- versionRevision :: !Int
- init :: IO Bool
- data InitHint
- initHint :: InitHint -> Bool -> IO ()
- terminate :: IO ()
- getVersion :: IO Version
- getVersionString :: IO (Maybe String)
- getError :: IO (Maybe (Error, String))
- clearError :: IO ()
- rawMouseMotionSupported :: IO Bool
- data Monitor
- data MonitorState
- data VideoMode = VideoMode {
- videoModeWidth :: !Int
- videoModeHeight :: !Int
- videoModeRedBits :: !Int
- videoModeGreenBits :: !Int
- videoModeBlueBits :: !Int
- videoModeRefreshRate :: !Int
- data GammaRamp
- makeGammaRamp :: [Int] -> [Int] -> [Int] -> Maybe GammaRamp
- getMonitors :: IO (Maybe [Monitor])
- getPrimaryMonitor :: IO (Maybe Monitor)
- getMonitorPos :: Monitor -> IO (Int, Int)
- getMonitorPhysicalSize :: Monitor -> IO (Int, Int)
- getMonitorContentScale :: Monitor -> IO (Float, Float)
- getMonitorWorkarea :: Monitor -> IO (Int, Int, Int, Int)
- getMonitorName :: Monitor -> IO (Maybe String)
- setMonitorCallback :: Maybe MonitorCallback -> IO ()
- type MonitorCallback = Monitor -> MonitorState -> IO ()
- getVideoModes :: Monitor -> IO (Maybe [VideoMode])
- getVideoMode :: Monitor -> IO (Maybe VideoMode)
- setGamma :: Monitor -> Double -> IO ()
- getGammaRamp :: Monitor -> IO (Maybe GammaRamp)
- setGammaRamp :: Monitor -> GammaRamp -> IO ()
- data Window
- data WindowHint
- = WindowHint'Resizable !Bool
- | WindowHint'Visible !Bool
- | WindowHint'Decorated !Bool
- | WindowHint'RedBits !(Maybe Int)
- | WindowHint'GreenBits !(Maybe Int)
- | WindowHint'BlueBits !(Maybe Int)
- | WindowHint'AlphaBits !(Maybe Int)
- | WindowHint'DepthBits !(Maybe Int)
- | WindowHint'StencilBits !(Maybe Int)
- | WindowHint'AccumRedBits !(Maybe Int)
- | WindowHint'AccumGreenBits !(Maybe Int)
- | WindowHint'AccumBlueBits !(Maybe Int)
- | WindowHint'AccumAlphaBits !(Maybe Int)
- | WindowHint'AuxBuffers !(Maybe Int)
- | WindowHint'Samples !(Maybe Int)
- | WindowHint'RefreshRate !(Maybe Int)
- | WindowHint'DoubleBuffer !Bool
- | WindowHint'Stereo !Bool
- | WindowHint'sRGBCapable !Bool
- | WindowHint'Floating !Bool
- | WindowHint'Focused !Bool
- | WindowHint'Maximized !Bool
- | WindowHint'AutoIconify !Bool
- | WindowHint'ClientAPI !ClientAPI
- | WindowHint'ContextCreationAPI !ContextCreationAPI
- | WindowHint'ContextVersionMajor !Int
- | WindowHint'ContextVersionMinor !Int
- | WindowHint'ContextRobustness !ContextRobustness
- | WindowHint'ContextReleaseBehavior !ContextReleaseBehavior
- | WindowHint'ContextNoError !Bool
- | WindowHint'OpenGLForwardCompat !Bool
- | WindowHint'OpenGLDebugContext !Bool
- | WindowHint'OpenGLProfile !OpenGLProfile
- | WindowHint'TransparentFramebuffer !Bool
- | WindowHint'CenterCursor !Bool
- | WindowHint'FocusOnShow !Bool
- | WindowHint'ScaleToMonitor !Bool
- | WindowHint'CocoaRetinaFramebuffer !Bool
- | WindowHint'CocoaGraphicsSwitching !Bool
- | WindowHint'CocoaFrameName !String
- | WindowHint'X11ClassName !String
- | WindowHint'X11InstanceName !String
- data WindowAttrib
- data ContextRobustness
- data OpenGLProfile
- data ClientAPI
- data ContextCreationAPI
- data ContextReleaseBehavior
- defaultWindowHints :: IO ()
- windowHint :: WindowHint -> IO ()
- setWindowAttrib :: Window -> WindowAttrib -> Bool -> IO ()
- getWindowAttrib :: Window -> WindowAttrib -> IO Bool
- createWindow :: Int -> Int -> String -> Maybe Monitor -> Maybe Window -> IO (Maybe Window)
- destroyWindow :: Window -> IO ()
- windowShouldClose :: Window -> IO Bool
- setWindowShouldClose :: Window -> Bool -> IO ()
- getWindowOpacity :: Window -> IO Float
- setWindowOpacity :: Window -> Float -> IO ()
- setWindowTitle :: Window -> String -> IO ()
- getWindowPos :: Window -> IO (Int, Int)
- setWindowPos :: Window -> Int -> Int -> IO ()
- getWindowSize :: Window -> IO (Int, Int)
- setWindowSize :: Window -> Int -> Int -> IO ()
- setWindowSizeLimits :: Window -> Maybe Int -> Maybe Int -> Maybe Int -> Maybe Int -> IO ()
- setWindowAspectRatio :: Window -> Maybe (Int, Int) -> IO ()
- getWindowFrameSize :: Window -> IO (Int, Int, Int, Int)
- getWindowContentScale :: Window -> IO (Float, Float)
- getFramebufferSize :: Window -> IO (Int, Int)
- setWindowIcon :: Window -> [Image] -> IO ()
- iconifyWindow :: Window -> IO ()
- restoreWindow :: Window -> IO ()
- focusWindow :: Window -> IO ()
- maximizeWindow :: Window -> IO ()
- showWindow :: Window -> IO ()
- hideWindow :: Window -> IO ()
- requestWindowAttention :: Window -> IO ()
- getWindowMonitor :: Window -> IO (Maybe Monitor)
- setCursorPos :: Window -> Double -> Double -> IO ()
- setFullscreen :: Window -> Monitor -> VideoMode -> IO ()
- setWindowed :: Window -> Int -> Int -> Int -> Int -> IO ()
- getWindowFocused :: Window -> IO Bool
- getWindowMaximized :: Window -> IO Bool
- getWindowFloating :: Window -> IO Bool
- getWindowIconified :: Window -> IO Bool
- getWindowResizable :: Window -> IO Bool
- getWindowDecorated :: Window -> IO Bool
- getWindowVisible :: Window -> IO Bool
- getWindowClientAPI :: Window -> IO ClientAPI
- getWindowContextCreationAPI :: Window -> IO ContextCreationAPI
- getWindowContextVersionMajor :: Window -> IO Int
- getWindowContextVersionMinor :: Window -> IO Int
- getWindowContextVersionRevision :: Window -> IO Int
- getWindowContextRobustness :: Window -> IO ContextRobustness
- getWindowContextReleaseBehavior :: Window -> IO ContextReleaseBehavior
- getWindowContextNoError :: Window -> IO Bool
- getWindowOpenGLForwardCompat :: Window -> IO Bool
- getWindowOpenGLDebugContext :: Window -> IO Bool
- getWindowOpenGLProfile :: Window -> IO OpenGLProfile
- setWindowPosCallback :: Window -> Maybe WindowPosCallback -> IO ()
- type WindowPosCallback = Window -> Int -> Int -> IO ()
- setWindowSizeCallback :: Window -> Maybe WindowSizeCallback -> IO ()
- type WindowSizeCallback = Window -> Int -> Int -> IO ()
- setWindowCloseCallback :: Window -> Maybe WindowCloseCallback -> IO ()
- type WindowCloseCallback = Window -> IO ()
- setWindowRefreshCallback :: Window -> Maybe WindowRefreshCallback -> IO ()
- type WindowRefreshCallback = Window -> IO ()
- setWindowFocusCallback :: Window -> Maybe WindowFocusCallback -> IO ()
- type WindowFocusCallback = Window -> Bool -> IO ()
- setWindowIconifyCallback :: Window -> Maybe WindowIconifyCallback -> IO ()
- type WindowIconifyCallback = Window -> Bool -> IO ()
- setFramebufferSizeCallback :: Window -> Maybe FramebufferSizeCallback -> IO ()
- type FramebufferSizeCallback = Window -> Int -> Int -> IO ()
- setWindowContentScaleCallback :: Window -> Maybe WindowContentScaleCallback -> IO ()
- type WindowContentScaleCallback = Window -> Float -> Float -> IO ()
- setWindowMaximizeCallback :: Window -> Maybe WindowMaximizeCallback -> IO ()
- type WindowMaximizeCallback = Window -> Bool -> IO ()
- pollEvents :: IO ()
- waitEvents :: IO ()
- waitEventsTimeout :: Double -> IO ()
- postEmptyEvent :: IO ()
- data Key
- = Key'Unknown
- | Key'Space
- | Key'Apostrophe
- | Key'Comma
- | Key'Minus
- | Key'Period
- | Key'Slash
- | Key'0
- | Key'1
- | Key'2
- | Key'3
- | Key'4
- | Key'5
- | Key'6
- | Key'7
- | Key'8
- | Key'9
- | Key'Semicolon
- | Key'Equal
- | Key'A
- | Key'B
- | Key'C
- | Key'D
- | Key'E
- | Key'F
- | Key'G
- | Key'H
- | Key'I
- | Key'J
- | Key'K
- | Key'L
- | Key'M
- | Key'N
- | Key'O
- | Key'P
- | Key'Q
- | Key'R
- | Key'S
- | Key'T
- | Key'U
- | Key'V
- | Key'W
- | Key'X
- | Key'Y
- | Key'Z
- | Key'LeftBracket
- | Key'Backslash
- | Key'RightBracket
- | Key'GraveAccent
- | Key'World1
- | Key'World2
- | Key'Escape
- | Key'Enter
- | Key'Tab
- | Key'Backspace
- | Key'Insert
- | Key'Delete
- | Key'Right
- | Key'Left
- | Key'Down
- | Key'Up
- | Key'PageUp
- | Key'PageDown
- | Key'Home
- | Key'End
- | Key'CapsLock
- | Key'ScrollLock
- | Key'NumLock
- | Key'PrintScreen
- | Key'Pause
- | Key'F1
- | Key'F2
- | Key'F3
- | Key'F4
- | Key'F5
- | Key'F6
- | Key'F7
- | Key'F8
- | Key'F9
- | Key'F10
- | Key'F11
- | Key'F12
- | Key'F13
- | Key'F14
- | Key'F15
- | Key'F16
- | Key'F17
- | Key'F18
- | Key'F19
- | Key'F20
- | Key'F21
- | Key'F22
- | Key'F23
- | Key'F24
- | Key'F25
- | Key'Pad0
- | Key'Pad1
- | Key'Pad2
- | Key'Pad3
- | Key'Pad4
- | Key'Pad5
- | Key'Pad6
- | Key'Pad7
- | Key'Pad8
- | Key'Pad9
- | Key'PadDecimal
- | Key'PadDivide
- | Key'PadMultiply
- | Key'PadSubtract
- | Key'PadAdd
- | Key'PadEnter
- | Key'PadEqual
- | Key'LeftShift
- | Key'LeftControl
- | Key'LeftAlt
- | Key'LeftSuper
- | Key'RightShift
- | Key'RightControl
- | Key'RightAlt
- | Key'RightSuper
- | Key'Menu
- data KeyState
- data Joystick
- data JoystickState
- data JoystickButtonState
- data MouseButton
- data MouseButtonState
- data CursorState
- data CursorInputMode
- data StickyKeysInputMode
- data StickyMouseButtonsInputMode
- data ModifierKeys = ModifierKeys {}
- data GamepadButton
- = GamepadButton'A
- | GamepadButton'B
- | GamepadButton'X
- | GamepadButton'Y
- | GamepadButton'LeftBumper
- | GamepadButton'RightBumper
- | GamepadButton'Back
- | GamepadButton'Start
- | GamepadButton'Guide
- | GamepadButton'LeftThumb
- | GamepadButton'RightThumb
- | GamepadButton'DpadUp
- | GamepadButton'DpadRight
- | GamepadButton'DpadDown
- | GamepadButton'DpadLeft
- | GamepadButton'Cross
- | GamepadButton'Circle
- | GamepadButton'Square
- | GamepadButton'Triangle
- data GamepadAxis
- data GamepadButtonState
- data GamepadState = GamepadState {}
- data Image
- mkImage :: Int -> Int -> (Int -> Int -> (Word8, Word8, Word8, Word8)) -> Image
- newtype Cursor = Cursor {}
- data StandardCursorShape
- getCursorInputMode :: Window -> IO CursorInputMode
- setCursorInputMode :: Window -> CursorInputMode -> IO ()
- getRawMouseMotion :: Window -> IO Bool
- setRawMouseMotion :: Window -> Bool -> IO ()
- getStickyKeysInputMode :: Window -> IO StickyKeysInputMode
- setStickyKeysInputMode :: Window -> StickyKeysInputMode -> IO ()
- getStickyMouseButtonsInputMode :: Window -> IO StickyMouseButtonsInputMode
- setStickyMouseButtonsInputMode :: Window -> StickyMouseButtonsInputMode -> IO ()
- getKey :: Window -> Key -> IO KeyState
- getKeyName :: Key -> Int -> IO (Maybe String)
- getKeyScancode :: Key -> IO Int
- getMouseButton :: Window -> MouseButton -> IO MouseButtonState
- getCursorPos :: Window -> IO (Double, Double)
- setKeyCallback :: Window -> Maybe KeyCallback -> IO ()
- type KeyCallback = Window -> Key -> Int -> KeyState -> ModifierKeys -> IO ()
- setCharCallback :: Window -> Maybe CharCallback -> IO ()
- type CharCallback = Window -> Char -> IO ()
- setCharModsCallback :: Window -> Maybe CharModsCallback -> IO ()
- type CharModsCallback = Window -> Char -> ModifierKeys -> IO ()
- setMouseButtonCallback :: Window -> Maybe MouseButtonCallback -> IO ()
- type MouseButtonCallback = Window -> MouseButton -> MouseButtonState -> ModifierKeys -> IO ()
- setCursorPosCallback :: Window -> Maybe CursorPosCallback -> IO ()
- type CursorPosCallback = Window -> Double -> Double -> IO ()
- setCursorEnterCallback :: Window -> Maybe CursorEnterCallback -> IO ()
- type CursorEnterCallback = Window -> CursorState -> IO ()
- createCursor :: Image -> Int -> Int -> IO Cursor
- createStandardCursor :: StandardCursorShape -> IO Cursor
- setCursor :: Window -> Cursor -> IO ()
- destroyCursor :: Cursor -> IO ()
- setScrollCallback :: Window -> Maybe ScrollCallback -> IO ()
- type ScrollCallback = Window -> Double -> Double -> IO ()
- setDropCallback :: Window -> Maybe DropCallback -> IO ()
- type DropCallback = Window -> [String] -> IO ()
- joystickPresent :: Joystick -> IO Bool
- joystickIsGamepad :: Joystick -> IO Bool
- getJoystickAxes :: Joystick -> IO (Maybe [Double])
- getJoystickButtons :: Joystick -> IO (Maybe [JoystickButtonState])
- getJoystickHats :: Joystick -> IO (Maybe [JoystickHatState])
- data JoystickHatState
- getJoystickName :: Joystick -> IO (Maybe String)
- getJoystickGUID :: Joystick -> IO (Maybe String)
- setJoystickCallback :: Maybe JoystickCallback -> IO ()
- type JoystickCallback = Joystick -> JoystickState -> IO ()
- getGamepadName :: Joystick -> IO (Maybe String)
- getGamepadState :: Joystick -> IO (Maybe GamepadState)
- updateGamepadMappings :: String -> IO Bool
- getTime :: IO (Maybe Double)
- setTime :: Double -> IO ()
- getTimerValue :: IO Word64
- getTimerFrequency :: IO Word64
- makeContextCurrent :: Maybe Window -> IO ()
- getCurrentContext :: IO (Maybe Window)
- swapBuffers :: Window -> IO ()
- swapInterval :: Int -> IO ()
- extensionSupported :: String -> IO Bool
- getClipboardString :: Window -> IO (Maybe String)
- setClipboardString :: Window -> String -> IO ()
- vulkanSupported :: IO Bool
- getRequiredInstanceExtensions :: IO [CString]
- getInstanceProcAddress :: Ptr vkInstance -> String -> IO (FunPtr vkProc)
- getPhysicalDevicePresentationSupport :: Ptr vkInstance -> Ptr vkPhysicalDevice -> Word32 -> IO Bool
- createWindowSurface :: Enum vkResult => Ptr vkInstance -> Window -> Ptr vkAllocationCallbacks -> Ptr vkSurfaceKHR -> IO vkResult
- getWin32Adapter :: Window -> IO CString
- getWin32Monitor :: Window -> IO CString
- getWin32Window :: Window -> IO (Ptr ())
- getWGLContext :: Window -> IO (Ptr ())
- getCocoaMonitor :: Window -> IO (Ptr Word32)
- getCocoaWindow :: Window -> IO (Ptr ())
- getNSGLContext :: Window -> IO (Ptr ())
- getX11Display :: Window -> IO (Ptr display)
- getX11Adapter :: Window -> IO Word64
- getX11Monitor :: Window -> IO Word64
- getX11Window :: Window -> IO Word64
- getX11SelectionString :: IO String
- setX11SelectionString :: String -> IO ()
- getGLXContext :: Window -> IO (Ptr ())
- getGLXWindow :: Window -> IO Word64
- getWaylandDisplay :: IO (Ptr wl_display)
- getWaylandMonitor :: Window -> IO (Ptr wl_output)
- getWaylandWindow :: Window -> IO (Ptr wl_surface)
- getEGLDisplay :: IO (Ptr ())
- getEGLContext :: Window -> IO (Ptr ())
- getEGLSurface :: Window -> IO (Ptr ())
- getOSMesaContext :: Window -> IO (Ptr ())
- getOSMesaColorBuffer :: Window -> IO (Maybe OSMesaColorBuffer)
- type OSMesaColorBuffer = Array (Int, Int) OSMesaRGBA
- type OSMesaRGBA = (Word8, Word8, Word8, Word8)
- getOSMesaDepthBuffer :: Window -> IO (Maybe (OSMesaDepthBuffer, Word32))
- type OSMesaDepthBuffer = Array (Int, Int) Word32
Error handling
An enum for one of the GLFW error codes.
Error'NotInitialized | |
Error'NoCurrentContext | |
Error'InvalidEnum | |
Error'InvalidValue | |
Error'OutOfMemory | |
Error'ApiUnavailable | |
Error'VersionUnavailable | |
Error'PlatformError | |
Error'FormatUnavailable |
Instances
Data Error Source # | |
Defined in Graphics.UI.GLFW.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Error -> c Error # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Error # dataTypeOf :: Error -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Error) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Error) # gmapT :: (forall b. Data b => b -> b) -> Error -> Error # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Error -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Error -> r # gmapQ :: (forall d. Data d => d -> u) -> Error -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Error -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Error -> m Error # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Error -> m Error # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Error -> m Error # | |
Bounded Error Source # | |
Enum Error Source # | |
Defined in Graphics.UI.GLFW.Types | |
Generic Error Source # | |
Read Error Source # | |
Show Error Source # | |
NFData Error Source # | |
Defined in Graphics.UI.GLFW.Types | |
Eq Error Source # | |
Ord Error Source # | |
C CInt Error Source # | |
type Rep Error Source # | |
Defined in Graphics.UI.GLFW.Types type Rep Error = D1 ('MetaData "Error" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" 'False) (((C1 ('MetaCons "Error'NotInitialized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error'NoCurrentContext" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Error'InvalidEnum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error'InvalidValue" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Error'OutOfMemory" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error'ApiUnavailable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Error'VersionUnavailable" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Error'PlatformError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error'FormatUnavailable" 'PrefixI 'False) (U1 :: Type -> Type))))) |
setErrorCallback :: Maybe ErrorCallback -> IO () Source #
Can (and probably should) be used before GLFW initialization. See glfwSetErrorCallback
type ErrorCallback = Error -> String -> IO () Source #
The error code and also a human-readable error message.
Initialization and version information
The library version of the GLFW implementation in use. See Version Management
Version | |
|
Instances
Data Version Source # | |
Defined in Graphics.UI.GLFW.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version # toConstr :: Version -> Constr # dataTypeOf :: Version -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) # gmapT :: (forall b. Data b => b -> b) -> Version -> Version # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # | |
Generic Version Source # | |
Read Version Source # | |
Show Version Source # | |
NFData Version Source # | |
Defined in Graphics.UI.GLFW.Types | |
Eq Version Source # | |
Ord Version Source # | |
type Rep Version Source # | |
Defined in Graphics.UI.GLFW.Types type Rep Version = D1 ('MetaData "Version" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "versionMajor") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "versionMinor") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "versionRevision") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)))) |
Attempts to initialize the GLFW library. When the library is not initialized, the only
allowed functions to call are getVersion
, getVersionString
, setErrorCallback
,
init
, and terminate
. Returns if the initialization was successful or not.
See glfwInit
and Initialization and Termination
Initialization hints are set before glfwInit and affect how the library behaves until termination. Hints are set with glfwInitHint. See Init Hints
Instances
Data InitHint Source # | |
Defined in Graphics.UI.GLFW.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InitHint -> c InitHint # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InitHint # toConstr :: InitHint -> Constr # dataTypeOf :: InitHint -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InitHint) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InitHint) # gmapT :: (forall b. Data b => b -> b) -> InitHint -> InitHint # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InitHint -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InitHint -> r # gmapQ :: (forall d. Data d => d -> u) -> InitHint -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InitHint -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InitHint -> m InitHint # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InitHint -> m InitHint # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InitHint -> m InitHint # | |
Bounded InitHint Source # | |
Enum InitHint Source # | |
Generic InitHint Source # | |
Read InitHint Source # | |
Show InitHint Source # | |
NFData InitHint Source # | |
Defined in Graphics.UI.GLFW.Types | |
Eq InitHint Source # | |
Ord InitHint Source # | |
Defined in Graphics.UI.GLFW.Types | |
C CInt InitHint Source # | |
type Rep InitHint Source # | |
Defined in Graphics.UI.GLFW.Types type Rep InitHint = D1 ('MetaData "InitHint" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" 'False) (C1 ('MetaCons "InitHint'JoystickHatButtons" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InitHint'CocoaChdirResources" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InitHint'CocoaMenubar" 'PrefixI 'False) (U1 :: Type -> Type))) |
initHint :: InitHint -> Bool -> IO () Source #
This function sets hints for the next initialization of GLFW. See glfwInitHint
Cleans up GLFW and puts the library into an uninitialized state. Once you call this, you must initilize the library again. Warning: No window's context may be current in another thread when this is called. See glfwTerminate and Initialization and Termination. This function is not reentrant.
getVersion :: IO Version Source #
Gets the version of the GLFW library that's being used with the current program. See glfwGetVersion
getVersionString :: IO (Maybe String) Source #
Gets the compile-time version string of the GLFW library binary.
Gives extra info like platform and compile time options used, but you should not
attempt to parse this to get the GLFW version number. Use getVersion
instead.
See glfwGetVersionString
getError :: IO (Maybe (Error, String)) Source #
Returns and clears the error code of the last error that occurred on the calling thread and a UTF-8 encoded human-readable description of it. If no error has occurred since the last call, it returns Nothing.
clearError :: IO () Source #
Clears the last error as would be retreived by getError
.
rawMouseMotionSupported :: IO Bool Source #
Returns true if raw mouse motion is supported on the current system. See glfwRawMouseMotionSupported
Monitor handling
Represents a physical monitor that's currently connected. See the Monitor Guide
Instances
Data Monitor Source # | |
Defined in Graphics.UI.GLFW.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Monitor -> c Monitor # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Monitor # toConstr :: Monitor -> Constr # dataTypeOf :: Monitor -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Monitor) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Monitor) # gmapT :: (forall b. Data b => b -> b) -> Monitor -> Monitor # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Monitor -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Monitor -> r # gmapQ :: (forall d. Data d => d -> u) -> Monitor -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Monitor -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Monitor -> m Monitor # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Monitor -> m Monitor # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Monitor -> m Monitor # | |
Generic Monitor Source # | |
Show Monitor Source # | |
Eq Monitor Source # | |
Ord Monitor Source # | |
C (Ptr C'GLFWmonitor) Monitor Source # | |
Defined in Graphics.UI.GLFW.C | |
type Rep Monitor Source # | |
Defined in Graphics.UI.GLFW.Types type Rep Monitor = D1 ('MetaData "Monitor" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" 'True) (C1 ('MetaCons "Monitor" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMonitor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr C'GLFWmonitor)))) |
data MonitorState Source #
Part of the MonitorCallback
, for when a monitor gets
connected or disconnected.
Instances
See Video Modes
VideoMode | |
|
Instances
Lets you adjust the gamma of a monitor. To ensure that only valid values are created, use makeGammaRamp
.
See Gamma Ramp.
Instances
Data GammaRamp Source # | |
Defined in Graphics.UI.GLFW.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GammaRamp -> c GammaRamp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GammaRamp # toConstr :: GammaRamp -> Constr # dataTypeOf :: GammaRamp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GammaRamp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GammaRamp) # gmapT :: (forall b. Data b => b -> b) -> GammaRamp -> GammaRamp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GammaRamp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GammaRamp -> r # gmapQ :: (forall d. Data d => d -> u) -> GammaRamp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GammaRamp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GammaRamp -> m GammaRamp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GammaRamp -> m GammaRamp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GammaRamp -> m GammaRamp # | |
Generic GammaRamp Source # | |
Read GammaRamp Source # | |
Show GammaRamp Source # | |
NFData GammaRamp Source # | |
Defined in Graphics.UI.GLFW.Types | |
Eq GammaRamp Source # | |
Ord GammaRamp Source # | |
Defined in Graphics.UI.GLFW.Types | |
type Rep GammaRamp Source # | |
Defined in Graphics.UI.GLFW.Types type Rep GammaRamp = D1 ('MetaData "GammaRamp" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" 'False) (C1 ('MetaCons "GammaRamp" 'PrefixI 'True) (S1 ('MetaSel ('Just "gammaRampRed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]) :*: (S1 ('MetaSel ('Just "gammaRampGreen") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]) :*: S1 ('MetaSel ('Just "gammaRampBlue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int])))) |
makeGammaRamp :: [Int] -> [Int] -> [Int] -> Maybe GammaRamp Source #
Smart constructor for a GammaRamp
.
getMonitors :: IO (Maybe [Monitor]) Source #
Gets the list of available monitors, if possible. See glfwGetMonitors
getPrimaryMonitor :: IO (Maybe Monitor) Source #
Gets the primary monitor. See glfwGetPrimaryMonitor
getMonitorPos :: Monitor -> IO (Int, Int) Source #
Gets the position of the specified monitor within the coordinate space. See glfwGetMonitorPos
getMonitorPhysicalSize :: Monitor -> IO (Int, Int) Source #
The physical width and height of the monitor. See glfwGetMonitorPhysicalSize
getMonitorContentScale :: Monitor -> IO (Float, Float) Source #
This function retrieves the content scale for the specified monitor. The content scale is the ratio between the current DPI and the platform's default DPI. See glfwGetMonitorContentScale
getMonitorWorkarea :: Monitor -> IO (Int, Int, Int, Int) Source #
This function returns the position, in screen coordinates, of the upper-left corner of the work area of the specified monitor along with the work area size in screen coordinates. Returned tuple is: (xPos, yPos, width, height) See glfwGetMonitorWorkarea
getMonitorName :: Monitor -> IO (Maybe String) Source #
A human-readable name for the monitor specified. See getMonitorName
setMonitorCallback :: Maybe MonitorCallback -> IO () Source #
Sets a callback for when a monitor is connected or disconnected. See glfwSetMonitorCallback
type MonitorCallback = Monitor -> MonitorState -> IO () Source #
Fires when a monitor is connected or disconnected.
getVideoModes :: Monitor -> IO (Maybe [VideoMode]) Source #
Obtains the possible video modes of the monitor. See glfwGetVideoModes
getVideoMode :: Monitor -> IO (Maybe VideoMode) Source #
Gets the active video mode of the monitor. See glfwGetVideoMode
getGammaRamp :: Monitor -> IO (Maybe GammaRamp) Source #
Gets the gamma ramp in use with the monitor. See glfwGetGammaRamp
setGammaRamp :: Monitor -> GammaRamp -> IO () Source #
Assigns a gamma ramp to use with the given monitor. See glfwSetGammaRamp
Window handling
Represents a GLFW window value. See the Window Guide
Instances
Data Window Source # | |
Defined in Graphics.UI.GLFW.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Window -> c Window # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Window # toConstr :: Window -> Constr # dataTypeOf :: Window -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Window) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Window) # gmapT :: (forall b. Data b => b -> b) -> Window -> Window # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Window -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Window -> r # gmapQ :: (forall d. Data d => d -> u) -> Window -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Window -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Window -> m Window # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Window -> m Window # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Window -> m Window # | |
Generic Window Source # | |
Show Window Source # | |
Eq Window Source # | |
Ord Window Source # | |
C (Ptr C'GLFWwindow) Window Source # | |
Defined in Graphics.UI.GLFW.C | |
type Rep Window Source # | |
Defined in Graphics.UI.GLFW.Types type Rep Window = D1 ('MetaData "Window" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" 'True) (C1 ('MetaCons "Window" 'PrefixI 'True) (S1 ('MetaSel ('Just "unWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr C'GLFWwindow)))) |
data WindowHint Source #
Lets you set various window hints before creating a Window
.
See Window Hints,
particularly Supported and Default Values.
Instances
data WindowAttrib Source #
A window-specific attribute. See Window Attributes
WindowAttrib'Decorated | |
WindowAttrib'Resizable | |
WindowAttrib'Floating | |
WindowAttrib'AutoIconify | |
WindowAttrib'FocusOnShow | |
WindowAttrib'Hovered |
Instances
data ContextRobustness Source #
The OpenGL robustness strategy.
ContextRobustness'NoRobustness | |
ContextRobustness'NoResetNotification | |
ContextRobustness'LoseContextOnReset |
Instances
data OpenGLProfile Source #
The OpenGL profile.
Instances
The type of OpenGL to create a context for.
Instances
data ContextCreationAPI Source #
The type of API to use for context creation. See the Window Guide for more information.
This is a hard constraint. If no client API is requested, this hint is ignored. Best practice is to stick to one API or the other, otherwise may segfault on Linux. OS X does not support the EGL API and will fail if this hint is used.
Instances
data ContextReleaseBehavior Source #
The context release behavior. See the Window Guide for more information.
Context release behaviors are described in detail by the KHR_context_flush_control extension.
Instances
defaultWindowHints :: IO () Source #
Sets all the window hints to default. See glfwDefaultWindowHints
windowHint :: WindowHint -> IO () Source #
Hints something to the GLFW windowing system. See glfwWindowHint and glfwWindowHintString
setWindowAttrib :: Window -> WindowAttrib -> Bool -> IO () Source #
Sets the value of an attribute of the specified window. See glfwSetWindowAttrib
getWindowAttrib :: Window -> WindowAttrib -> IO Bool Source #
Returns the value of an attribute of the specified window or its OpenGL or OpenGL ES context. See glfwGetWindowAttrib
:: Int | Desired width for the window. |
-> Int | Desired height for the window. |
-> String | Desired title for the window. |
-> Maybe Monitor | Monitor to use in fullscreen mode. |
-> Maybe Window | Window for context object sharing, see here. |
-> IO (Maybe Window) |
Creates a new window.
Note: If running in GHCI don't forget to :set -fno-ghci-sandbox
or you
may run into an assertion failure, segfault or other nasty crash.
See glfwCreateWindow
destroyWindow :: Window -> IO () Source #
Cleans up a window and all associated resources See glfwDestroyWindow. This function is not reentrant.
windowShouldClose :: Window -> IO Bool Source #
If the window should close or not. See glfwWindowShouldClose
setWindowShouldClose :: Window -> Bool -> IO () Source #
Sets if the window should close or not. See glfwSetWindowShouldClose
getWindowOpacity :: Window -> IO Float Source #
Returns the opacity of the window, including any decorations. See <https://www.glfw.org/docs/3.3/group__window.html#gad09f0bd7a6307c4533b7061828480a84 glfwGetWindowOpacity
setWindowOpacity :: Window -> Float -> IO () Source #
Sets the opacity of the window, including any decorations See glfwSetWindowOpacity
setWindowTitle :: Window -> String -> IO () Source #
Sets the Title string of the window. See glfwSetWindowTitle
getWindowPos :: Window -> IO (Int, Int) Source #
Gets the window's position (in screen coordinates). See glfwGetWindowPos
setWindowPos :: Window -> Int -> Int -> IO () Source #
Sets the window's position (in screen coordinates). See glfwSetWindowPos
getWindowSize :: Window -> IO (Int, Int) Source #
Gets the size of the window (in screen coordinates). See glfwGetWindowSize
setWindowSize :: Window -> Int -> Int -> IO () Source #
Sets the size of the client area for the window (in screen coordinates). See glfwSetWindowSize
:: Window | |
-> Maybe Int | The minimum width, in screen coordinates, of the client area. |
-> Maybe Int | The minimum height, in screen coordinates, of the client area. |
-> Maybe Int | The maximum width, in screen coordinates, of the client area. |
-> Maybe Int | The maximum height, in screen coordinates, of the client area. |
-> IO () |
Sets the size limits of the client area of the specified window. If the
window is full screen, the size limits only take effect once it is made
windowed. If the window is not resizable this function does nothing. Pass
Nothing
in any argument to disable the limit.
See glfwSetWindowSizeLimits
setWindowAspectRatio :: Window -> Maybe (Int, Int) -> IO () Source #
Sets the required aspect ratio of the client area of the specified window. Pass Nothing to disable the limit. See glfwSetWindowAspectRatio
getWindowFrameSize :: Window -> IO (Int, Int, Int, Int) Source #
Gets the size of the frame around the window (in screen coordinates). This
size includes the title bar, if the window has one. Not to be confused with
getFramebufferSize
, which gets the size of the rendering area.
See glfwGetWindowFrameSize
getWindowContentScale :: Window -> IO (Float, Float) Source #
This function retrieves the content scale for the specified window. The content scale is the ratio between the current DPI and the platform's default DPI. See glfwGetWindowContentScale
getFramebufferSize :: Window -> IO (Int, Int) Source #
The size of the framebuffer (in Pixels) See glfwGetFramebufferSize
setWindowIcon :: Window -> [Image] -> IO () Source #
Sets the icon of the specified window. The system will try to find the image with the dimensions closest to the ones required by the platform. This image is then scaled and used as the icon for that size. Good sizes are 16x16, 32x32, and 48x48. Pass the empty list to reset to the default icon. Has no effect on OS X (See the Bundle Programming Guide)
iconifyWindow :: Window -> IO () Source #
Iconifies (minimizes) the window. See glfwIconifyWindow
restoreWindow :: Window -> IO () Source #
Restores the window from an iconified/minimized state. See glfwRestoreWindow
focusWindow :: Window -> IO () Source #
Brings the specified window to front and sets input focus. The window should already be visible and not iconified. See glfwFocusWindow
maximizeWindow :: Window -> IO () Source #
Maximizes the specified window if it was not already maximized. See glfwMaximizeWindow
showWindow :: Window -> IO () Source #
Shows the window. See glfwShowWindow
hideWindow :: Window -> IO () Source #
Hides the window. See glfwHideWindow
requestWindowAttention :: Window -> IO () Source #
Requests user attention to the specified window. See glfwRequestWindowAttention
getWindowMonitor :: Window -> IO (Maybe Monitor) Source #
Gets the monitor that this window is running on, provided the window is fullscreen. See glfwGetWindowMonitor
setCursorPos :: Window -> Double -> Double -> IO () Source #
Sets the position of the cursor within the window. See glfwSetCursorPos
setFullscreen :: Window -> Monitor -> VideoMode -> IO () Source #
Makes a window fullscreen on the given monitor. The number of red, green,
and blue bits is ignored. Note, this shouldn't be used to update the
resolution of a fullscreen window. Use setWindowSize
instead.
See glfwSetWindowMonitor
:: Window | |
-> Int | The width of the client area |
-> Int | The height of the client area |
-> Int | The x position of the window |
-> Int | The y position of the window |
-> IO () |
Updates a window to be windowed instead of fullscreen. Note, this shouldn't
be used to update the position or size of a window. Use setWindowPos
and
setWindowSize
instead.
See glfwSetWindowMonitor
getWindowFocused :: Window -> IO Bool Source #
If the window has focus or not. See glfwGetWindowAttrib
getWindowMaximized :: Window -> IO Bool Source #
If the window is maximized or not. See glfwGetWindowAttrib
getWindowFloating :: Window -> IO Bool Source #
If the window has been set to be 'always on top' or not. See glfwGetWindowAttrib
getWindowIconified :: Window -> IO Bool Source #
If the window is iconified (minimized) or not. See glfwGetWindowAttrib
getWindowResizable :: Window -> IO Bool Source #
If the window is resizable or not. See glfwGetWindowAttrib
getWindowDecorated :: Window -> IO Bool Source #
If the window is decorated or not. See glfwGetWindowAttrib
getWindowVisible :: Window -> IO Bool Source #
If the window is visible or not. See glfwGetWindowAttrib
getWindowClientAPI :: Window -> IO ClientAPI Source #
The client api for this window. See glfwGetWindowAttrib
getWindowContextCreationAPI :: Window -> IO ContextCreationAPI Source #
Returns the context creation API used to create the specified window. See glfwGetWindowAttrib
getWindowContextVersionMajor :: Window -> IO Int Source #
The context's "major" version, x.0.0 See glfwGetWindowAttrib
getWindowContextVersionMinor :: Window -> IO Int Source #
The context's "minor" version, 0.y.0 See glfwGetWindowAttrib
getWindowContextVersionRevision :: Window -> IO Int Source #
The context's "revision" version, 0.0.z See glfwGetWindowAttrib
getWindowContextRobustness :: Window -> IO ContextRobustness Source #
The context robustness of this window. See glfwGetWindowAttrib
getWindowContextReleaseBehavior :: Window -> IO ContextReleaseBehavior Source #
Returns the context release behavior. See glfwGetWindowAttrib
getWindowContextNoError :: Window -> IO Bool Source #
Returns true if the window is set to NO_ERROR (see the KHR_no_error extension.
getWindowOpenGLForwardCompat :: Window -> IO Bool Source #
If this window is set for opengl to be forward compatible. See glfwGetWindowAttrib
getWindowOpenGLDebugContext :: Window -> IO Bool Source #
If the window has an opengl debug context See glfwGetWindowAttrib
getWindowOpenGLProfile :: Window -> IO OpenGLProfile Source #
Obtains the current opengl profile. See glfwGetWindowAttrib
setWindowPosCallback :: Window -> Maybe WindowPosCallback -> IO () Source #
Sets the callback to use when the window position changes. See glfwSetWindowPosCallback
type WindowPosCallback = Window -> Int -> Int -> IO () Source #
Fires when the window position changes.
setWindowSizeCallback :: Window -> Maybe WindowSizeCallback -> IO () Source #
Sets the callback to use when the window's size changes. See glfwSetWindowSizeCallback
type WindowSizeCallback = Window -> Int -> Int -> IO () Source #
Fires when the window is resized (in Screen Coordinates, which might not map 1:1 with pixels).
setWindowCloseCallback :: Window -> Maybe WindowCloseCallback -> IO () Source #
Sets the callback to use when the user attempts to close the window. See glfwSetWindowCloseCallback
type WindowCloseCallback = Window -> IO () Source #
Fires when the user is attempting to close the window
setWindowRefreshCallback :: Window -> Maybe WindowRefreshCallback -> IO () Source #
Sets the callback to use when the window's data is partly dead and it should refresh. See glfwSetWindowRefreshCallback
type WindowRefreshCallback = Window -> IO () Source #
Fires when the contents of the window are damaged and they must be refreshed.
setWindowFocusCallback :: Window -> Maybe WindowFocusCallback -> IO () Source #
Sets the callback to use when the window gains or loses focus. See glfwSetWindowFocusCallback
type WindowFocusCallback = Window -> Bool -> IO () Source #
Fires when the window gains or loses input focus.
setWindowIconifyCallback :: Window -> Maybe WindowIconifyCallback -> IO () Source #
Sets the callback to use when the window is iconified or not (aka, minimized or not). See glfwSetWindowIconifyCallback
type WindowIconifyCallback = Window -> Bool -> IO () Source #
Fires when the window is iconified (minimized) or not.
setFramebufferSizeCallback :: Window -> Maybe FramebufferSizeCallback -> IO () Source #
Sets the callback to use when the framebuffer's size changes. See glfwSetFramebufferSizeCallback
type FramebufferSizeCallback = Window -> Int -> Int -> IO () Source #
Fires when the size of the framebuffer for the window changes (in Pixels).
setWindowContentScaleCallback :: Window -> Maybe WindowContentScaleCallback -> IO () Source #
Sets the callback for when the content scale of the window changes. See Window Content Scale
type WindowContentScaleCallback = Window -> Float -> Float -> IO () Source #
Fires when a window is rescaled
setWindowMaximizeCallback :: Window -> Maybe WindowMaximizeCallback -> IO () Source #
Sets the maximization callback of the specified window, which is called when the window is maximized or restored. See Window maximization
type WindowMaximizeCallback = Window -> Bool -> IO () Source #
Fires when a window is maximized or restored. Returns True if the window was maximized and False if the window was restored.
pollEvents :: IO () Source #
Checks for any pending events, processes them, and then immediately returns. This is most useful for continual rendering, such as games. See the Event Processing Guide. This function is not reentrant.
waitEvents :: IO () Source #
Waits until at least one event is in the queue then processes the queue and returns. Requires at least one window to be active for it to sleep. This saves a lot of CPU, and is better if you're doing only periodic rendering, such as with an editor program. See the Event Processing Guide. This function is not reentrant.
waitEventsTimeout :: Double -> IO () Source #
Same as waitEvents
, with a timeout after which the function returns.
See the Event Processing Guide. This
function is not reentrant.
postEmptyEvent :: IO () Source #
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
Input handling
Part of the Keyboard Input system.
Instances
Data Key Source # | |
Defined in Graphics.UI.GLFW.Types 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 # 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 :: forall r r'. (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 # | |
Bounded Key Source # | |
Enum Key Source # | |
Generic Key Source # | |
Read Key Source # | |
Show Key Source # | |
NFData Key Source # | |
Defined in Graphics.UI.GLFW.Types | |
Eq Key Source # | |
Ord Key Source # | |
C CInt Key Source # | |
type Rep Key Source # | |
Defined in Graphics.UI.GLFW.Types type Rep Key = D1 ('MetaData "Key" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" '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)))))))) |
The state of an individual key when getKey
is called.
Instances
Data KeyState Source # | |
Defined in Graphics.UI.GLFW.Types 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 :: forall r r'. (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 # | |
Bounded KeyState Source # | |
Enum KeyState Source # | |
Generic KeyState Source # | |
Read KeyState Source # | |
Show KeyState Source # | |
NFData KeyState Source # | |
Defined in Graphics.UI.GLFW.Types | |
Eq KeyState Source # | |
Ord KeyState Source # | |
Defined in Graphics.UI.GLFW.Types | |
C CInt KeyState Source # | |
type Rep KeyState Source # | |
Defined in Graphics.UI.GLFW.Types type Rep KeyState = D1 ('MetaData "KeyState" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" '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))) |
For use with the Joystick Input system.
Joystick'1 | |
Joystick'2 | |
Joystick'3 | |
Joystick'4 | |
Joystick'5 | |
Joystick'6 | |
Joystick'7 | |
Joystick'8 | |
Joystick'9 | |
Joystick'10 | |
Joystick'11 | |
Joystick'12 | |
Joystick'13 | |
Joystick'14 | |
Joystick'15 | |
Joystick'16 |
Instances
Data Joystick Source # | |
Defined in Graphics.UI.GLFW.Types 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 :: forall r r'. (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 # | |
Bounded Joystick Source # | |
Enum Joystick Source # | |
Generic Joystick Source # | |
Read Joystick Source # | |
Show Joystick Source # | |
NFData Joystick Source # | |
Defined in Graphics.UI.GLFW.Types | |
Eq Joystick Source # | |
Ord Joystick Source # | |
Defined in Graphics.UI.GLFW.Types | |
C CInt Joystick Source # | |
type Rep Joystick Source # | |
Defined in Graphics.UI.GLFW.Types type Rep Joystick = D1 ('MetaData "Joystick" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" '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 JoystickState Source #
Part of the JoystickCallback
, for when a monitor gets
connected or disconnected.
Instances
data JoystickButtonState Source #
If a given joystick button is pressed or not when
getJoystickButtons
is called.
Instances
data MouseButton Source #
Part of the Mouse Input system.
MouseButton'1 | |
MouseButton'2 | |
MouseButton'3 | |
MouseButton'4 | |
MouseButton'5 | |
MouseButton'6 | |
MouseButton'7 | |
MouseButton'8 |
Instances
data MouseButtonState Source #
If the mouse button is pressed or not when getMouseButton
is
called.
Instances
data CursorState Source #
If the mouse's cursor is in the window or not.
Instances
data CursorInputMode Source #
Allows for special forms of mouse input. See Cursor Modes
Instances
data StickyKeysInputMode Source #
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
data StickyMouseButtonsInputMode Source #
This is the mouse version of StickyKeysInputMode.
Instances
data ModifierKeys Source #
Modifier keys that were pressed as part of another keypress event.
ModifierKeys | |
|
Instances
data GamepadButton Source #
The different types of buttons we can find on a Gamepad.
Instances
data GamepadAxis Source #
The different axes along which we can measure continuous input on a Gamepad
GamepadAxis'LeftX | |
GamepadAxis'LeftY | |
GamepadAxis'RightX | |
GamepadAxis'RightY | |
GamepadAxis'LeftTrigger | |
GamepadAxis'RightTrigger |
Instances
data GamepadButtonState Source #
The states in which the gamepad buttons are found
Instances
data GamepadState Source #
This describes the input state of a gamepad
GamepadState | |
|
Instances
Generic GamepadState Source # | |
Defined in Graphics.UI.GLFW.Types type Rep GamepadState :: Type -> Type # from :: GamepadState -> Rep GamepadState x # to :: Rep GamepadState x -> GamepadState # | |
NFData GamepadState Source # | |
Defined in Graphics.UI.GLFW.Types rnf :: GamepadState -> () # | |
Eq GamepadState Source # | |
Defined in Graphics.UI.GLFW.Types (==) :: GamepadState -> GamepadState -> Bool # (/=) :: GamepadState -> GamepadState -> Bool # | |
type Rep GamepadState Source # | |
Defined in Graphics.UI.GLFW.Types type Rep GamepadState = D1 ('MetaData "GamepadState" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" 'False) (C1 ('MetaCons "GamepadState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getButtonState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GamepadButton -> GamepadButtonState)) :*: S1 ('MetaSel ('Just "getAxisState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GamepadAxis -> Float)))) |
GLFW image data, for setting up custom mouse cursor appearnaces.
Instances
Data Image Source # | |
Defined in Graphics.UI.GLFW.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Image -> c Image # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Image # dataTypeOf :: Image -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Image) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image) # gmapT :: (forall b. Data b => b -> b) -> Image -> Image # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r # gmapQ :: (forall d. Data d => d -> u) -> Image -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Image -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Image -> m Image # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image # | |
Generic Image Source # | |
Read Image Source # | |
Show Image Source # | |
NFData Image Source # | |
Defined in Graphics.UI.GLFW.Types | |
Eq Image Source # | |
Ord Image Source # | |
type Rep Image Source # | |
Defined in Graphics.UI.GLFW.Types type Rep Image = D1 ('MetaData "Image" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" 'False) (C1 ('MetaCons "Image" 'PrefixI 'True) (S1 ('MetaSel ('Just "imageWidth") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "imageHeight") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "imagePixels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CUChar])))) |
mkImage :: Int -> Int -> (Int -> Int -> (Word8, Word8, Word8, Word8)) -> Image Source #
Create an image given the function to generate 8-bit RGBA values based on the pixel location.
Represents a GLFW cursor.
Instances
Data Cursor Source # | |
Defined in Graphics.UI.GLFW.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cursor -> c Cursor # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cursor # toConstr :: Cursor -> Constr # dataTypeOf :: Cursor -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cursor) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cursor) # gmapT :: (forall b. Data b => b -> b) -> Cursor -> Cursor # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cursor -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cursor -> r # gmapQ :: (forall d. Data d => d -> u) -> Cursor -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Cursor -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cursor -> m Cursor # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cursor -> m Cursor # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cursor -> m Cursor # | |
Generic Cursor Source # | |
Show Cursor Source # | |
Eq Cursor Source # | |
Ord Cursor Source # | |
type Rep Cursor Source # | |
Defined in Graphics.UI.GLFW.Types type Rep Cursor = D1 ('MetaData "Cursor" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.0-K2q0hvgXVju4vqklfjfJpZ" 'True) (C1 ('MetaCons "Cursor" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCursor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Ptr C'GLFWcursor)))) |
data StandardCursorShape Source #
Lets you use one of the standard cursor appearnaces that the local system theme provides for. See Standard Cursor Creation.
StandardCursorShape'Arrow | |
StandardCursorShape'IBeam | |
StandardCursorShape'Crosshair | |
StandardCursorShape'Hand | |
StandardCursorShape'HResize | |
StandardCursorShape'VResize |
Instances
getCursorInputMode :: Window -> IO CursorInputMode Source #
Gets the current cursor input mode. See glfwSetInputMode
setCursorInputMode :: Window -> CursorInputMode -> IO () Source #
Set the cursor input mode. See glfwSetInputMode
getRawMouseMotion :: Window -> IO Bool Source #
Returns whether or not we've currently enabled raw mouse motion. See Raw Mouse Motion
setRawMouseMotion :: Window -> Bool -> IO () Source #
Sets the cursor to receive raw input, if available (See rawMouseMotionSupported and Raw Mouse Motion
getStickyKeysInputMode :: Window -> IO StickyKeysInputMode Source #
Gets the current sticky keys mode. See glfwSetInputMode
setStickyKeysInputMode :: Window -> StickyKeysInputMode -> IO () Source #
Sets if sticky keys should be used or not. See glfwSetInputMode
getStickyMouseButtonsInputMode :: Window -> IO StickyMouseButtonsInputMode Source #
Gets if sticky mouse buttons are on or not. See glfwSetInputMode
setStickyMouseButtonsInputMode :: Window -> StickyMouseButtonsInputMode -> IO () Source #
Sets if sticky mouse buttons should be used or not. See glfwSetInputMode
getKey :: Window -> Key -> IO KeyState Source #
Gets the state of the specified key. If Stickey Keys isn't enabled then it's possible for keyboard polling to miss individual key presses. Use the callback to avoid this. See glfwGetKey
getKeyName :: Key -> Int -> IO (Maybe String) Source #
Returns the localized name of the specified printable key. This is intended
for displaying key bindings to the user. The scancode is used if the provided
Key
isn't printable. If the scancode maps to a non-printable key as well,
then Nothing
is returned.
See glfwGetKeyName
getKeyScancode :: Key -> IO Int Source #
This function returns the platform-specific scancode of the specified key. See glfwGetKeyScancode
getMouseButton :: Window -> MouseButton -> IO MouseButtonState Source #
Gets the state of a single specified mouse button. If sticky mouse button mode isn't enabled it's possible for mouse polling to miss individual mouse events. Use the call back to avoid this. See glfwGetMouseButton
getCursorPos :: Window -> IO (Double, Double) Source #
Returns the position, in screen coodinates, relative to the upper left.
If the CursorInputMode
is "disabled", then results are unbounded by the window size.
See glfwGetCursorPos
setKeyCallback :: Window -> Maybe KeyCallback -> IO () Source #
Assigns the given callback to use for all keyboard presses and repeats. See glfwSetKeyCallback
type KeyCallback = Window -> Key -> Int -> KeyState -> ModifierKeys -> IO () Source #
Fires for each press or repeat of keyboard keys (regardless of if it has textual meaning or not, eg Shift)
setCharCallback :: Window -> Maybe CharCallback -> IO () Source #
Sets the callback to use when the user types a character See glfwSetCharCallback
type CharCallback = Window -> Char -> IO () Source #
Fires when a complete character codepoint is typed by the user, Shift then "b" generates B.
setCharModsCallback :: Window -> Maybe CharModsCallback -> IO () Source #
Sets the callback to use with Unicode characters regardless of what modifier keys are used. See glfwSetCharModsCallback
type CharModsCallback = Window -> Char -> ModifierKeys -> IO () Source #
Similar to CharCallback
, fires when a complete unicode codepoint is typed by the user.
setMouseButtonCallback :: Window -> Maybe MouseButtonCallback -> IO () Source #
Assigns the callback to run whenver a mouse button is clicked. See glfwSetMouseButtonCallback
type MouseButtonCallback = Window -> MouseButton -> MouseButtonState -> ModifierKeys -> IO () Source #
Fires whenever a mouse button is clicked.
setCursorPosCallback :: Window -> Maybe CursorPosCallback -> IO () Source #
Assigns the callback to run whenver the cursor position changes. See glfwSetCursorPosCallback
type CursorPosCallback = Window -> Double -> Double -> IO () Source #
Fires every time the cursor position changes. Sub-pixel accuracy is used, when available.
setCursorEnterCallback :: Window -> Maybe CursorEnterCallback -> IO () Source #
Sets the callback for when the cursor enters or leaves the client area. See Cursor Enter/Leave Events
type CursorEnterCallback = Window -> CursorState -> IO () Source #
Fires when the cursor enters or exits the client area of the window.
:: 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.
createStandardCursor :: StandardCursorShape -> IO Cursor Source #
Creates a cursor with a standard shape that can be set for a window with setCursor.
setCursor :: Window -> Cursor -> IO () Source #
Sets the cursor image to be used when the cursor is over the client area
of the specified window. The set cursor will only be visible when the cursor
mode of the window is GLFW_CURSOR_NORMAL
.
destroyCursor :: Cursor -> IO () Source #
Destroys a cursor previously created with createCursor
. Any remaining
cursors will be destroyed by terminate
. This function is not
reentrant.
setScrollCallback :: Window -> Maybe ScrollCallback -> IO () Source #
Sets the callback to run when the user scrolls with the mouse wheel or a touch gesture. See Scroll Input
type ScrollCallback = Window -> Double -> Double -> IO () Source #
Fires when the user scrolls the mouse wheel or via touch gesture.
setDropCallback :: Window -> Maybe DropCallback -> IO () Source #
Sets the file drop callback of the specified window, which is called when one or more dragged files are dropped on the window.
type DropCallback Source #
A callback that allows for drag and drop support.
joystickPresent :: Joystick -> IO Bool Source #
Tests if the joystick is present at all See glfwJoystickPresent
joystickIsGamepad :: Joystick -> IO Bool Source #
This function returns whether the specified joystick is both present and has a gamepad mapping. See glfwJoystickIsGamepad
getJoystickAxes :: Joystick -> IO (Maybe [Double]) Source #
Returns the values of all axes of the specified joystick, normalized to between -1.0 and 1.0 See glfwGetJoystickAxes
getJoystickButtons :: Joystick -> IO (Maybe [JoystickButtonState]) Source #
Returns a list of all joystick button states for the specified joystick. See glfwGetJoystickButtons
getJoystickHats :: Joystick -> IO (Maybe [JoystickHatState]) Source #
Returns a list of all hats of the specified joystick. See glfwGetJoystickHats
data JoystickHatState Source #
The valid hat states of a joystick. Part of the joystick hat system.
Instances
getJoystickName :: Joystick -> IO (Maybe String) Source #
A human-readable name for a Joystick. Not guranteed to be unique. See glfwGetJoystickName
getJoystickGUID :: Joystick -> IO (Maybe String) Source #
This function returns the SDL compatible GUID of the specified joystick. See glfwGetJoystickGUID
setJoystickCallback :: Maybe JoystickCallback -> IO () Source #
Sets a callback for when a joystick is connected or disconnected. See glfwSetJoystickCallback
type JoystickCallback = Joystick -> JoystickState -> IO () Source #
Fires when a joystick is connected or disconnected.
getGamepadName :: Joystick -> IO (Maybe String) Source #
This function returns the human-readable name of the gamepad from the gamepad mapping assigned to the specified joystick. See glfwGetGamepadName
getGamepadState :: Joystick -> IO (Maybe GamepadState) Source #
This function retrives the state of the specified joystick remapped to an Xbox-like gamepad. See glfwGetGamepadState
updateGamepadMappings :: String -> IO Bool Source #
Adds the specified SDL_GameControllerDB gamepad mappings. See glfwUpdateGamepadMappings
Time
getTime :: IO (Maybe Double) Source #
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
setTime :: Double -> IO () Source #
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
getTimerValue :: IO Word64 Source #
Returns the current value of the raw timer, measured in 1 / frequency seconds. The frequency can be queried using getTimerFrequency. See Timer input
getTimerFrequency :: IO Word64 Source #
Returns the frequency, in Hz, of the raw timer. See Timer input
Context
makeContextCurrent :: Maybe Window -> IO () Source #
Makes the context of the specified window the current one for the calling thread. A context can only be made current on a single thread at a time, and each thread can have only a single current context at a time. See glfwMakeContextCurrent
getCurrentContext :: IO (Maybe Window) Source #
Obtains which window owns the current context of the calling thread. See glfwGetCurrentContext
swapBuffers :: Window -> IO () Source #
Swaps the front and back buffers of the window. See glfwSwapBuffers
swapInterval :: Int -> IO () Source #
Sets the number of screen updates that the GPU should wait after swapBuffers
before actually swapping the buffers.
Generates Error'NoCurrentContext
if no context is current.
See glfwSwapInterval
extensionSupported :: String -> IO Bool Source #
If the current OpenGL or OpenGL ES context supports the extension specified.
Generates Error'NoCurrentContext
if no context is current.
See glfwExtensionSupported
Clipboard
getClipboardString :: Window -> IO (Maybe String) Source #
Obtains the contents of the system keyboard, if possible.
Generates Error'FormatUnavailable
if the system clipboard is empty or if it's not a UTF-8 string.
See glfwGetClipboardString
setClipboardString :: Window -> String -> IO () Source #
The window that will own the clipboard contents, and also the clipboard string. See glfwSetClipboardString
Vulkan-related functions
vulkanSupported :: IO Bool Source #
This function returns whether the Vulkan loader has been found.
This check is performed by init
.
getInstanceProcAddress Source #
:: Ptr vkInstance | VkInstance. Note, the returned function must be used with the same instance or its child. |
-> String | Function name |
-> IO (FunPtr vkProc) |
Returns the address of the specified Vulkan instance function.
getPhysicalDevicePresentationSupport Source #
:: Ptr vkInstance | VkInstance |
-> Ptr vkPhysicalDevice | VkPhysicalDevice |
-> Word32 | Index of a queue family to query.
This is an index in the array returned by
|
-> IO Bool |
Returns whether the specified queue family can present images.
:: Enum vkResult | |
=> Ptr vkInstance | VkInstance |
-> Window | GLFWwindow *window |
-> Ptr vkAllocationCallbacks | const VkAllocationCallbacks *allocator |
-> Ptr vkSurfaceKHR | VkSurfaceKHR *surface |
-> IO vkResult |
Creates a Vulkan surface for the specified window
Native access functions
The low level native-access bindings are exposed here via bindings-GLFW.
These must be enabled with the ExposeNative
flag passed to bindings-GLFW.
The return values of these functions are used as a best-guess and are not
coupled with any other implementation. They should be used with caution
and at your own risk.
getX11Window :: Window -> IO Word64 Source #
See glfwGetX11Window
setX11SelectionString :: String -> IO () Source #
getGLXWindow :: Window -> IO Word64 Source #
See glfwGetGLXWindow
getWaylandDisplay :: IO (Ptr wl_display) Source #
getEGLDisplay :: IO (Ptr ()) Source #
getOSMesaColorBuffer :: Window -> IO (Maybe OSMesaColorBuffer) Source #
Returns the color buffer of the offscreen context provided by OSMesa. The color buffer is returned as an array whose integers are unsigned and represent the (R, G, B, A) values. For formats that do not have alpha, A will always be 255.
type OSMesaColorBuffer = Array (Int, Int) OSMesaRGBA Source #
A color buffer is a two dimensional array of RGBA values. The first dimension is width, and the second is height.
TODO: It's a shame this is an Array and not a UArray.
type OSMesaRGBA = (Word8, Word8, Word8, Word8) Source #
An RGBA type is a low-dynamic range representation of a color, represented by a 32-bit value. The channels here are in order: R, G, B, A
getOSMesaDepthBuffer :: Window -> IO (Maybe (OSMesaDepthBuffer, Word32)) Source #
Returns the depth buffer and maximum depth value of the offscreen render target that's provided by OSMesa.