sdl2-2.4.1.0: Both high- and low-level bindings to the SDL library (version 2.0.4+).

Safe HaskellNone
LanguageHaskell2010

SDL.Video.OpenGL

Contents

Synopsis

Creating and Configuring OpenGL Contexts

data OpenGLConfig Source #

Configuration used when creating an OpenGL rendering context.

Constructors

OpenGLConfig 

Fields

Instances

Eq OpenGLConfig Source # 
Ord OpenGLConfig Source # 
Read OpenGLConfig Source # 
Show OpenGLConfig Source # 
Generic OpenGLConfig Source # 

Associated Types

type Rep OpenGLConfig :: * -> * #

type Rep OpenGLConfig Source # 
type Rep OpenGLConfig = D1 * (MetaData "OpenGLConfig" "SDL.Video.OpenGL" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "OpenGLConfig" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "glColorPrecision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (V4 CInt))) (S1 * (MetaSel (Just Symbol "glDepthPrecision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CInt))) ((:*:) * (S1 * (MetaSel (Just Symbol "glStencilPrecision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CInt)) ((:*:) * (S1 * (MetaSel (Just Symbol "glMultisampleSamples") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CInt)) (S1 * (MetaSel (Just Symbol "glProfile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Profile))))))

data GLContext Source #

A created OpenGL context.

Instances

glCreateContext :: (Functor m, MonadIO m) => Window -> m GLContext Source #

Create a new OpenGL context and makes it the current context for the window.

Throws SDLException if the window wasn't configured with OpenGL support, or if context creation fails.

See SDL_GL_CreateContext for C documentation.

data Profile Source #

The profile a driver should use when creating an OpenGL context.

Constructors

Core Mode CInt CInt

Use the OpenGL core profile, with a given major and minor version

Compatibility Mode CInt CInt

Use the compatibilty profile with a given major and minor version. The compatibility profile allows you to use deprecated functions such as immediate mode

ES Mode CInt CInt

Use an OpenGL profile for embedded systems

Instances

Eq Profile Source # 

Methods

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

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

Ord Profile Source # 
Read Profile Source # 
Show Profile Source # 
Generic Profile Source # 

Associated Types

type Rep Profile :: * -> * #

Methods

from :: Profile -> Rep Profile x #

to :: Rep Profile x -> Profile #

type Rep Profile Source # 

data Mode Source #

The mode a driver should use when creating an OpenGL context.

Constructors

Normal

A normal profile with no special debugging support

Debug

Use a debug context, allowing the usage of extensions such as GL_ARB_debug_output

Instances

Bounded Mode Source # 
Enum Mode Source # 

Methods

succ :: Mode -> Mode #

pred :: Mode -> Mode #

toEnum :: Int -> Mode #

fromEnum :: Mode -> Int #

enumFrom :: Mode -> [Mode] #

enumFromThen :: Mode -> Mode -> [Mode] #

enumFromTo :: Mode -> Mode -> [Mode] #

enumFromThenTo :: Mode -> Mode -> Mode -> [Mode] #

Eq Mode Source # 

Methods

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

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

Data Mode Source # 

Methods

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

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

toConstr :: Mode -> Constr #

dataTypeOf :: Mode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Mode Source # 

Methods

compare :: Mode -> Mode -> Ordering #

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

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

(>) :: Mode -> Mode -> Bool #

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

max :: Mode -> Mode -> Mode #

min :: Mode -> Mode -> Mode #

Read Mode Source # 
Show Mode Source # 

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Generic Mode Source # 

Associated Types

type Rep Mode :: * -> * #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

type Rep Mode Source # 
type Rep Mode = D1 * (MetaData "Mode" "SDL.Video.OpenGL" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) ((:+:) * (C1 * (MetaCons "Normal" PrefixI False) (U1 *)) (C1 * (MetaCons "Debug" PrefixI False) (U1 *)))

glMakeCurrent :: (Functor m, MonadIO m) => Window -> GLContext -> m () Source #

Set up an OpenGL context for rendering into an OpenGL window.

Throws SDLException on failure.

See SDL_GL_MakeCurrent for C documentation.

glDeleteContext :: MonadIO m => GLContext -> m () Source #

Delete the given OpenGL context.

You must make sure that there are no pending commands in the OpenGL command queue, the driver may still be processing commands even if you have stopped issuing them!

The glFinish command will block until the command queue has been fully processed. You should call that function before deleting a context.

See SDL_GL_DeleteContext for C documentation.

Querying for the drawable size without a Renderer

glGetDrawableSize :: MonadIO m => Window -> m (V2 CInt) Source #

Get the size of a window's underlying drawable area in pixels (for use with glViewport).

It may differ from windowSize if window was created with windowHighDPI flag.

Swapping

The process of "swapping" means to move the back-buffer into the window contents itself.

glSwapWindow :: MonadIO m => Window -> m () Source #

Replace the contents of the front buffer with the back buffer's. The contents of the back buffer are undefined, clear them with glClear or equivalent before drawing to them again.

See SDL_GL_SwapWindow for C documentation.

data SwapInterval Source #

The swap interval for the current OpenGL context.

Constructors

ImmediateUpdates

No vertical retrace synchronization

SynchronizedUpdates

The buffer swap is synchronized with the vertical retrace

LateSwapTearing 

Instances

Bounded SwapInterval Source # 
Enum SwapInterval Source # 
Eq SwapInterval Source # 
Data SwapInterval Source # 

Methods

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

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

toConstr :: SwapInterval -> Constr #

dataTypeOf :: SwapInterval -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SwapInterval Source # 
Read SwapInterval Source # 
Show SwapInterval Source # 
Generic SwapInterval Source # 

Associated Types

type Rep SwapInterval :: * -> * #

ToNumber SwapInterval CInt Source # 
FromNumber SwapInterval CInt Source # 
type Rep SwapInterval Source # 
type Rep SwapInterval = D1 * (MetaData "SwapInterval" "SDL.Video.OpenGL" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) ((:+:) * (C1 * (MetaCons "ImmediateUpdates" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "SynchronizedUpdates" PrefixI False) (U1 *)) (C1 * (MetaCons "LateSwapTearing" PrefixI False) (U1 *))))

swapInterval :: StateVar SwapInterval Source #

Get or set the swap interval for the current OpenGL context.

This StateVar can be modified using $= and the current value retrieved with get.

See SDL_GL_SetSwapInterval and SDL_GL_GetSwapInterval for C documentation.

Function Loading