glfw-group-0.1.0.0: GLFW package with window groups destroyed together
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.UI.GlfwG.Window

Synopsis

CREATE AND DESTROY

data W s Source #

Instances

Instances details
Show (W s) Source # 
Instance details

Defined in Graphics.UI.GlfwG.Window.Type

Methods

showsPrec :: Int -> W s -> ShowS #

show :: W s -> String #

showList :: [W s] -> ShowS #

Eq (W s) Source # 
Instance details

Defined in Graphics.UI.GlfwG.Window.Type

Methods

(==) :: W s -> W s -> Bool #

(/=) :: W s -> W s -> Bool #

Ord (W s) Source # 
Instance details

Defined in Graphics.UI.GlfwG.Window.Type

Methods

compare :: W s -> W s -> Ordering #

(<) :: W s -> W s -> Bool #

(<=) :: W s -> W s -> Bool #

(>) :: W s -> W s -> Bool #

(>=) :: W s -> W s -> Bool #

max :: W s -> W s -> W s #

min :: W s -> W s -> W s #

create :: Int -> Int -> String -> Maybe Monitor -> Maybe Window -> (forall s. W s -> IO a) -> IO a Source #

data Group s k Source #

group :: (forall s. Group s k -> IO a) -> IO a Source #

create' :: Ord k => Group s k -> k -> Int -> Int -> String -> Maybe Monitor -> Maybe Window -> IO (Either String (W s)) Source #

unsafeDestroy :: Ord k => Group s k -> k -> IO (Either String ()) Source #

lookup :: Ord k => Group s k -> k -> IO (Maybe (W s)) Source #

setShouldClose :: W sw -> Bool -> IO () Source #

HINT

data WindowHint #

Lets you set various window hints before creating a Window. See Window Hints, particularly Supported and Default Values.

Instances

Instances details
Data WindowHint 
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 #

Generic WindowHint 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep WindowHint :: Type -> Type #

Read WindowHint 
Instance details

Defined in Graphics.UI.GLFW.Types

Show WindowHint 
Instance details

Defined in Graphics.UI.GLFW.Types

NFData WindowHint 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: WindowHint -> () #

Eq WindowHint 
Instance details

Defined in Graphics.UI.GLFW.Types

Ord WindowHint 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep WindowHint 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep WindowHint = D1 ('MetaData "WindowHint" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.1-CbbIOqvtyyzkbPgJI2V5g" '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 ClientAPI #

The type of OpenGL to create a context for.

Instances

Instances details
Data ClientAPI 
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 #

Bounded ClientAPI 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum ClientAPI 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic ClientAPI 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep ClientAPI :: Type -> Type #

Read ClientAPI 
Instance details

Defined in Graphics.UI.GLFW.Types

Show ClientAPI 
Instance details

Defined in Graphics.UI.GLFW.Types

NFData ClientAPI 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: ClientAPI -> () #

Eq ClientAPI 
Instance details

Defined in Graphics.UI.GLFW.Types

Ord ClientAPI 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep ClientAPI 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep ClientAPI = D1 ('MetaData "ClientAPI" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.1-CbbIOqvtyyzkbPgJI2V5g" '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)))

PARAMETER

getSize :: W sw -> IO (Int, Int) Source #

setSize :: W sw -> Int -> Int -> IO () Source #

CALLBACK

type KeyCallback s = W s -> Key -> Int -> KeyState -> ModifierKeys -> IO () Source #

type FramebufferSizeCallback = Window -> Int -> Int -> IO () #

Fires when the size of the framebuffer for the window changes (in Pixels).

STATE

getKey :: W sw -> Key -> IO KeyState Source #