GPipe-2.2.5: Typesafe functional GPU graphics programming

Safe HaskellNone
LanguageHaskell98

Graphics.GPipe.Context

Contents

Description

A Context in GPipe (just as in OpenGl) consist of two things, a window and an object space. The object space consists of Buffers, Textures and Shaders. You may create a context without a window (for example for rendering to textures that are saved as pngs instead of showed), and you can create a context that shares the object space with another context.

Context creation is abstracted away from GPipe, and you need a package that provides a ContextFactory, such as GPipe-GLFW.

Synopsis

Contexts

data ContextT ctx os m a Source #

The monad transformer that encapsulates a GPipe context (which wraps an OpenGl context).

A value of type ContextT ctx os m a is an action on a context with these parameters:

ctx
The context handler.
os
An abstract type that is used to denote the object space. This is an forall type defined by the runContextT call which will restrict any objects created inside this context to be returned from it or used by another context (the same trick as the ST monad uses).
m
The monad this monad transformer wraps. Need to have IO in the bottom for this ContextT to be runnable.
a
The value returned from this monad action.
Instances
MonadTrans (ContextT ctx os) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

lift :: Monad m => m a -> ContextT ctx os m a #

Monad m => Monad (ContextT ctx os m) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

(>>=) :: ContextT ctx os m a -> (a -> ContextT ctx os m b) -> ContextT ctx os m b #

(>>) :: ContextT ctx os m a -> ContextT ctx os m b -> ContextT ctx os m b #

return :: a -> ContextT ctx os m a #

fail :: String -> ContextT ctx os m a #

Functor m => Functor (ContextT ctx os m) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

fmap :: (a -> b) -> ContextT ctx os m a -> ContextT ctx os m b #

(<$) :: a -> ContextT ctx os m b -> ContextT ctx os m a #

MonadIO m => MonadFail (ContextT ctx os m) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

fail :: String -> ContextT ctx os m a #

Monad m => Applicative (ContextT ctx os m) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

pure :: a -> ContextT ctx os m a #

(<*>) :: ContextT ctx os m (a -> b) -> ContextT ctx os m a -> ContextT ctx os m b #

liftA2 :: (a -> b -> c) -> ContextT ctx os m a -> ContextT ctx os m b -> ContextT ctx os m c #

(*>) :: ContextT ctx os m a -> ContextT ctx os m b -> ContextT ctx os m b #

(<*) :: ContextT ctx os m a -> ContextT ctx os m b -> ContextT ctx os m a #

MonadIO m => MonadIO (ContextT ctx os m) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

liftIO :: IO a -> ContextT ctx os m a #

MonadException m => MonadException (ContextT ctx os m) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

throw :: Exception e => e -> ContextT ctx os m a #

catch :: Exception e => ContextT ctx os m a -> (e -> ContextT ctx os m a) -> ContextT ctx os m a #

finally :: ContextT ctx os m a -> ContextT ctx os m b -> ContextT ctx os m a #

MonadAsyncException m => MonadAsyncException (ContextT ctx os m) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

mask :: ((forall a. ContextT ctx os m a -> ContextT ctx os m a) -> ContextT ctx os m b) -> ContextT ctx os m b #

runContextT :: (MonadIO m, MonadAsyncException m, ContextHandler ctx) => ContextHandlerParameters ctx -> (forall os. ContextT ctx os m a) -> m a Source #

Run a ContextT monad transformer that encapsulates an object space. You need an implementation of a ContextHandler, which is provided by an auxillary package, such as GPipe-GLFW.

Windows

data Window os c ds Source #

Instances
Eq (Window os c ds) Source # 
Instance details

Defined in Graphics.GPipe.Internal.Context

Methods

(==) :: Window os c ds -> Window os c ds -> Bool #

(/=) :: Window os c ds -> Window os c ds -> Bool #

newWindow :: (ContextHandler ctx, MonadIO m) => WindowFormat c ds -> WindowParameters ctx -> ContextT ctx os m (Window os c ds) Source #

Creates a window

deleteWindow :: (ContextHandler ctx, MonadIO m) => Window os c ds -> ContextT ctx os m () Source #

Deletes a window. Any rendering to this window will become a noop.

getFrameBufferSize :: (ContextHandler ctx, MonadIO m) => Window os c ds -> ContextT ctx os m (V2 Int) Source #

Return the current size of the context frame buffer. This is needed to set viewport size and to get the aspect ratio to calculate projection matrices.

swapWindowBuffers :: (ContextHandler ctx, MonadIO m) => Window os c ds -> ContextT ctx os m () Source #

Run this action after a render call to swap out the context windows back buffer with the front buffer, effectively showing the result. This call may block if vsync is enabled in the system and/or too many frames are outstanding. After this call, the context window content is undefined and should be cleared at earliest convenience using clearContextColor and friends.

withContextWindow :: MonadIO m => Window os c ds -> (Maybe (ContextWindow ctx) -> IO a) -> ContextT ctx os m a Source #

Use the context window handle, which type is specific to the window system used. This handle shouldn't be returned from this function

Extending interface

class ContextHandler ctx where Source #

Class implementing a window handler that can create openGL contexts, such as GLFW or GLUT

Associated Types

data ContextHandlerParameters ctx Source #

Implementation specific context handler parameters, eg error handling and event processing policies

type ContextWindow ctx Source #

Implementation specific window type

type WindowParameters ctx Source #

Implementation specific window parameters, eg initial size and border decoration

Methods

contextHandlerCreate :: ContextHandlerParameters ctx -> IO ctx Source #

Create a context handler. Called from the main thread

contextHandlerDelete :: ctx -> IO () Source #

Delete the context handler. All contexts created from this handler will be deleted using contextDelete prior to calling this.

createContext :: ctx -> Maybe (WindowBits, WindowParameters ctx) -> IO (ContextWindow ctx) Source #

Create a new context sharing all other contexts created by this ContextHandler. If the parameter is Nothing, a hidden off-screen context is created, otherwise creates a window with the provided window bits and implementation specific parameters. Only ever called from the mainthread (i.e. the thread that called contextHandlerCreate).

contextDoAsync :: ctx -> Maybe (ContextWindow ctx) -> IO () -> IO () Source #

Run an OpenGL IO action in this context, that doesn't return any value to the caller. This may be run after contextDelete or contextHandlerDelete has been called. The thread calling this may not be the same creating the context (for finalizers it is most definetly not). May also be called on previously deleted windows in the case of finalizers.

contextSwap :: ctx -> ContextWindow ctx -> IO () Source #

Swap the front and back buffers in the context's default frame buffer. Only ever called from the mainthread (i.e. the thread that called contextHandlerCreate). Never called on deleted windows.

contextFrameBufferSize :: ctx -> ContextWindow ctx -> IO (Int, Int) Source #

Get the current size of the context's default framebuffer (which may change if the window is resized). Only ever called from the mainthread (i.e. the thread that called contextHandlerCreate)

contextDelete :: ctx -> ContextWindow ctx -> IO () Source #

Delete a context and close any associated window. Only ever called from the mainthread (i.e. the thread that called contextHandlerCreate). Only ever called once per window, and will always be called for each window before the context is deleted with contextHandlerDelete.

Hardware exceptions

data GPipeException Source #

This kind of exception may be thrown from GPipe when a GPU hardware limit is reached (for instance, too many textures are drawn to from the same FragmentStream)

Constructors

GPipeException String