GLFW-b-3.3.0.0: Bindings to GLFW OpenGL library
Safe HaskellNone
LanguageHaskell2010

Graphics.UI.GLFW

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

Instances details
Bounded Error Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum Error Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq Error Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

Data Error Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: 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 #

Ord Error Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

Defined in Graphics.UI.GLFW.Types

Show Error Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Generic Error Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep Error :: Type -> Type #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

NFData Error Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: Error -> () #

type Rep Error Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep Error = D1 ('MetaData "Error" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" '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

data Version Source #

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

Constructors

Version 

Instances

Instances details
Eq Version Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

Data Version Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 #

Ord Version Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read Version Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show Version Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic Version Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

NFData Version Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: Version -> () #

type Rep Version Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep Version = D1 ('MetaData "Version" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" '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))))

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

data InitHint Source #

Initialization hints are set before glfwInit and affect how the library behaves until termination. Hints are set with glfwInitHint. See Init Hints

Instances

Instances details
Bounded InitHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum InitHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq InitHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data InitHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 #

Ord InitHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read InitHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show InitHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic InitHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep InitHint :: Type -> Type #

Methods

from :: InitHint -> Rep InitHint x #

to :: Rep InitHint x -> InitHint #

NFData InitHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: InitHint -> () #

type Rep InitHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep InitHint = D1 ('MetaData "InitHint" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" '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

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

data Monitor Source #

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

Instances

Instances details
Eq Monitor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

Data Monitor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 #

Ord Monitor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show Monitor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic Monitor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep Monitor :: Type -> Type #

Methods

from :: Monitor -> Rep Monitor x #

to :: Rep Monitor x -> Monitor #

type Rep Monitor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep Monitor = D1 ('MetaData "Monitor" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" '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

Instances details
Eq MonitorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data MonitorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read MonitorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show MonitorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic MonitorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep MonitorState :: Type -> Type #

NFData MonitorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: MonitorState -> () #

type Rep MonitorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep MonitorState = D1 ('MetaData "MonitorState" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) (C1 ('MetaCons "MonitorState'Connected" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonitorState'Disconnected" 'PrefixI 'False) (U1 :: Type -> Type))

data VideoMode Source #

Instances

Instances details
Eq VideoMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data VideoMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read VideoMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show VideoMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic VideoMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep VideoMode :: Type -> Type #

NFData VideoMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: VideoMode -> () #

type Rep VideoMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep VideoMode = D1 ('MetaData "VideoMode" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) (C1 ('MetaCons "VideoMode" 'PrefixI 'True) ((S1 ('MetaSel ('Just "videoModeWidth") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "videoModeHeight") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "videoModeRedBits") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: (S1 ('MetaSel ('Just "videoModeGreenBits") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "videoModeBlueBits") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "videoModeRefreshRate") 'SourceUnpack 'SourceStrict 'DecidedStrict) (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

Instances details
Eq GammaRamp Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data GammaRamp Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 #

Ord GammaRamp Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read GammaRamp Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show GammaRamp Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic GammaRamp Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep GammaRamp :: Type -> Type #

NFData GammaRamp Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: GammaRamp -> () #

type Rep GammaRamp Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GammaRamp = D1 ('MetaData "GammaRamp" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" '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

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 #

Represents a GLFW window value. See the Window Guide

Instances

Instances details
Eq Window Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

Data Window Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 #

Ord Window Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show Window Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic Window Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep Window :: Type -> Type #

Methods

from :: Window -> Rep Window x #

to :: Rep Window x -> Window #

type Rep Window Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep Window = D1 ('MetaData "Window" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" '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

Instances details
Eq WindowHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data WindowHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read WindowHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show WindowHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic WindowHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep WindowHint :: Type -> Type #

NFData WindowHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: WindowHint -> () #

type Rep WindowHint Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep WindowHint = D1 ('MetaData "WindowHint" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) (((((C1 ('MetaCons "WindowHint'Resizable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "WindowHint'Visible" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :+: (C1 ('MetaCons "WindowHint'Decorated" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: (C1 ('MetaCons "WindowHint'RedBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: C1 ('MetaCons "WindowHint'GreenBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)))))) :+: ((C1 ('MetaCons "WindowHint'BlueBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: C1 ('MetaCons "WindowHint'AlphaBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)))) :+: (C1 ('MetaCons "WindowHint'DepthBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: (C1 ('MetaCons "WindowHint'StencilBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: C1 ('MetaCons "WindowHint'AccumRedBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))))))) :+: (((C1 ('MetaCons "WindowHint'AccumGreenBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: C1 ('MetaCons "WindowHint'AccumBlueBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)))) :+: (C1 ('MetaCons "WindowHint'AccumAlphaBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: (C1 ('MetaCons "WindowHint'AuxBuffers" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: C1 ('MetaCons "WindowHint'Samples" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)))))) :+: ((C1 ('MetaCons "WindowHint'RefreshRate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :+: (C1 ('MetaCons "WindowHint'DoubleBuffer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "WindowHint'Stereo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))) :+: (C1 ('MetaCons "WindowHint'sRGBCapable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: (C1 ('MetaCons "WindowHint'Floating" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "WindowHint'Focused" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))))))) :+: ((((C1 ('MetaCons "WindowHint'Maximized" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "WindowHint'AutoIconify" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :+: (C1 ('MetaCons "WindowHint'ClientAPI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ClientAPI)) :+: (C1 ('MetaCons "WindowHint'ContextCreationAPI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContextCreationAPI)) :+: C1 ('MetaCons "WindowHint'ContextVersionMajor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int))))) :+: ((C1 ('MetaCons "WindowHint'ContextVersionMinor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "WindowHint'ContextRobustness" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContextRobustness))) :+: (C1 ('MetaCons "WindowHint'ContextReleaseBehavior" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ContextReleaseBehavior)) :+: (C1 ('MetaCons "WindowHint'ContextNoError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "WindowHint'OpenGLForwardCompat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))))) :+: (((C1 ('MetaCons "WindowHint'OpenGLDebugContext" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "WindowHint'OpenGLProfile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OpenGLProfile))) :+: (C1 ('MetaCons "WindowHint'TransparentFramebuffer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: (C1 ('MetaCons "WindowHint'CenterCursor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "WindowHint'FocusOnShow" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))))) :+: ((C1 ('MetaCons "WindowHint'ScaleToMonitor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: (C1 ('MetaCons "WindowHint'CocoaRetinaFramebuffer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :+: C1 ('MetaCons "WindowHint'CocoaGraphicsSwitching" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))) :+: (C1 ('MetaCons "WindowHint'CocoaFrameName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)) :+: (C1 ('MetaCons "WindowHint'X11ClassName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)) :+: C1 ('MetaCons "WindowHint'X11InstanceName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))))))))

data WindowAttrib Source #

A window-specific attribute. See Window Attributes

Instances

Instances details
Bounded WindowAttrib Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum WindowAttrib Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq WindowAttrib Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data WindowAttrib Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: WindowAttrib -> Constr #

dataTypeOf :: WindowAttrib -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WindowAttrib Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read WindowAttrib Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show WindowAttrib Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic WindowAttrib Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep WindowAttrib :: Type -> Type #

NFData WindowAttrib Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: WindowAttrib -> () #

type Rep WindowAttrib Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep WindowAttrib = D1 ('MetaData "WindowAttrib" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) ((C1 ('MetaCons "WindowAttrib'Decorated" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WindowAttrib'Resizable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WindowAttrib'Floating" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "WindowAttrib'AutoIconify" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WindowAttrib'FocusOnShow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WindowAttrib'Hovered" 'PrefixI 'False) (U1 :: Type -> Type))))

data ContextRobustness Source #

The OpenGL robustness strategy.

Instances

Instances details
Bounded ContextRobustness Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum ContextRobustness Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq ContextRobustness Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data ContextRobustness Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read ContextRobustness Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show ContextRobustness Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic ContextRobustness Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep ContextRobustness :: Type -> Type #

NFData ContextRobustness Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: ContextRobustness -> () #

type Rep ContextRobustness Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep ContextRobustness = D1 ('MetaData "ContextRobustness" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) (C1 ('MetaCons "ContextRobustness'NoRobustness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ContextRobustness'NoResetNotification" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ContextRobustness'LoseContextOnReset" 'PrefixI 'False) (U1 :: Type -> Type)))

data OpenGLProfile Source #

The OpenGL profile.

Instances

Instances details
Bounded OpenGLProfile Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum OpenGLProfile Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq OpenGLProfile Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data OpenGLProfile Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read OpenGLProfile Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show OpenGLProfile Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic OpenGLProfile Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep OpenGLProfile :: Type -> Type #

NFData OpenGLProfile Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: OpenGLProfile -> () #

type Rep OpenGLProfile Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep OpenGLProfile = D1 ('MetaData "OpenGLProfile" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) (C1 ('MetaCons "OpenGLProfile'Any" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OpenGLProfile'Compat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OpenGLProfile'Core" 'PrefixI 'False) (U1 :: Type -> Type)))

data ClientAPI Source #

The type of OpenGL to create a context for.

Instances

Instances details
Bounded ClientAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum ClientAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq ClientAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data ClientAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read ClientAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show ClientAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic ClientAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep ClientAPI :: Type -> Type #

NFData ClientAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: ClientAPI -> () #

type Rep ClientAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep ClientAPI = D1 ('MetaData "ClientAPI" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) (C1 ('MetaCons "ClientAPI'NoAPI" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ClientAPI'OpenGL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ClientAPI'OpenGLES" 'PrefixI 'False) (U1 :: Type -> Type)))

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

Instances details
Bounded ContextCreationAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum ContextCreationAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq ContextCreationAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data ContextCreationAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: ContextCreationAPI -> Constr #

dataTypeOf :: ContextCreationAPI -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ContextCreationAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read ContextCreationAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show ContextCreationAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic ContextCreationAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep ContextCreationAPI :: Type -> Type #

NFData ContextCreationAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: ContextCreationAPI -> () #

type Rep ContextCreationAPI Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep ContextCreationAPI = D1 ('MetaData "ContextCreationAPI" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) (C1 ('MetaCons "ContextCreationAPI'Native" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ContextCreationAPI'EGL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ContextCreationAPI'OSMesa" 'PrefixI 'False) (U1 :: Type -> Type)))

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

Instances details
Bounded ContextReleaseBehavior Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum ContextReleaseBehavior Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq ContextReleaseBehavior Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data ContextReleaseBehavior Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: ContextReleaseBehavior -> Constr #

dataTypeOf :: ContextReleaseBehavior -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ContextReleaseBehavior Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read ContextReleaseBehavior Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show ContextReleaseBehavior Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic ContextReleaseBehavior Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep ContextReleaseBehavior :: Type -> Type #

NFData ContextReleaseBehavior Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: ContextReleaseBehavior -> () #

type Rep ContextReleaseBehavior Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep ContextReleaseBehavior = D1 ('MetaData "ContextReleaseBehavior" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) (C1 ('MetaCons "ContextReleaseBehavior'Any" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ContextReleaseBehavior'None" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ContextReleaseBehavior'Flush" 'PrefixI 'False) (U1 :: Type -> Type)))

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

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

setWindowSizeLimits Source #

Arguments

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

setWindowed Source #

Arguments

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

 
 

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

data Key Source #

Part of the Keyboard Input system.

Instances

Instances details
Bounded Key Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

minBound :: Key #

maxBound :: Key #

Enum Key Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

succ :: Key -> Key #

pred :: Key -> Key #

toEnum :: Int -> Key #

fromEnum :: Key -> Int #

enumFrom :: Key -> [Key] #

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

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

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

Eq Key Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

Data Key Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: Key -> Constr #

dataTypeOf :: Key -> DataType #

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

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

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

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

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

Ord Key Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

compare :: Key -> Key -> Ordering #

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

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

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

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Read Key Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show Key Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

NFData Key Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: Key -> () #

type Rep Key Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data KeyState Source #

The state of an individual key when getKey is called.

Instances

Instances details
Bounded KeyState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum KeyState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq KeyState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data KeyState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: KeyState -> Constr #

dataTypeOf :: KeyState -> DataType #

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

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

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

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

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

Ord KeyState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read KeyState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show KeyState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic KeyState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep KeyState :: Type -> Type #

Methods

from :: KeyState -> Rep KeyState x #

to :: Rep KeyState x -> KeyState #

NFData KeyState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: KeyState -> () #

type Rep KeyState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data Joystick Source #

For use with the Joystick Input system.

Instances

Instances details
Bounded Joystick Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum Joystick Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq Joystick Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data Joystick Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: Joystick -> Constr #

dataTypeOf :: Joystick -> DataType #

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

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

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

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

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

Ord Joystick Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read Joystick Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show Joystick Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic Joystick Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep Joystick :: Type -> Type #

Methods

from :: Joystick -> Rep Joystick x #

to :: Rep Joystick x -> Joystick #

NFData Joystick Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: Joystick -> () #

type Rep Joystick Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep Joystick = D1 ('MetaData "Joystick" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" '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

Instances details
Bounded JoystickState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum JoystickState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq JoystickState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data JoystickState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: JoystickState -> Constr #

dataTypeOf :: JoystickState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JoystickState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read JoystickState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show JoystickState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic JoystickState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep JoystickState :: Type -> Type #

NFData JoystickState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: JoystickState -> () #

type Rep JoystickState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep JoystickState = D1 ('MetaData "JoystickState" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) (C1 ('MetaCons "JoystickState'Connected" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JoystickState'Disconnected" 'PrefixI 'False) (U1 :: Type -> Type))

data JoystickButtonState Source #

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

Instances

Instances details
Bounded JoystickButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum JoystickButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq JoystickButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data JoystickButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: JoystickButtonState -> Constr #

dataTypeOf :: JoystickButtonState -> DataType #

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

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

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

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

gmapQr :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read JoystickButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show JoystickButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic JoystickButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep JoystickButtonState :: Type -> Type #

NFData JoystickButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: JoystickButtonState -> () #

type Rep JoystickButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data MouseButton Source #

Part of the Mouse Input system.

Instances

Instances details
Bounded MouseButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum MouseButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq MouseButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data MouseButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: MouseButton -> Constr #

dataTypeOf :: MouseButton -> DataType #

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

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

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

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

gmapQr :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read MouseButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show MouseButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic MouseButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep MouseButton :: Type -> Type #

NFData MouseButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: MouseButton -> () #

type Rep MouseButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data MouseButtonState Source #

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

Instances

Instances details
Bounded MouseButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum MouseButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq MouseButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data MouseButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: MouseButtonState -> Constr #

dataTypeOf :: MouseButtonState -> DataType #

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

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

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

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

gmapQr :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read MouseButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show MouseButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic MouseButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep MouseButtonState :: Type -> Type #

NFData MouseButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: MouseButtonState -> () #

type Rep MouseButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data CursorState Source #

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

Instances

Instances details
Bounded CursorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum CursorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq CursorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data CursorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: CursorState -> Constr #

dataTypeOf :: CursorState -> DataType #

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

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

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

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

gmapQr :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read CursorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show CursorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic CursorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep CursorState :: Type -> Type #

NFData CursorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: CursorState -> () #

type Rep CursorState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data CursorInputMode Source #

Allows for special forms of mouse input. See Cursor Modes

Instances

Instances details
Bounded CursorInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum CursorInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq CursorInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data CursorInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: CursorInputMode -> Constr #

dataTypeOf :: CursorInputMode -> DataType #

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

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

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

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

gmapQr :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read CursorInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show CursorInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic CursorInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep CursorInputMode :: Type -> Type #

NFData CursorInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: CursorInputMode -> () #

type Rep CursorInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data 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

Instances details
Bounded StickyKeysInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum StickyKeysInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq StickyKeysInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data StickyKeysInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: StickyKeysInputMode -> Constr #

dataTypeOf :: StickyKeysInputMode -> DataType #

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

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

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

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

gmapQr :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read StickyKeysInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show StickyKeysInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic StickyKeysInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep StickyKeysInputMode :: Type -> Type #

NFData StickyKeysInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: StickyKeysInputMode -> () #

type Rep StickyKeysInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data StickyMouseButtonsInputMode Source #

This is the mouse version of StickyKeysInputMode.

Instances

Instances details
Bounded StickyMouseButtonsInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum StickyMouseButtonsInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq StickyMouseButtonsInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data StickyMouseButtonsInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: StickyMouseButtonsInputMode -> Constr #

dataTypeOf :: StickyMouseButtonsInputMode -> DataType #

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

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

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

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

gmapQr :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read StickyMouseButtonsInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show StickyMouseButtonsInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic StickyMouseButtonsInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep StickyMouseButtonsInputMode :: Type -> Type #

NFData StickyMouseButtonsInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep StickyMouseButtonsInputMode Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data ModifierKeys Source #

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

Instances

Instances details
Eq ModifierKeys Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data ModifierKeys Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: ModifierKeys -> Constr #

dataTypeOf :: ModifierKeys -> DataType #

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

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

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

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

gmapQr :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read ModifierKeys Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show ModifierKeys Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic ModifierKeys Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep ModifierKeys :: Type -> Type #

NFData ModifierKeys Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: ModifierKeys -> () #

type Rep ModifierKeys Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data GamepadButton Source #

The different types of buttons we can find on a Gamepad.

Instances

Instances details
Bounded GamepadButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum GamepadButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq GamepadButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data GamepadButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: GamepadButton -> Constr #

dataTypeOf :: GamepadButton -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GamepadButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read GamepadButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show GamepadButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic GamepadButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep GamepadButton :: Type -> Type #

NFData GamepadButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: GamepadButton -> () #

type Rep GamepadButton Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadButton = D1 ('MetaData "GamepadButton" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) ((((C1 ('MetaCons "GamepadButton'A" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'B" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GamepadButton'X" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'Y" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GamepadButton'LeftBumper" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'RightBumper" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GamepadButton'Back" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GamepadButton'Start" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'Guide" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "GamepadButton'LeftThumb" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'RightThumb" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GamepadButton'DpadUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GamepadButton'DpadRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'DpadDown" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "GamepadButton'DpadLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'Cross" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GamepadButton'Circle" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GamepadButton'Square" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'Triangle" 'PrefixI 'False) (U1 :: Type -> Type))))))

data GamepadAxis Source #

The different axes along which we can measure continuous input on a Gamepad

Instances

Instances details
Bounded GamepadAxis Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum GamepadAxis Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq GamepadAxis Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data GamepadAxis Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: GamepadAxis -> Constr #

dataTypeOf :: GamepadAxis -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GamepadAxis Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read GamepadAxis Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show GamepadAxis Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic GamepadAxis Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep GamepadAxis :: Type -> Type #

NFData GamepadAxis Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: GamepadAxis -> () #

type Rep GamepadAxis Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadAxis = D1 ('MetaData "GamepadAxis" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) ((C1 ('MetaCons "GamepadAxis'LeftX" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GamepadAxis'LeftY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadAxis'RightX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "GamepadAxis'RightY" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GamepadAxis'LeftTrigger" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadAxis'RightTrigger" 'PrefixI 'False) (U1 :: Type -> Type))))

data GamepadButtonState Source #

The states in which the gamepad buttons are found

Instances

Instances details
Bounded GamepadButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum GamepadButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq GamepadButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data GamepadButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: GamepadButtonState -> Constr #

dataTypeOf :: GamepadButtonState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GamepadButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read GamepadButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show GamepadButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic GamepadButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep GamepadButtonState :: Type -> Type #

NFData GamepadButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: GamepadButtonState -> () #

type Rep GamepadButtonState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

data GamepadState Source #

This describes the input state of a gamepad

Constructors

GamepadState 

Fields

Instances

Instances details
Eq GamepadState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic GamepadState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep GamepadState :: Type -> Type #

NFData GamepadState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: GamepadState -> () #

type Rep GamepadState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadState = D1 ('MetaData "GamepadState" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" '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))))

data Image Source #

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

Instances

Instances details
Eq Image Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

Data Image Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 :: 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 #

Ord Image Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

Defined in Graphics.UI.GLFW.Types

Show Image Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep Image :: Type -> Type #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

NFData Image Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: Image -> () #

type Rep Image Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep Image = D1 ('MetaData "Image" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" '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.

newtype Cursor Source #

Represents a GLFW cursor.

Constructors

Cursor 

Instances

Instances details
Eq Cursor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

Data Cursor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 #

Ord Cursor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show Cursor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic Cursor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep Cursor :: Type -> Type #

Methods

from :: Cursor -> Rep Cursor x #

to :: Rep Cursor x -> Cursor #

type Rep Cursor Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep Cursor = D1 ('MetaData "Cursor" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" '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.

Instances

Instances details
Bounded StandardCursorShape Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum StandardCursorShape Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq StandardCursorShape Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data StandardCursorShape Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: StandardCursorShape -> Constr #

dataTypeOf :: StandardCursorShape -> DataType #

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

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

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

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

gmapQr :: forall r r'. (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 # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read StandardCursorShape Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show StandardCursorShape Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic StandardCursorShape Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep StandardCursorShape :: Type -> Type #

NFData StandardCursorShape Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: StandardCursorShape -> () #

type Rep StandardCursorShape Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

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

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.

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

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

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

Instances details
Bounded JoystickHatState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum JoystickHatState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Eq JoystickHatState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Data JoystickHatState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: JoystickHatState -> Constr #

dataTypeOf :: JoystickHatState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord JoystickHatState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Read JoystickHatState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Show JoystickHatState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic JoystickHatState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep JoystickHatState :: Type -> Type #

NFData JoystickHatState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: JoystickHatState -> () #

type Rep JoystickHatState Source # 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep JoystickHatState = D1 ('MetaData "JoystickHatState" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.0.0-inplace" 'False) (((C1 ('MetaCons "JoystickHatState'Centered" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JoystickHatState'Up" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "JoystickHatState'Right" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JoystickHatState'Down" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "JoystickHatState'Left" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JoystickHatState'RightUp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "JoystickHatState'RightDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "JoystickHatState'LeftUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JoystickHatState'LeftDown" 'PrefixI 'False) (U1 :: Type -> Type)))))

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.

getRequiredInstanceExtensions :: IO [CString] Source #

Get required vulkan extensions; Pointer memory is managed by GLFW, destroyed by terminate call.

The returned extension names are kept in CString type, because they are expected to be consumed by vulkan device initialization functions.

getInstanceProcAddress Source #

Arguments

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

Arguments

:: Ptr vkInstance

VkInstance

-> Ptr vkPhysicalDevice

VkPhysicalDevice

-> Word32

Index of a queue family to query. This is an index in the array returned by vkGetPhysicalDeviceQueueFamilyProperties function.

-> IO Bool 

Returns whether the specified queue family can present images.

createWindowSurface Source #

Arguments

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

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.

type OSMesaDepthBuffer = Array (Int, Int) Word32 Source #

A depth buffer is a two dimensional array of depth values. The range is usually determined by a parameter returned from the query function.