Safe Haskell | None |
---|---|
Language | Haskell2010 |
Window manipulation functions covering much of the GLFW Window guide: http://www.glfw.org/docs/latest/window_guide.html. Notably absent are the window creation functions. These are handled automatically by GPipe-GLFW.
Actions are in the GPipe ContextT
monad when a window handle is required,
otherwise they are bare reexported IO actions which can be lifted into the ContextT
monad.
The Window
taken by many of these functions is the window resource from GPipe.
Synopsis
- windowShouldClose :: MonadIO m => Window os c ds -> ContextT Handle os m (Maybe Bool)
- setWindowShouldClose :: MonadIO m => Window os c ds -> Bool -> ContextT Handle os m (Maybe ())
- setWindowCloseCallback :: MonadIO m => Window os c ds -> Maybe (IO ()) -> ContextT Handle os m (Maybe ())
- getWindowSize :: MonadIO m => Window os c ds -> ContextT Handle os m (Maybe (Int, Int))
- setWindowSizeCallback :: MonadIO m => Window os c ds -> Maybe (Int -> Int -> IO ()) -> ContextT Handle os m (Maybe ())
- getFrameBufferSize :: forall ctx (m :: Type -> Type) os c ds. (ContextHandler ctx, MonadIO m) => Window os c ds -> ContextT ctx os m (V2 Int)
Window objects
Window event processing
GLFW event processing is performed by 'GPipe-GLFW' after each call to the GPipe
swapBuffers
.
No further action is required, but additional controls are available for complex applications in
Graphics.GPipe.Context.GLFW.
Window properties and events
Window closing and close flag
setWindowShouldClose :: MonadIO m => Window os c ds -> Bool -> ContextT Handle os m (Maybe ()) Source #
setWindowCloseCallback :: MonadIO m => Window os c ds -> Maybe (IO ()) -> ContextT Handle os m (Maybe ()) Source #
Window size
setWindowSizeCallback :: MonadIO m => Window os c ds -> Maybe (Int -> Int -> IO ()) -> ContextT Handle os m (Maybe ()) Source #
Framebuffer size
Reexported from Graphics.GPipe.Context.
getFrameBufferSize :: forall ctx (m :: Type -> Type) os c ds. (ContextHandler ctx, MonadIO m) => Window os c ds -> ContextT ctx os m (V2 Int) #
Buffer swapping
Buffer swapping is initiated via the GPipe
swapBuffers
function.
Not supported
Some GLFW functionality isn't currently exposed by Graphics.UI.GLFW.
glfwSetWindowUserPointer
,glfwGetWindowUserPointer