GLFW-b-1.4.8.1: Bindings to GLFW OpenGL library

Safe HaskellNone
LanguageHaskell2010

Graphics.UI.GLFW

Contents

Synopsis

Error handling

data Error Source #

Instances

Enum Error Source # 
Eq Error Source # 

Methods

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

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

Data Error Source # 

Methods

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

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

toConstr :: Error -> Constr #

dataTypeOf :: Error -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Error Source # 

Methods

compare :: Error -> Error -> Ordering #

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

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

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

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

max :: Error -> Error -> Error #

min :: Error -> Error -> Error #

Read Error Source # 
Show Error Source # 

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Generic Error Source # 

Associated Types

type Rep Error :: * -> * #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

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

Initialization and version information

data Version Source #

Constructors

Version 

Instances

Eq Version Source # 

Methods

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

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

Data Version Source # 

Methods

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

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

toConstr :: Version -> Constr #

dataTypeOf :: Version -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

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

Monitor handling

data Monitor Source #

Instances

Eq Monitor Source # 

Methods

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

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

Data Monitor Source # 

Methods

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

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

toConstr :: Monitor -> Constr #

dataTypeOf :: Monitor -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep Monitor :: * -> * #

Methods

from :: Monitor -> Rep Monitor x #

to :: Rep Monitor x -> Monitor #

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

data MonitorState Source #

Instances

Eq MonitorState Source # 
Data MonitorState Source # 

Methods

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

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

toConstr :: MonitorState -> Constr #

dataTypeOf :: MonitorState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep MonitorState :: * -> * #

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

data VideoMode Source #

Instances

Eq VideoMode Source # 
Data VideoMode Source # 

Methods

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

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

toConstr :: VideoMode -> Constr #

dataTypeOf :: VideoMode -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep VideoMode :: * -> * #

type Rep VideoMode Source # 

data GammaRamp Source #

Instances

Eq GammaRamp Source # 
Data GammaRamp Source # 

Methods

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

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

toConstr :: GammaRamp -> Constr #

dataTypeOf :: GammaRamp -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep GammaRamp :: * -> * #

type Rep GammaRamp Source # 
type Rep GammaRamp = D1 (MetaData "GammaRamp" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) (C1 (MetaCons "GammaRamp" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "gammaRampRed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int])) ((:*:) (S1 (MetaSel (Just Symbol "gammaRampGreen") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int])) (S1 (MetaSel (Just Symbol "gammaRampBlue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int])))))

Window handling

data Window Source #

Instances

Eq Window Source # 

Methods

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

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

Data Window Source # 

Methods

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

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

toConstr :: Window -> Constr #

dataTypeOf :: Window -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep Window :: * -> * #

Methods

from :: Window -> Rep Window x #

to :: Rep Window x -> Window #

type Rep Window Source # 
type Rep Window = D1 (MetaData "Window" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" True) (C1 (MetaCons "Window" PrefixI True) (S1 (MetaSel (Just Symbol "unWindow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ptr C'GLFWwindow))))

data WindowHint Source #

Instances

Eq WindowHint Source # 
Data WindowHint Source # 

Methods

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

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

toConstr :: WindowHint -> Constr #

dataTypeOf :: WindowHint -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep WindowHint :: * -> * #

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

data FocusState Source #

Instances

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

Methods

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

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

toConstr :: FocusState -> Constr #

dataTypeOf :: FocusState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep FocusState :: * -> * #

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

data IconifyState Source #

Instances

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

Methods

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

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

toConstr :: IconifyState -> Constr #

dataTypeOf :: IconifyState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep IconifyState :: * -> * #

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

data ContextRobustness Source #

Instances

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

Methods

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

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

toConstr :: ContextRobustness -> Constr #

dataTypeOf :: ContextRobustness -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ContextRobustness Source # 
Read ContextRobustness Source # 
Show ContextRobustness Source # 
Generic ContextRobustness Source # 
type Rep ContextRobustness Source # 
type Rep ContextRobustness = D1 (MetaData "ContextRobustness" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" False) ((:+:) (C1 (MetaCons "ContextRobustness'NoRobustness" PrefixI False) U1) ((:+:) (C1 (MetaCons "ContextRobustness'NoResetNotification" PrefixI False) U1) (C1 (MetaCons "ContextRobustness'LoseContextOnReset" PrefixI False) U1)))

data OpenGLProfile Source #

Instances

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

Methods

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

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

toConstr :: OpenGLProfile -> Constr #

dataTypeOf :: OpenGLProfile -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep OpenGLProfile :: * -> * #

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

data ClientAPI Source #

Instances

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

Methods

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

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

toConstr :: ClientAPI -> Constr #

dataTypeOf :: ClientAPI -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep ClientAPI :: * -> * #

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

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.

 
 
 
 
 
 
 
 
 
 
 
 

Input handling

data Key Source #

Instances

Enum Key Source # 

Methods

succ :: Key -> Key #

pred :: Key -> Key #

toEnum :: Int -> Key #

fromEnum :: Key -> Int #

enumFrom :: Key -> [Key] #

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

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

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

Eq Key Source # 

Methods

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

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

Data Key Source # 

Methods

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

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

toConstr :: Key -> Constr #

dataTypeOf :: Key -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Key Source # 

Methods

compare :: Key -> Key -> Ordering #

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

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

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

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Read Key Source # 
Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

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

data KeyState Source #

Instances

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

Methods

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

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

toConstr :: KeyState -> Constr #

dataTypeOf :: KeyState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord KeyState Source # 
Read KeyState Source # 
Show KeyState Source # 
Generic KeyState Source # 

Associated Types

type Rep KeyState :: * -> * #

Methods

from :: KeyState -> Rep KeyState x #

to :: Rep KeyState x -> KeyState #

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

data Joystick Source #

Instances

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

Methods

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

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

toConstr :: Joystick -> Constr #

dataTypeOf :: Joystick -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Joystick Source # 
Read Joystick Source # 
Show Joystick Source # 
Generic Joystick Source # 

Associated Types

type Rep Joystick :: * -> * #

Methods

from :: Joystick -> Rep Joystick x #

to :: Rep Joystick x -> Joystick #

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

data JoystickButtonState Source #

Instances

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

Methods

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

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

toConstr :: JoystickButtonState -> Constr #

dataTypeOf :: JoystickButtonState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

data MouseButton Source #

Instances

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

Methods

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

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

toConstr :: MouseButton -> Constr #

dataTypeOf :: MouseButton -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MouseButton Source # 
Read MouseButton Source # 
Show MouseButton Source # 
Generic MouseButton Source # 

Associated Types

type Rep MouseButton :: * -> * #

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

data MouseButtonState Source #

Instances

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

Methods

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

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

toConstr :: MouseButtonState -> Constr #

dataTypeOf :: MouseButtonState -> DataType #

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

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

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

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

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

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

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

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

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

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

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

data CursorState Source #

Instances

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

Methods

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

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

toConstr :: CursorState -> Constr #

dataTypeOf :: CursorState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CursorState Source # 
Read CursorState Source # 
Show CursorState Source # 
Generic CursorState Source # 

Associated Types

type Rep CursorState :: * -> * #

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

data CursorInputMode Source #

Instances

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

Methods

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

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

toConstr :: CursorInputMode -> Constr #

dataTypeOf :: CursorInputMode -> DataType #

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

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

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

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

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

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

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

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

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

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

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

data StickyKeysInputMode Source #

Instances

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

Methods

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

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

toConstr :: StickyKeysInputMode -> Constr #

dataTypeOf :: StickyKeysInputMode -> DataType #

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

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

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

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

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

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

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

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

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

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

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

data StickyMouseButtonsInputMode Source #

Instances

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

Methods

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

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

toConstr :: StickyMouseButtonsInputMode -> Constr #

dataTypeOf :: StickyMouseButtonsInputMode -> DataType #

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

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

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

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

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

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

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

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

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

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

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

data ModifierKeys Source #

Instances

Eq ModifierKeys Source # 
Data ModifierKeys Source # 

Methods

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

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

toConstr :: ModifierKeys -> Constr #

dataTypeOf :: ModifierKeys -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ModifierKeys Source # 
Read ModifierKeys Source # 
Show ModifierKeys Source # 
Generic ModifierKeys Source # 

Associated Types

type Rep ModifierKeys :: * -> * #

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

data Image Source #

Constructors

Image 

Instances

Eq Image Source # 

Methods

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

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

Data Image Source # 

Methods

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

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

toConstr :: Image -> Constr #

dataTypeOf :: Image -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Image Source # 

Methods

compare :: Image -> Image -> Ordering #

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

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

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

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

max :: Image -> Image -> Image #

min :: Image -> Image -> Image #

Read Image Source # 
Show Image Source # 

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

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

newtype Cursor Source #

Constructors

Cursor 

Instances

Eq Cursor Source # 

Methods

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

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

Data Cursor Source # 

Methods

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

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

toConstr :: Cursor -> Constr #

dataTypeOf :: Cursor -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Associated Types

type Rep Cursor :: * -> * #

Methods

from :: Cursor -> Rep Cursor x #

to :: Rep Cursor x -> Cursor #

type Rep Cursor Source # 
type Rep Cursor = D1 (MetaData "Cursor" "Graphics.UI.GLFW.Types" "GLFW-b-1.4.8.1-Al6jnUrPA9PAgpgZuphRiw" True) (C1 (MetaCons "Cursor" PrefixI True) (S1 (MetaSel (Just Symbol "unCursor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ptr C'GLFWcursor))))

data StandardCursorShape Source #

Instances

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

Methods

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

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

toConstr :: StandardCursorShape -> Constr #

dataTypeOf :: StandardCursorShape -> DataType #

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

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

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

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

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

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

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

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

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

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

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

type CharCallback = Window -> Char -> IO () Source #

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.

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

Time

Context

Clipboard