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

Safe HaskellNone
LanguageHaskell2010

SDL.Video.Renderer

Contents

Description

SDL.Video.Renderer provides a high-level interface to SDL's accelerated 2D rendering library.

Synopsis

Documentation

data Renderer Source #

An SDL rendering device. This can be created with createRenderer.

Instances

Eq Renderer Source # 
Data Renderer Source # 

Methods

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

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

toConstr :: Renderer -> Constr #

dataTypeOf :: Renderer -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Renderer Source # 
Show Renderer Source # 
Generic Renderer Source # 

Associated Types

type Rep Renderer :: * -> * #

Methods

from :: Renderer -> Rep Renderer x #

to :: Rep Renderer x -> Renderer #

type Rep Renderer Source # 
type Rep Renderer = D1 (MetaData "Renderer" "SDL.Internal.Types" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" True) (C1 (MetaCons "Renderer" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Renderer)))

Renderer Configuration

These configuration options can be used with createRenderer to create Renderers.

data RendererConfig Source #

The configuration data used when creating windows.

Constructors

RendererConfig 

Fields

Instances

Eq RendererConfig Source # 
Data RendererConfig Source # 

Methods

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

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

toConstr :: RendererConfig -> Constr #

dataTypeOf :: RendererConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RendererConfig Source # 
Read RendererConfig Source # 
Show RendererConfig Source # 
Generic RendererConfig Source # 

Associated Types

type Rep RendererConfig :: * -> * #

ToNumber RendererConfig Word32 Source # 
FromNumber RendererConfig Word32 Source # 
type Rep RendererConfig Source # 
type Rep RendererConfig = D1 (MetaData "RendererConfig" "SDL.Video.Renderer" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" False) (C1 (MetaCons "RendererConfig" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "rendererType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RendererType)) (S1 (MetaSel (Just Symbol "rendererTargetTexture") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))

data RendererType Source #

Renderer acceleration mode

Constructors

UnacceleratedRenderer

The renderer does not use hardware acceleration

AcceleratedRenderer

The renderer uses hardware acceleration and refresh rate is ignored

AcceleratedVSyncRenderer

The renderer uses hardware acceleration and present is synchronized with the refresh rate

SoftwareRenderer

The renderer is a software fallback

Instances

Bounded RendererType Source # 
Enum RendererType Source # 
Eq RendererType Source # 
Data RendererType Source # 

Methods

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

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

toConstr :: RendererType -> Constr #

dataTypeOf :: RendererType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RendererType Source # 
Read RendererType Source # 
Show RendererType Source # 
Generic RendererType Source # 

Associated Types

type Rep RendererType :: * -> * #

type Rep RendererType Source # 
type Rep RendererType = D1 (MetaData "RendererType" "SDL.Video.Renderer" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" False) ((:+:) ((:+:) (C1 (MetaCons "UnacceleratedRenderer" PrefixI False) U1) (C1 (MetaCons "AcceleratedRenderer" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AcceleratedVSyncRenderer" PrefixI False) U1) (C1 (MetaCons "SoftwareRenderer" PrefixI False) U1)))

Drawing Primitives

clear :: (Functor m, MonadIO m) => Renderer -> m () Source #

Clear the current rendering target with the drawing color.

See SDL_RenderClear for C documentation.

copy Source #

Arguments

:: MonadIO m 
=> Renderer

The rendering context

-> Texture

The source texture

-> Maybe (Rectangle CInt)

The source rectangle to copy, or Nothing for the whole texture

-> Maybe (Rectangle CInt)

The destination rectangle to copy to, or Nothing for the whole rendering target. The texture will be stretched to fill the given rectangle.

-> m () 

Copy a portion of the texture to the current rendering target.

See SDL_RenderCopy for C documentation.

copyEx Source #

Arguments

:: MonadIO m 
=> Renderer

The rendering context

-> Texture

The source texture

-> Maybe (Rectangle CInt)

The source rectangle to copy, or Nothing for the whole texture

-> Maybe (Rectangle CInt)

The destination rectangle to copy to, or Nothing for the whole rendering target. The texture will be stretched to fill the given rectangle.

-> CDouble

An angle in degrees that indicates the point around which the destination rectangle will be rotated.

-> Maybe (Point V2 CInt)

The point of rotation

-> V2 Bool

Whether to flip in the X or Y axis.

-> m ()

Whether to flip in the X or Y axis.

Copy a portion of the texture to the current rendering target, optionally rotating it by angle around the given center and also flipping it top-bottom and/or left-right.

See SDL_RenderCopyEx for C documentation.

drawLine Source #

Arguments

:: (Functor m, MonadIO m) 
=> Renderer 
-> Point V2 CInt

The start point of the line

-> Point V2 CInt

The end point of the line

-> m () 

Draw a line on the current rendering target.

See SDL_RenderDrawLine for C documentation.

drawLines Source #

Arguments

:: MonadIO m 
=> Renderer 
-> Vector (Point V2 CInt)

A Vector of points along the line. SDL will draw lines between these points.

-> m () 

Draw a series of connected lines on the current rendering target.

See SDL_RenderDrawLines for C documentation.

drawPoint :: (Functor m, MonadIO m) => Renderer -> Point V2 CInt -> m () Source #

Draw a point on the current rendering target.

See SDL_RenderDrawPoint for C documentation.

drawPoints :: MonadIO m => Renderer -> Vector (Point V2 CInt) -> m () Source #

Draw multiple points on the current rendering target.

See SDL_RenderDrawPoints for C documentation.

drawRect Source #

Arguments

:: MonadIO m 
=> Renderer 
-> Maybe (Rectangle CInt)

The rectangle outline to draw. Nothing for the entire rendering context.

-> m () 

Draw a rectangle outline on the current rendering target.

See SDL_RenderDrawRect for C documentation.

drawRects :: MonadIO m => Renderer -> Vector (Rectangle CInt) -> m () Source #

Draw some number of rectangles on the current rendering target.

See SDL_RenderDrawRects for C documentation.

fillRect Source #

Arguments

:: MonadIO m 
=> Renderer 
-> Maybe (Rectangle CInt)

The rectangle to fill. Nothing for the entire rendering context.

-> m () 

Fill a rectangle on the current rendering target with the drawing color.

See SDL_RenderFillRect for C documentation.

fillRects :: MonadIO m => Renderer -> Vector (Rectangle CInt) -> m () Source #

Fill some number of rectangles on the current rendering target with the drawing color.

See SDL_RenderFillRects for C documentation.

present :: MonadIO m => Renderer -> m () Source #

Update the screen with any rendering performed since the previous call.

SDL's rendering functions operate on a backbuffer; that is, calling a rendering function such as drawLine does not directly put a line on the screen, but rather updates the backbuffer. As such, you compose your entire scene and present the composed backbuffer to the screen as a complete picture.

Therefore, when using SDL's rendering API, one does all drawing intended for the frame, and then calls this function once per frame to present the final drawing to the user.

The backbuffer should be considered invalidated after each present; do not assume that previous contents will exist between frames. You are strongly encouraged to call clear to initialize the backbuffer before starting each new frame's drawing, even if you plan to overwrite every pixel.

See SDL_RenderPresent for C documentation.

Renderer State

SDL exposes a stateful interface to Renderers - the above primitives drawing routines will change their output depending on the value of these state variables.

rendererDrawBlendMode :: Renderer -> StateVar BlendMode Source #

Get or set the blend mode used for drawing operations (fill and line).

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

See SDL_SetRenderDrawBlendMode and SDL_GetRenderDrawBlendMode for C documentation.

rendererDrawColor :: Renderer -> StateVar (V4 Word8) Source #

Get or set the color used for drawing operations (rect, line and clear).

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

See SDL_SetRenderDrawColor and SDL_GetRenderDrawColor for C documentation.

rendererRenderTarget :: Renderer -> StateVar (Maybe Texture) Source #

Get or set the current render target. Nothing corresponds to the default render target.

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

See SDL_SetRenderTarget and SDL_GetRenderTarget for C documentation.

rendererClipRect :: Renderer -> StateVar (Maybe (Rectangle CInt)) Source #

Get or set the clip rectangle for rendering on the specified target.

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

See SDL_RenderSetClipRect and SDL_RenderGetClipRect for C documentation.

rendererLogicalSize :: Renderer -> StateVar (Maybe (V2 CInt)) Source #

Get or set the device independent resolution for rendering.

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

See SDL_RenderSetLogicalSize and SDL_RenderGetLogicalSize for C documentation.

rendererScale :: Renderer -> StateVar (V2 CFloat) Source #

Get or set the drawing scale for rendering on the current target.

The drawing coordinates are scaled by the x/y scaling factors before they are used by the renderer. This allows resolution independent drawing with a single coordinate system.

If this results in scaling or subpixel drawing by the rendering backend, it will be handled using the appropriate quality hints. For best results use integer scaling factors.

See SDL_RenderSetScale and SDL_RenderGetScale for C documentation.

rendererViewport :: Renderer -> StateVar (Maybe (Rectangle CInt)) Source #

Get or set the drawing area for rendering on the current target.

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

See SDL_RenderSetViewport and SDL_RenderGetViewport for C documentation.

renderTargetSupported :: MonadIO m => Renderer -> m Bool Source #

Determine whether a window supports the use of render targets.

See SDL_RenderTargetSupported for C documentation.

Surfaces

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

Copy the window surface to the screen.

This is the function you use to reflect any changes to the surface on the screen.

See SDL_UpdateWindowSurface for C documentation.

surfaceBlit Source #

Arguments

:: MonadIO m 
=> Surface

The Surface to be copied from

-> Maybe (Rectangle CInt)

The rectangle to be copied, or Nothing to copy the entire surface

-> Surface

The Surface that is the blit target

-> Maybe (Point V2 CInt)

The position to blit to

-> m (Maybe (Rectangle CInt)) 

Perform a fast surface copy to a destination surface.

See SDL_BlitSurface for C documentation.

surfaceBlitScaled Source #

Arguments

:: MonadIO m 
=> Surface

The Surface to be copied from

-> Maybe (Rectangle CInt)

The rectangle to be copied, or Nothing to copy the entire surface

-> Surface

The Surface that is the blit target

-> Maybe (Rectangle CInt)

The rectangle that is copied into, or Nothing to copy into the entire surface

-> m () 

Perform a scaled surface copy to a destination surface.

See SDL_BlitScaled for C documentation.

surfaceFillRect Source #

Arguments

:: MonadIO m 
=> Surface

The Surface that is the drawing target.

-> Maybe (Rectangle CInt)

The rectangle to fill, or Nothing to fill the entire surface.

-> V4 Word8

The color to fill with. If the color value contains an alpha component then the destination is simply filled with that alpha information, no blending takes place. This colour will be implictly mapped to the closest approximation that matches the surface's pixel format.

-> m () 

Perform a fast fill of a rectangle with a specific color.

If there is a clip rectangle set on the destination (set via clipRect), then this function will fill based on the intersection of the clip rectangle and the given Rectangle.

See SDL_FillRect for C documentation.

surfaceFillRects Source #

Arguments

:: MonadIO m 
=> Surface

The Surface that is the drawing target.

-> Vector (Rectangle CInt)

A Vector of Rectangles to be filled.

-> V4 Word8

The color to fill with. If the color value contains an alpha component then the destination is simply filled with that alpha information, no blending takes place. This colour will be implictly mapped to the closest approximation that matches the surface's pixel format.

-> m () 

Perform a fast fill of a set of rectangles with a specific color.

If there is a clip rectangle set on any of the destinations (set via clipRect), then this function will fill based on the intersection of the clip rectangle and the given Rectangles.

See SDL_FillRects for C documentation.

Creating and Destroying Surfaces

convertSurface Source #

Arguments

:: (Functor m, MonadIO m) 
=> Surface

The Surface to convert

-> SurfacePixelFormat

The pixel format that the new surface is optimized for

-> m Surface 

Copy an existing surface into a new one that is optimized for blitting to a surface of a specified pixel format.

This function is used to optimize images for faster repeat blitting. This is accomplished by converting the original and storing the result as a new surface. The new, optimized surface can then be used as the source for future blits, making them faster.

See SDL_ConvertSurface for C documentation.

createRGBSurface Source #

Arguments

:: (Functor m, MonadIO m) 
=> V2 CInt

The size of the surface

-> PixelFormat

The bit depth, red, green, blue and alpha mask for the pixels

-> m Surface 

Allocate a new RGB surface.

See SDL_CreateRGBSurface for C documentation.

createRGBSurfaceFrom Source #

Arguments

:: (Functor m, MonadIO m) 
=> IOVector Word8

The existing pixel data

-> V2 CInt

The size of the surface

-> CInt

The pitch - the length of a row of pixels in bytes

-> PixelFormat

The bit depth, red, green, blue and alpha mask for the pixels

-> m Surface 

Allocate a new RGB surface with existing pixel data.

See SDL_CreateRGBSurfaceFrom for C documentation.

freeSurface :: MonadIO m => Surface -> m () Source #

Free an RGB surface.

If the surface was created using createRGBSurfaceFrom then the pixel data is not freed.

See SDL_FreeSurface for the C documentation.

getWindowSurface :: (Functor m, MonadIO m) => Window -> m Surface Source #

Get the SDL surface associated with the window.

See SDL_GetWindowSurface for C documentation.

loadBMP :: MonadIO m => FilePath -> m Surface Source #

Load a surface from a BMP file.

See SDL_LoadBMP for C documentation.

Surface state

surfaceColorKey :: Surface -> StateVar (Maybe (V4 Word8)) Source #

Get or set the color key (transparent pixel color) for a surface.

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

See SDL_SetColorKey and SDL_GetColorKey for C documentation.

surfaceBlendMode :: Surface -> StateVar BlendMode Source #

Get or set the blend mode used for blit operations.

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

See SDL_SetSurfaceBlendMode and SDL_GetSurfaceBlendMode for C documentation.

surfaceDimensions :: MonadIO m => Surface -> m (V2 CInt) Source #

Retrive the width and height of a Surface.

surfaceFormat :: MonadIO m => Surface -> m SurfacePixelFormat Source #

Inspect the pixel format under a surface.

surfacePixels :: MonadIO m => Surface -> m (Ptr ()) Source #

Obtain the pointer to the underlying pixels in a surface. You should bracket this call with lockSurface and unlockSurface, respectively.

Accessing Surface Data

lockSurface :: MonadIO m => Surface -> m () Source #

Set up a surface for directly accessing the pixels.

See SDL_LockSurface for C documentation.

unlockSurface :: MonadIO m => Surface -> m () Source #

Release a surface after directly accessing the pixels.

See SDL_UnlockSurface for C documentation.

Palettes and pixel formats

data Palette Source #

Instances

data PixelFormat Source #

Instances

Bounded PixelFormat Source # 
Enum PixelFormat Source # 
Eq PixelFormat Source # 
Data PixelFormat Source # 

Methods

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

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

toConstr :: PixelFormat -> Constr #

dataTypeOf :: PixelFormat -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PixelFormat Source # 
Read PixelFormat Source # 
Show PixelFormat Source # 
Generic PixelFormat Source # 

Associated Types

type Rep PixelFormat :: * -> * #

ToNumber PixelFormat Word32 Source # 
FromNumber PixelFormat Word32 Source # 
type Rep PixelFormat Source # 
type Rep PixelFormat = D1 (MetaData "PixelFormat" "SDL.Video.Renderer" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Unknown" PrefixI False) U1) (C1 (MetaCons "Index1LSB" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Index1MSB" PrefixI False) U1) (C1 (MetaCons "Index4LSB" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Index4MSB" PrefixI False) U1) (C1 (MetaCons "Index8" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RGB332" PrefixI False) U1) ((:+:) (C1 (MetaCons "RGB444" PrefixI False) U1) (C1 (MetaCons "RGB555" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "BGR555" PrefixI False) U1) (C1 (MetaCons "ARGB4444" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RGBA4444" PrefixI False) U1) (C1 (MetaCons "ABGR4444" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "BGRA4444" PrefixI False) U1) (C1 (MetaCons "ARGB1555" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RGBA5551" PrefixI False) U1) ((:+:) (C1 (MetaCons "ABGR1555" PrefixI False) U1) (C1 (MetaCons "BGRA5551" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "RGB565" PrefixI False) U1) (C1 (MetaCons "BGR565" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RGB24" PrefixI False) U1) (C1 (MetaCons "BGR24" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "RGB888" PrefixI False) U1) (C1 (MetaCons "RGBX8888" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BGR888" PrefixI False) U1) ((:+:) (C1 (MetaCons "BGRX8888" PrefixI False) U1) (C1 (MetaCons "ARGB8888" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "RGBA8888" PrefixI False) U1) (C1 (MetaCons "ABGR8888" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BGRA8888" PrefixI False) U1) (C1 (MetaCons "ARGB2101010" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "YV12" PrefixI False) U1) (C1 (MetaCons "IYUV" PrefixI False) U1)) ((:+:) (C1 (MetaCons "YUY2" PrefixI False) U1) ((:+:) (C1 (MetaCons "UYVY" PrefixI False) U1) (C1 (MetaCons "YVYU" PrefixI False) U1)))))))

setPaletteColors Source #

Arguments

:: MonadIO m 
=> Palette

The Palette to modify

-> Vector (V4 Word8)

A Vector of colours to copy into the palette

-> CInt

The index of the first palette entry to modify

-> m () 

Set a range of colors in a palette.

See SDL_SetPaletteColors for C documentation.

pixelFormatToMasks :: MonadIO m => PixelFormat -> m (CInt, V4 Word32) Source #

Convert the given the enumerated pixel format to a bpp value and RGBA masks.

See SDL_PixelFormatEnumToMasks for C documentation.

masksToPixelFormat :: MonadIO m => CInt -> V4 Word32 -> m PixelFormat Source #

Convert a bpp value and RGBA masks to an enumerated pixel format.

See SDL_MasksToPixelFormatEnum for C documentation.

Textures

data Texture Source #

Instances

Creating, Using and Destroying Textures

createTexture Source #

Arguments

:: (Functor m, MonadIO m) 
=> Renderer

The rendering context.

-> PixelFormat 
-> TextureAccess 
-> V2 CInt

The size of the texture.

-> m Texture 

Create a texture for a rendering context.

See SDL_CreateTexture for C documentation.

data TextureAccess Source #

Information to the GPU about how you will use a texture.

Constructors

TextureAccessStatic

Changes rarely, cannot be locked

TextureAccessStreaming

changes frequently, can be locked

TextureAccessTarget

Can be used as a render target

Instances

Bounded TextureAccess Source # 
Enum TextureAccess Source # 
Eq TextureAccess Source # 
Data TextureAccess Source # 

Methods

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

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

toConstr :: TextureAccess -> Constr #

dataTypeOf :: TextureAccess -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TextureAccess Source # 
Read TextureAccess Source # 
Show TextureAccess Source # 
Generic TextureAccess Source # 

Associated Types

type Rep TextureAccess :: * -> * #

ToNumber TextureAccess CInt Source # 
FromNumber TextureAccess CInt Source # 
type Rep TextureAccess Source # 
type Rep TextureAccess = D1 (MetaData "TextureAccess" "SDL.Video.Renderer" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" False) ((:+:) (C1 (MetaCons "TextureAccessStatic" PrefixI False) U1) ((:+:) (C1 (MetaCons "TextureAccessStreaming" PrefixI False) U1) (C1 (MetaCons "TextureAccessTarget" PrefixI False) U1)))

createTextureFromSurface Source #

Arguments

:: (Functor m, MonadIO m) 
=> Renderer

The rendering context

-> Surface

The surface containing pixel data used to fill the texture

-> m Texture 

Create a texture from an existing surface.

See SDL_CreateTextureFromSurface for C documentation.

updateTexture Source #

Arguments

:: (Functor m, MonadIO m) 
=> Texture

The Texture to be updated

-> Maybe (Rectangle CInt)

The area to update, Nothing for entire texture

-> ByteString

The raw pixel data

-> CInt

The number of bytes in a row of pixel data, including padding between lines

-> m Texture 

Updates texture rectangle with new pixel data.

See SDL_UpdateTexture for C documentation.

destroyTexture :: MonadIO m => Texture -> m () Source #

Destroy the specified texture.

See SDL_DestroyTexture for the C documentation.

glBindTexture Source #

Arguments

:: (Functor m, MonadIO m) 
=> Texture

The texture to bind to the current OpenGL/ES/ES2 context

-> m () 

Bind an OpenGL/ES/ES2 texture to the current context for use with when rendering OpenGL primitives directly.

See SDL_GL_BindTexture for C documentation.

glUnbindTexture Source #

Arguments

:: (Functor m, MonadIO m) 
=> Texture

The texture to unbind from the current OpenGL/ES/ES2 context

-> m () 

Unbind an OpenGL/ES/ES2 texture from the current context.

See SDL_GL_UnbindTexture for C documentation.

Texture State

textureAlphaMod :: Texture -> StateVar Word8 Source #

Get or set the additional alpha value multiplied into render copy operations.

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

See SDL_SetTextureAlphaMod and SDL_GetTextureAlphaMod for C documentation.

textureBlendMode :: Texture -> StateVar BlendMode Source #

Get or set the blend mode used for texture copy operations.

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

See SDL_SetTextureBlendMode and SDL_GetTextureBlendMode for C documentation.

data BlendMode Source #

Blend modes used in copy and drawing operations.

Constructors

BlendNone

No blending

BlendAlphaBlend

Alpha blending.

dstRGB = (srcRGB * srcA) + (dstRGB * (1-srcA))
dstA = srcA + (dstA * (1-srcA))
BlendAdditive

Additive blending

dstRGB = (srcRGB * srcA) + dstRGB
dstA = dstA
BlendMod

Color modulate

@ dstRGB = srcRGB * dstRGB dstA = dstA

Instances

Bounded BlendMode Source # 
Enum BlendMode Source # 
Eq BlendMode Source # 
Data BlendMode Source # 

Methods

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

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

toConstr :: BlendMode -> Constr #

dataTypeOf :: BlendMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BlendMode Source # 
Read BlendMode Source # 
Show BlendMode Source # 
Generic BlendMode Source # 

Associated Types

type Rep BlendMode :: * -> * #

ToNumber BlendMode Word32 Source # 
FromNumber BlendMode Word32 Source # 
type Rep BlendMode Source # 
type Rep BlendMode = D1 (MetaData "BlendMode" "SDL.Video.Renderer" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" False) ((:+:) ((:+:) (C1 (MetaCons "BlendNone" PrefixI False) U1) (C1 (MetaCons "BlendAlphaBlend" PrefixI False) U1)) ((:+:) (C1 (MetaCons "BlendAdditive" PrefixI False) U1) (C1 (MetaCons "BlendMod" PrefixI False) U1)))

textureColorMod :: Texture -> StateVar (V3 Word8) Source #

Get or set the additional color value multiplied into render copy operations.

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

See SDL_SetTextureColorMod and SDL_GetTextureColorMod for C documentation.

Accessing Texture Data

lockTexture Source #

Arguments

:: MonadIO m 
=> Texture

The Texture to lock for access, which must have been created with TextureAccessStreaming

-> Maybe (Rectangle CInt)

The area to lock for access; Nothing to lock the entire texture

-> m (Ptr (), CInt)

A pointer to the locked pixels, appropriately offset by the locked area, and the pitch of the locked pixels (the pitch is the length of one row in bytes).

Lock a portion of the texture for *write-only* pixel access.

See SDL_LockTexture for C documentation.

unlockTexture :: MonadIO m => Texture -> m () Source #

Unlock a texture, uploading the changes to video memory, if needed.

Warning: See Bug No. 1586 before using this function!

See SDL_UnlockTexture for C documentation.

queryTexture :: MonadIO m => Texture -> m TextureInfo Source #

Query the attributes of a texture.

See SDL_QueryTexture for C documentation.

data TextureInfo Source #

Constructors

TextureInfo 

Fields

Instances

Eq TextureInfo Source # 
Ord TextureInfo Source # 
Read TextureInfo Source # 
Show TextureInfo Source # 
Generic TextureInfo Source # 

Associated Types

type Rep TextureInfo :: * -> * #

type Rep TextureInfo Source # 

data Rectangle a Source #

Constructors

Rectangle (Point V2 a) (V2 a) 

Instances

Functor Rectangle Source # 

Methods

fmap :: (a -> b) -> Rectangle a -> Rectangle b #

(<$) :: a -> Rectangle b -> Rectangle a #

Eq a => Eq (Rectangle a) Source # 

Methods

(==) :: Rectangle a -> Rectangle a -> Bool #

(/=) :: Rectangle a -> Rectangle a -> Bool #

Ord a => Ord (Rectangle a) Source # 
Read a => Read (Rectangle a) Source # 
Show a => Show (Rectangle a) Source # 
Generic (Rectangle a) Source # 

Associated Types

type Rep (Rectangle a) :: * -> * #

Methods

from :: Rectangle a -> Rep (Rectangle a) x #

to :: Rep (Rectangle a) x -> Rectangle a #

Storable a => Storable (Rectangle a) Source # 

Methods

sizeOf :: Rectangle a -> Int #

alignment :: Rectangle a -> Int #

peekElemOff :: Ptr (Rectangle a) -> Int -> IO (Rectangle a) #

pokeElemOff :: Ptr (Rectangle a) -> Int -> Rectangle a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rectangle a) #

pokeByteOff :: Ptr b -> Int -> Rectangle a -> IO () #

peek :: Ptr (Rectangle a) -> IO (Rectangle a) #

poke :: Ptr (Rectangle a) -> Rectangle a -> IO () #

type Rep (Rectangle a) Source # 
type Rep (Rectangle a) = D1 (MetaData "Rectangle" "SDL.Video.Renderer" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" False) (C1 (MetaCons "Rectangle" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Point V2 a))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (V2 a)))))

Available Renderers

These functions allow you to query the current system for available Renderers that can be created with createRenderer.

getRendererInfo :: MonadIO m => Renderer -> m RendererInfo Source #

Get information about a rendering context.

See SDL_GetRendererInfo for C documentation.

data RendererInfo Source #

Information about an instantiated Renderer.

Constructors

RendererInfo 

Fields

Instances

Eq RendererInfo Source # 
Ord RendererInfo Source # 
Read RendererInfo Source # 
Show RendererInfo Source # 
Generic RendererInfo Source # 

Associated Types

type Rep RendererInfo :: * -> * #

type Rep RendererInfo Source # 
type Rep RendererInfo = D1 (MetaData "RendererInfo" "SDL.Video.Renderer" "sdl2-2.2.0-5VQZDI9iWv0Hz6tewdjJSZ" False) (C1 (MetaCons "RendererInfo" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "rendererInfoName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "rendererInfoFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RendererConfig)) (S1 (MetaSel (Just Symbol "rendererInfoNumTextureFormats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))) ((:*:) (S1 (MetaSel (Just Symbol "rendererInfoTextureFormats") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PixelFormat])) ((:*:) (S1 (MetaSel (Just Symbol "rendererInfoMaxTextureWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CInt)) (S1 (MetaSel (Just Symbol "rendererInfoMaxTextureHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CInt))))))

getRenderDriverInfo :: MonadIO m => m [RendererInfo] Source #

Enumerate all known render drivers on the system, and determine their supported features.

See SDL_GetRenderDriverInfo for C documentation.