GLFW-b-1.4.8.4: Bindings to GLFW OpenGL library

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.GLFW

Contents

Description

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

Error handling

data Error Source #

An enum for one of the GLFW error codes.

Instances

Bounded Error Source # 
Enum Error Source # 
Eq Error Source # 

Methods

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

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

Data Error Source # 

Methods

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 #

toConstr :: Error -> Constr #

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 :: (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 #

Ord Error Source # 

Methods

compare :: Error -> Error -> Ordering #

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

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

(>) :: Error -> Error -> Bool #

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

max :: Error -> Error -> Error #

min :: Error -> Error -> Error #

Read Error Source # 
Show Error Source # 

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Generic Error Source # 

Associated Types

type Rep Error :: * -> * #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

NFData Error Source # 

Methods

rnf :: Error -> () #

type Rep Error Source # 
type Rep Error = D1 * (MetaData "Error" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Error'NotInitialized" PrefixI False) (U1 *)) (C1 * (MetaCons "Error'NoCurrentContext" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Error'InvalidEnum" PrefixI False) (U1 *)) (C1 * (MetaCons "Error'InvalidValue" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Error'OutOfMemory" PrefixI False) (U1 *)) (C1 * (MetaCons "Error'ApiUnavailable" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Error'VersionUnavailable" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Error'PlatformError" PrefixI False) (U1 *)) (C1 * (MetaCons "Error'FormatUnavailable" PrefixI False) (U1 *))))))

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

data Version Source #

The library version of the GLFW implementation in use. See Version Management

Constructors

Version 

Instances

Eq Version Source # 

Methods

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

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

Data Version Source # 

Methods

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 :: (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 #

Ord Version Source # 
Read Version Source # 
Show Version Source # 
Generic Version Source # 

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

NFData Version Source # 

Methods

rnf :: Version -> () #

type Rep Version Source # 
type Rep Version = D1 * (MetaData "Version" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) (C1 * (MetaCons "Version" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "versionMajor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "versionMinor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "versionRevision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))))

init :: IO Bool Source #

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

terminate :: IO () Source #

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

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

Monitor handling

data Monitor Source #

Represents a physical monitor that's currently connected. See the Monitor Guide

Instances

Eq Monitor Source # 

Methods

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

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

Data Monitor Source # 

Methods

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 :: (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 #

Ord Monitor Source # 
Show Monitor Source # 
Generic Monitor Source # 

Associated Types

type Rep Monitor :: * -> * #

Methods

from :: Monitor -> Rep Monitor x #

to :: Rep Monitor x -> Monitor #

type Rep Monitor Source # 
type Rep Monitor = D1 * (MetaData "Monitor" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" True) (C1 * (MetaCons "Monitor" PrefixI True) (S1 * (MetaSel (Just Symbol "unMonitor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Ptr C'GLFWmonitor))))

data MonitorState Source #

Part of the MonitorCallback, for when a monitor gets connected or disconnected.

Instances

Eq MonitorState Source # 
Data MonitorState Source # 

Methods

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

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

toConstr :: MonitorState -> Constr #

dataTypeOf :: MonitorState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MonitorState Source # 
Read MonitorState Source # 
Show MonitorState Source # 
Generic MonitorState Source # 

Associated Types

type Rep MonitorState :: * -> * #

NFData MonitorState Source # 

Methods

rnf :: MonitorState -> () #

type Rep MonitorState Source # 
type Rep MonitorState = D1 * (MetaData "MonitorState" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "MonitorState'Connected" PrefixI False) (U1 *)) (C1 * (MetaCons "MonitorState'Disconnected" PrefixI False) (U1 *)))

data VideoMode Source #

Instances

Eq VideoMode Source # 
Data VideoMode Source # 

Methods

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

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

toConstr :: VideoMode -> Constr #

dataTypeOf :: VideoMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord VideoMode Source # 
Read VideoMode Source # 
Show VideoMode Source # 
Generic VideoMode Source # 

Associated Types

type Rep VideoMode :: * -> * #

NFData VideoMode Source # 

Methods

rnf :: VideoMode -> () #

type Rep VideoMode Source # 
type Rep VideoMode = D1 * (MetaData "VideoMode" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) (C1 * (MetaCons "VideoMode" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "videoModeWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "videoModeHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "videoModeRedBits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))) ((:*:) * (S1 * (MetaSel (Just Symbol "videoModeGreenBits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "videoModeBlueBits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "videoModeRefreshRate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))))

data GammaRamp Source #

Lets you adjust the gamma of a monitor. To ensure that only valid values are created, use makeGammaRamp. See Gamma Ramp.

Instances

Eq GammaRamp Source # 
Data GammaRamp Source # 

Methods

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 :: (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 #

Ord GammaRamp Source # 
Read GammaRamp Source # 
Show GammaRamp Source # 
Generic GammaRamp Source # 

Associated Types

type Rep GammaRamp :: * -> * #

NFData GammaRamp Source # 

Methods

rnf :: GammaRamp -> () #

type Rep GammaRamp Source # 
type Rep GammaRamp = D1 * (MetaData "GammaRamp" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) (C1 * (MetaCons "GammaRamp" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "gammaRampRed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Int])) ((:*:) * (S1 * (MetaSel (Just Symbol "gammaRampGreen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Int])) (S1 * (MetaSel (Just Symbol "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

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

setGamma :: Monitor -> Double -> IO () Source #

Sets the gamma of a monitor. See glfwSetGamma

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

data Window Source #

Reprisents a GLFW window value. See the Window Guide

Instances

Eq Window Source # 

Methods

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

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

Data Window Source # 

Methods

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 :: (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 #

Ord Window Source # 
Show Window Source # 
Generic Window Source # 

Associated Types

type Rep Window :: * -> * #

Methods

from :: Window -> Rep Window x #

to :: Rep Window x -> Window #

type Rep Window Source # 
type Rep Window = D1 * (MetaData "Window" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" True) (C1 * (MetaCons "Window" PrefixI True) (S1 * (MetaSel (Just Symbol "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

Eq WindowHint Source # 
Data WindowHint Source # 

Methods

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

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

toConstr :: WindowHint -> Constr #

dataTypeOf :: WindowHint -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WindowHint Source # 
Read WindowHint Source # 
Show WindowHint Source # 
Generic WindowHint Source # 

Associated Types

type Rep WindowHint :: * -> * #

NFData WindowHint Source # 

Methods

rnf :: WindowHint -> () #

type Rep WindowHint Source # 
type Rep WindowHint = D1 * (MetaData "WindowHint" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "WindowHint'Resizable" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:+:) * (C1 * (MetaCons "WindowHint'Visible" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) (C1 * (MetaCons "WindowHint'Decorated" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))) ((:+:) * (C1 * (MetaCons "WindowHint'RedBits" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:+:) * (C1 * (MetaCons "WindowHint'GreenBits" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "WindowHint'BlueBits" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "WindowHint'AlphaBits" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:+:) * (C1 * (MetaCons "WindowHint'DepthBits" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "WindowHint'StencilBits" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))) ((:+:) * (C1 * (MetaCons "WindowHint'AccumRedBits" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:+:) * (C1 * (MetaCons "WindowHint'AccumGreenBits" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "WindowHint'AccumBlueBits" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "WindowHint'AccumAlphaBits" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:+:) * (C1 * (MetaCons "WindowHint'AuxBuffers" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "WindowHint'Samples" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))) ((:+:) * (C1 * (MetaCons "WindowHint'RefreshRate" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) ((:+:) * (C1 * (MetaCons "WindowHint'Stereo" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) (C1 * (MetaCons "WindowHint'sRGBCapable" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))) ((:+:) * ((:+:) * (C1 * (MetaCons "WindowHint'ClientAPI" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ClientAPI))) ((:+:) * (C1 * (MetaCons "WindowHint'ContextVersionMajor" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))) (C1 * (MetaCons "WindowHint'ContextVersionMinor" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int))))) ((:+:) * ((:+:) * (C1 * (MetaCons "WindowHint'ContextRobustness" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ContextRobustness))) (C1 * (MetaCons "WindowHint'OpenGLForwardCompat" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))) ((:+:) * (C1 * (MetaCons "WindowHint'OpenGLDebugContext" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) (C1 * (MetaCons "WindowHint'OpenGLProfile" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * OpenGLProfile))))))))

data FocusState Source #

For use with the focus callback.

Instances

Bounded FocusState Source # 
Enum FocusState Source # 
Eq FocusState Source # 
Data FocusState Source # 

Methods

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

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

toConstr :: FocusState -> Constr #

dataTypeOf :: FocusState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FocusState Source # 
Read FocusState Source # 
Show FocusState Source # 
Generic FocusState Source # 

Associated Types

type Rep FocusState :: * -> * #

NFData FocusState Source # 

Methods

rnf :: FocusState -> () #

type Rep FocusState Source # 
type Rep FocusState = D1 * (MetaData "FocusState" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "FocusState'Focused" PrefixI False) (U1 *)) (C1 * (MetaCons "FocusState'Defocused" PrefixI False) (U1 *)))

data IconifyState Source #

For use with the iconify callback. (note: iconified means minimized)

Instances

Bounded IconifyState Source # 
Enum IconifyState Source # 
Eq IconifyState Source # 
Data IconifyState Source # 

Methods

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

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

toConstr :: IconifyState -> Constr #

dataTypeOf :: IconifyState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IconifyState Source # 
Read IconifyState Source # 
Show IconifyState Source # 
Generic IconifyState Source # 

Associated Types

type Rep IconifyState :: * -> * #

NFData IconifyState Source # 

Methods

rnf :: IconifyState -> () #

type Rep IconifyState Source # 
type Rep IconifyState = D1 * (MetaData "IconifyState" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "IconifyState'Iconified" PrefixI False) (U1 *)) (C1 * (MetaCons "IconifyState'NotIconified" PrefixI False) (U1 *)))

data ContextRobustness Source #

The OpenGL robustness strategy.

Instances

Bounded ContextRobustness Source # 
Enum ContextRobustness Source # 
Eq ContextRobustness Source # 
Data ContextRobustness Source # 

Methods

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

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

toConstr :: ContextRobustness -> Constr #

dataTypeOf :: ContextRobustness -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ContextRobustness Source # 
Read ContextRobustness Source # 
Show ContextRobustness Source # 
Generic ContextRobustness Source # 
NFData ContextRobustness Source # 

Methods

rnf :: ContextRobustness -> () #

type Rep ContextRobustness Source # 
type Rep ContextRobustness = D1 * (MetaData "ContextRobustness" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "ContextRobustness'NoRobustness" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ContextRobustness'NoResetNotification" PrefixI False) (U1 *)) (C1 * (MetaCons "ContextRobustness'LoseContextOnReset" PrefixI False) (U1 *))))

data OpenGLProfile Source #

The OpenGL profile.

Instances

Bounded OpenGLProfile Source # 
Enum OpenGLProfile Source # 
Eq OpenGLProfile Source # 
Data OpenGLProfile Source # 

Methods

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

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

toConstr :: OpenGLProfile -> Constr #

dataTypeOf :: OpenGLProfile -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OpenGLProfile Source # 
Read OpenGLProfile Source # 
Show OpenGLProfile Source # 
Generic OpenGLProfile Source # 

Associated Types

type Rep OpenGLProfile :: * -> * #

NFData OpenGLProfile Source # 

Methods

rnf :: OpenGLProfile -> () #

type Rep OpenGLProfile Source # 
type Rep OpenGLProfile = D1 * (MetaData "OpenGLProfile" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "OpenGLProfile'Any" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "OpenGLProfile'Compat" PrefixI False) (U1 *)) (C1 * (MetaCons "OpenGLProfile'Core" PrefixI False) (U1 *))))

data ClientAPI Source #

The type of OpenGL to create a context for.

Instances

Bounded ClientAPI Source # 
Enum ClientAPI Source # 
Eq ClientAPI Source # 
Data ClientAPI Source # 

Methods

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

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

toConstr :: ClientAPI -> Constr #

dataTypeOf :: ClientAPI -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ClientAPI Source # 
Read ClientAPI Source # 
Show ClientAPI Source # 
Generic ClientAPI Source # 

Associated Types

type Rep ClientAPI :: * -> * #

NFData ClientAPI Source # 

Methods

rnf :: ClientAPI -> () #

type Rep ClientAPI Source # 
type Rep ClientAPI = D1 * (MetaData "ClientAPI" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "ClientAPI'OpenGL" PrefixI False) (U1 *)) (C1 * (MetaCons "ClientAPI'OpenGLES" PrefixI False) (U1 *)))

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

createWindow Source #

Arguments

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

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

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

getFramebufferSize :: Window -> IO (Int, Int) Source #

The size of the framebuffer (in Pixels) See glfwGetFramebufferSize

iconifyWindow :: Window -> IO () Source #

Iconifies (minimizes) the window. See glfwIconifyWindow

restoreWindow :: Window -> IO () Source #

Restores the window from an iconified/minimized state. See glfwRestoreWindow

showWindow :: Window -> IO () Source #

Shows the window. See glfwShowWindow

hideWindow :: Window -> IO () Source #

Hides the window. See glfwHideWindow

getWindowMonitor :: Window -> IO (Maybe Monitor) Source #

Gets the monitor that this window is running on. See glfwGetWindowMonitor

setCursorPos :: Window -> Double -> Double -> IO () Source #

Sets the position of the cursor within the window. See glfwSetCursorPos

getWindowFocused :: Window -> IO FocusState Source #

If the window has focus or not. See glfwGetWindowAttrib

 

getWindowIconified :: Window -> IO IconifyState 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

 

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

 

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 -> FocusState -> 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 -> IconifyState -> 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).

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

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

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

data Key Source #

Part of the Keyboard Input system.

Instances

Bounded Key Source # 

Methods

minBound :: Key #

maxBound :: Key #

Enum Key Source # 

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 Source # 

Methods

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

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

Data Key Source # 

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 Source # 

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 Source # 
Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

NFData Key Source # 

Methods

rnf :: Key -> () #

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

data KeyState Source #

The state of an individual key when getKey is called.

Instances

Bounded KeyState Source # 
Enum KeyState Source # 
Eq KeyState Source # 
Data KeyState Source # 

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 Source # 
Read KeyState Source # 
Show KeyState Source # 
Generic KeyState Source # 

Associated Types

type Rep KeyState :: * -> * #

Methods

from :: KeyState -> Rep KeyState x #

to :: Rep KeyState x -> KeyState #

NFData KeyState Source # 

Methods

rnf :: KeyState -> () #

type Rep KeyState Source # 
type Rep KeyState = D1 * (MetaData "KeyState" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "KeyState'Pressed" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "KeyState'Released" PrefixI False) (U1 *)) (C1 * (MetaCons "KeyState'Repeating" PrefixI False) (U1 *))))

data Joystick Source #

For use with the Joystick Input system.

Instances

Bounded Joystick Source # 
Enum Joystick Source # 
Eq Joystick Source # 
Data Joystick Source # 

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 Source # 
Read Joystick Source # 
Show Joystick Source # 
Generic Joystick Source # 

Associated Types

type Rep Joystick :: * -> * #

Methods

from :: Joystick -> Rep Joystick x #

to :: Rep Joystick x -> Joystick #

NFData Joystick Source # 

Methods

rnf :: Joystick -> () #

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

data JoystickButtonState Source #

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

Instances

Bounded JoystickButtonState Source # 
Enum JoystickButtonState Source # 
Eq JoystickButtonState Source # 
Data JoystickButtonState Source # 

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 Source # 
Read JoystickButtonState Source # 
Show JoystickButtonState Source # 
Generic JoystickButtonState Source # 
NFData JoystickButtonState Source # 

Methods

rnf :: JoystickButtonState -> () #

type Rep JoystickButtonState Source # 
type Rep JoystickButtonState = D1 * (MetaData "JoystickButtonState" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "JoystickButtonState'Pressed" PrefixI False) (U1 *)) (C1 * (MetaCons "JoystickButtonState'Released" PrefixI False) (U1 *)))

data MouseButton Source #

Part of the Mouse Input system.

Instances

Bounded MouseButton Source # 
Enum MouseButton Source # 
Eq MouseButton Source # 
Data MouseButton Source # 

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 Source # 
Read MouseButton Source # 
Show MouseButton Source # 
Generic MouseButton Source # 

Associated Types

type Rep MouseButton :: * -> * #

NFData MouseButton Source # 

Methods

rnf :: MouseButton -> () #

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

data MouseButtonState Source #

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

Instances

Bounded MouseButtonState Source # 
Enum MouseButtonState Source # 
Eq MouseButtonState Source # 
Data MouseButtonState Source # 

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 Source # 
Read MouseButtonState Source # 
Show MouseButtonState Source # 
Generic MouseButtonState Source # 
NFData MouseButtonState Source # 

Methods

rnf :: MouseButtonState -> () #

type Rep MouseButtonState Source # 
type Rep MouseButtonState = D1 * (MetaData "MouseButtonState" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "MouseButtonState'Pressed" PrefixI False) (U1 *)) (C1 * (MetaCons "MouseButtonState'Released" PrefixI False) (U1 *)))

data CursorState Source #

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

Instances

Bounded CursorState Source # 
Enum CursorState Source # 
Eq CursorState Source # 
Data CursorState Source # 

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 Source # 
Read CursorState Source # 
Show CursorState Source # 
Generic CursorState Source # 

Associated Types

type Rep CursorState :: * -> * #

NFData CursorState Source # 

Methods

rnf :: CursorState -> () #

type Rep CursorState Source # 
type Rep CursorState = D1 * (MetaData "CursorState" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "CursorState'InWindow" PrefixI False) (U1 *)) (C1 * (MetaCons "CursorState'NotInWindow" PrefixI False) (U1 *)))

data CursorInputMode Source #

Allows for special forms of mouse input. See Cursor Modes

Instances

Bounded CursorInputMode Source # 
Enum CursorInputMode Source # 
Eq CursorInputMode Source # 
Data CursorInputMode Source # 

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 Source # 
Read CursorInputMode Source # 
Show CursorInputMode Source # 
Generic CursorInputMode Source # 
NFData CursorInputMode Source # 

Methods

rnf :: CursorInputMode -> () #

type Rep CursorInputMode Source # 
type Rep CursorInputMode = D1 * (MetaData "CursorInputMode" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "CursorInputMode'Normal" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "CursorInputMode'Hidden" PrefixI False) (U1 *)) (C1 * (MetaCons "CursorInputMode'Disabled" PrefixI False) (U1 *))))

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

Bounded StickyKeysInputMode Source # 
Enum StickyKeysInputMode Source # 
Eq StickyKeysInputMode Source # 
Data StickyKeysInputMode Source # 

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 Source # 
Read StickyKeysInputMode Source # 
Show StickyKeysInputMode Source # 
Generic StickyKeysInputMode Source # 
NFData StickyKeysInputMode Source # 

Methods

rnf :: StickyKeysInputMode -> () #

type Rep StickyKeysInputMode Source # 
type Rep StickyKeysInputMode = D1 * (MetaData "StickyKeysInputMode" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * (C1 * (MetaCons "StickyKeysInputMode'Enabled" PrefixI False) (U1 *)) (C1 * (MetaCons "StickyKeysInputMode'Disabled" PrefixI False) (U1 *)))

data StickyMouseButtonsInputMode Source #

This is the mouse version of StickyKeysInputMode.

Instances

Bounded StickyMouseButtonsInputMode Source # 
Enum StickyMouseButtonsInputMode Source # 
Eq StickyMouseButtonsInputMode Source # 
Data StickyMouseButtonsInputMode Source # 

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

data ModifierKeys Source #

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

Instances

Eq ModifierKeys Source # 
Data ModifierKeys Source # 

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 Source # 
Read ModifierKeys Source # 
Show ModifierKeys Source # 
Generic ModifierKeys Source # 

Associated Types

type Rep ModifierKeys :: * -> * #

NFData ModifierKeys Source # 

Methods

rnf :: ModifierKeys -> () #

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

data Image Source #

GLFW image data, for setting up custom mouse cursor appearnaces.

Constructors

Image 

Instances

Eq Image Source # 

Methods

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

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

Data Image Source # 

Methods

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 #

toConstr :: Image -> Constr #

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 :: (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 #

Ord Image Source # 

Methods

compare :: Image -> Image -> Ordering #

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

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

(>) :: Image -> Image -> Bool #

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

max :: Image -> Image -> Image #

min :: Image -> Image -> Image #

Read Image Source # 
Show Image Source # 

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

NFData Image Source # 

Methods

rnf :: Image -> () #

type Rep Image Source # 
type Rep Image = D1 * (MetaData "Image" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) (C1 * (MetaCons "Image" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "imageWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "imageHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "imagePixels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [CUChar])))))

newtype Cursor Source #

Reprisents a GLFW cursor.

Constructors

Cursor 

Instances

Eq Cursor Source # 

Methods

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

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

Data Cursor Source # 

Methods

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 :: (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 #

Ord Cursor Source # 
Show Cursor Source # 
Generic Cursor Source # 

Associated Types

type Rep Cursor :: * -> * #

Methods

from :: Cursor -> Rep Cursor x #

to :: Rep Cursor x -> Cursor #

type Rep Cursor Source # 
type Rep Cursor = D1 * (MetaData "Cursor" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" True) (C1 * (MetaCons "Cursor" PrefixI True) (S1 * (MetaSel (Just Symbol "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.

Instances

Bounded StandardCursorShape Source # 
Enum StandardCursorShape Source # 
Eq StandardCursorShape Source # 
Data StandardCursorShape Source # 

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 Source # 
Read StandardCursorShape Source # 
Show StandardCursorShape Source # 
Generic StandardCursorShape Source # 
NFData StandardCursorShape Source # 

Methods

rnf :: StandardCursorShape -> () #

type Rep StandardCursorShape Source # 
type Rep StandardCursorShape = D1 * (MetaData "StandardCursorShape" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.4-7bEEwJvbs2NCaF5kxqg0rD" False) ((:+:) * ((:+:) * (C1 * (MetaCons "StandardCursorShape'Arrow" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StandardCursorShape'IBeam" PrefixI False) (U1 *)) (C1 * (MetaCons "StandardCursorShape'Crosshair" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "StandardCursorShape'Hand" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StandardCursorShape'HResize" PrefixI False) (U1 *)) (C1 * (MetaCons "StandardCursorShape'VResize" PrefixI False) (U1 *)))))

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

 

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

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.

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.

createCursor Source #

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.

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.

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 #

Arguments

 = Window

The window that received the event.

-> [String]

The file and/or directory path names

-> IO () 

A callback that allows for drag and drop support.

joystickPresent :: Joystick -> IO Bool Source #

Tests if the joystick is present at all See glfwJoystickPresent

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

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

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

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

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