Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Graphics.UI.GlfwG.Window
Synopsis
- data W s
- create :: Int -> Int -> String -> Maybe Monitor -> Maybe Window -> (forall s. W s -> IO a) -> IO a
- data Group s k
- group :: (forall s. Group s k -> IO a) -> IO a
- create' :: Ord k => Group s k -> k -> Int -> Int -> String -> Maybe Monitor -> Maybe Window -> IO (Either String (W s))
- unsafeDestroy :: Ord k => Group s k -> k -> IO (Either String ())
- lookup :: Ord k => Group s k -> k -> IO (Maybe (W s))
- shouldClose :: W sw -> IO Bool
- setShouldClose :: W sw -> Bool -> IO ()
- hint :: WindowHint -> IO ()
- data WindowHint
- = WindowHint'Resizable !Bool
- | WindowHint'Visible !Bool
- | WindowHint'Decorated !Bool
- | WindowHint'RedBits !(Maybe Int)
- | WindowHint'GreenBits !(Maybe Int)
- | WindowHint'BlueBits !(Maybe Int)
- | WindowHint'AlphaBits !(Maybe Int)
- | WindowHint'DepthBits !(Maybe Int)
- | WindowHint'StencilBits !(Maybe Int)
- | WindowHint'AccumRedBits !(Maybe Int)
- | WindowHint'AccumGreenBits !(Maybe Int)
- | WindowHint'AccumBlueBits !(Maybe Int)
- | WindowHint'AccumAlphaBits !(Maybe Int)
- | WindowHint'AuxBuffers !(Maybe Int)
- | WindowHint'Samples !(Maybe Int)
- | WindowHint'RefreshRate !(Maybe Int)
- | WindowHint'DoubleBuffer !Bool
- | WindowHint'Stereo !Bool
- | WindowHint'sRGBCapable !Bool
- | WindowHint'Floating !Bool
- | WindowHint'Focused !Bool
- | WindowHint'Maximized !Bool
- | WindowHint'AutoIconify !Bool
- | WindowHint'ClientAPI !ClientAPI
- | WindowHint'ContextCreationAPI !ContextCreationAPI
- | WindowHint'ContextVersionMajor !Int
- | WindowHint'ContextVersionMinor !Int
- | WindowHint'ContextRobustness !ContextRobustness
- | WindowHint'ContextReleaseBehavior !ContextReleaseBehavior
- | WindowHint'ContextNoError !Bool
- | WindowHint'OpenGLForwardCompat !Bool
- | WindowHint'OpenGLDebugContext !Bool
- | WindowHint'OpenGLProfile !OpenGLProfile
- | WindowHint'TransparentFramebuffer !Bool
- | WindowHint'CenterCursor !Bool
- | WindowHint'FocusOnShow !Bool
- | WindowHint'ScaleToMonitor !Bool
- | WindowHint'CocoaRetinaFramebuffer !Bool
- | WindowHint'CocoaGraphicsSwitching !Bool
- | WindowHint'CocoaFrameName !String
- | WindowHint'X11ClassName !String
- | WindowHint'X11InstanceName !String
- data ClientAPI
- getSize :: W sw -> IO (Int, Int)
- setSize :: W sw -> Int -> Int -> IO ()
- getFrameSize :: W sw -> IO (Int, Int, Int, Int)
- getFramebufferSize :: W sw -> IO (Int, Int)
- setKeyCallback :: W s -> Maybe (KeyCallback s) -> IO ()
- type KeyCallback s = W s -> Key -> Int -> KeyState -> ModifierKeys -> IO ()
- setFramebufferSizeCallback :: W s -> Maybe FramebufferSizeCallback -> IO ()
- type FramebufferSizeCallback = Window -> Int -> Int -> IO ()
- getKey :: W sw -> Key -> IO KeyState
CREATE AND DESTROY
create :: Int -> Int -> String -> Maybe Monitor -> Maybe Window -> (forall s. W s -> 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 #
HINT
hint :: WindowHint -> IO () Source #
data WindowHint #
Lets you set various window hints before creating a Window
.
See Window Hints,
particularly Supported and Default Values.
Constructors
Instances
The type of OpenGL to create a context for.
Constructors
ClientAPI'NoAPI | |
ClientAPI'OpenGL | |
ClientAPI'OpenGLES |
Instances
Data ClientAPI | |
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 | |
Enum ClientAPI | |
Defined in Graphics.UI.GLFW.Types Methods succ :: ClientAPI -> ClientAPI # pred :: ClientAPI -> ClientAPI # fromEnum :: ClientAPI -> Int # enumFrom :: ClientAPI -> [ClientAPI] # enumFromThen :: ClientAPI -> ClientAPI -> [ClientAPI] # enumFromTo :: ClientAPI -> ClientAPI -> [ClientAPI] # enumFromThenTo :: ClientAPI -> ClientAPI -> ClientAPI -> [ClientAPI] # | |
Generic ClientAPI | |
Read ClientAPI | |
Show ClientAPI | |
NFData ClientAPI | |
Defined in Graphics.UI.GLFW.Types | |
Eq ClientAPI | |
Ord ClientAPI | |
type Rep ClientAPI | |
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
CALLBACK
setKeyCallback :: W s -> Maybe (KeyCallback s) -> IO () Source #
type KeyCallback s = W s -> Key -> Int -> KeyState -> ModifierKeys -> IO () Source #
setFramebufferSizeCallback :: W s -> Maybe FramebufferSizeCallback -> IO () Source #
type FramebufferSizeCallback = Window -> Int -> Int -> IO () #
Fires when the size of the framebuffer for the window changes (in Pixels).