Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
SDL.Video.Renderer provides a high-level interface to SDL's accelerated 2D rendering library.
Synopsis
- data Renderer
- data RendererConfig = RendererConfig {}
- defaultRenderer :: RendererConfig
- data RendererType
- clear :: (Functor m, MonadIO m) => Renderer -> m ()
- copy :: MonadIO m => Renderer -> Texture -> Maybe (Rectangle CInt) -> Maybe (Rectangle CInt) -> m ()
- copyEx :: MonadIO m => Renderer -> Texture -> Maybe (Rectangle CInt) -> Maybe (Rectangle CInt) -> CDouble -> Maybe (Point V2 CInt) -> V2 Bool -> m ()
- drawLine :: (Functor m, MonadIO m) => Renderer -> Point V2 CInt -> Point V2 CInt -> m ()
- drawLines :: MonadIO m => Renderer -> Vector (Point V2 CInt) -> m ()
- drawPoint :: (Functor m, MonadIO m) => Renderer -> Point V2 CInt -> m ()
- drawPoints :: MonadIO m => Renderer -> Vector (Point V2 CInt) -> m ()
- drawRect :: MonadIO m => Renderer -> Maybe (Rectangle CInt) -> m ()
- drawRects :: MonadIO m => Renderer -> Vector (Rectangle CInt) -> m ()
- fillRect :: MonadIO m => Renderer -> Maybe (Rectangle CInt) -> m ()
- fillRects :: MonadIO m => Renderer -> Vector (Rectangle CInt) -> m ()
- copyF :: MonadIO m => Renderer -> Texture -> Maybe (Rectangle CInt) -> Maybe (Rectangle CFloat) -> m ()
- copyExF :: MonadIO m => Renderer -> Texture -> Maybe (Rectangle CInt) -> Maybe (Rectangle CFloat) -> CDouble -> Maybe (Point V2 CFloat) -> V2 Bool -> m ()
- drawLineF :: MonadIO m => Renderer -> Point V2 CFloat -> Point V2 CFloat -> m ()
- drawLinesF :: MonadIO m => Renderer -> Vector (Point V2 CFloat) -> m ()
- drawPointF :: MonadIO m => Renderer -> Point V2 CFloat -> m ()
- drawPointsF :: MonadIO m => Renderer -> Vector (Point V2 CFloat) -> m ()
- drawRectF :: MonadIO m => Renderer -> Rectangle CFloat -> m ()
- drawRectsF :: MonadIO m => Renderer -> Vector (Rectangle CFloat) -> m ()
- fillRectF :: MonadIO m => Renderer -> Rectangle CFloat -> m ()
- fillRectsF :: MonadIO m => Renderer -> Vector (Rectangle CFloat) -> m ()
- renderGeometry :: MonadIO m => Renderer -> Maybe Texture -> Vector Vertex -> Vector CInt -> m ()
- data Vertex = Vertex {
- vertexPosition :: !FPoint
- vertexColor :: !Color
- vertexTexCoord :: !FPoint
- renderGeometryRaw :: forall ix m. (Storable ix, MonadIO m) => Renderer -> Maybe Texture -> Ptr FPoint -> CInt -> Ptr Color -> CInt -> Ptr FPoint -> CInt -> CInt -> Vector ix -> m ()
- present :: MonadIO m => Renderer -> m ()
- rendererDrawBlendMode :: Renderer -> StateVar BlendMode
- rendererDrawColor :: Renderer -> StateVar (V4 Word8)
- rendererRenderTarget :: Renderer -> StateVar (Maybe Texture)
- rendererClipRect :: Renderer -> StateVar (Maybe (Rectangle CInt))
- rendererLogicalSize :: Renderer -> StateVar (Maybe (V2 CInt))
- rendererScale :: Renderer -> StateVar (V2 CFloat)
- rendererViewport :: Renderer -> StateVar (Maybe (Rectangle CInt))
- renderTargetSupported :: MonadIO m => Renderer -> m Bool
- data Surface = Surface (Ptr Surface) (Maybe (IOVector Word8))
- updateWindowSurface :: (Functor m, MonadIO m) => Window -> m ()
- surfaceBlit :: MonadIO m => Surface -> Maybe (Rectangle CInt) -> Surface -> Maybe (Point V2 CInt) -> m (Maybe (Rectangle CInt))
- surfaceBlitScaled :: MonadIO m => Surface -> Maybe (Rectangle CInt) -> Surface -> Maybe (Rectangle CInt) -> m ()
- surfaceFillRect :: MonadIO m => Surface -> Maybe (Rectangle CInt) -> V4 Word8 -> m ()
- surfaceFillRects :: MonadIO m => Surface -> Vector (Rectangle CInt) -> V4 Word8 -> m ()
- convertSurface :: (Functor m, MonadIO m) => Surface -> SurfacePixelFormat -> m Surface
- createRGBSurface :: (Functor m, MonadIO m) => V2 CInt -> PixelFormat -> m Surface
- createRGBSurfaceFrom :: (Functor m, MonadIO m) => IOVector Word8 -> V2 CInt -> CInt -> PixelFormat -> m Surface
- freeSurface :: MonadIO m => Surface -> m ()
- getWindowSurface :: (Functor m, MonadIO m) => Window -> m Surface
- loadBMP :: MonadIO m => FilePath -> m Surface
- surfaceColorKey :: Surface -> StateVar (Maybe (V4 Word8))
- surfaceBlendMode :: Surface -> StateVar BlendMode
- surfaceDimensions :: MonadIO m => Surface -> m (V2 CInt)
- surfaceFormat :: MonadIO m => Surface -> m SurfacePixelFormat
- surfacePixels :: MonadIO m => Surface -> m (Ptr ())
- lockSurface :: MonadIO m => Surface -> m ()
- unlockSurface :: MonadIO m => Surface -> m ()
- data Palette
- paletteNColors :: MonadIO m => Palette -> m CInt
- paletteColors :: MonadIO m => Palette -> m (Maybe (Vector (V4 Word8)))
- paletteColor :: MonadIO m => Palette -> CInt -> m (Maybe (V4 Word8))
- data PixelFormat
- = Unknown !Word32
- | Index1LSB
- | Index1MSB
- | Index4LSB
- | Index4MSB
- | Index8
- | RGB332
- | RGB444
- | RGB555
- | BGR555
- | ARGB4444
- | RGBA4444
- | ABGR4444
- | BGRA4444
- | ARGB1555
- | RGBA5551
- | ABGR1555
- | BGRA5551
- | RGB565
- | BGR565
- | RGB24
- | BGR24
- | RGB888
- | RGBX8888
- | BGR888
- | BGRX8888
- | ARGB8888
- | RGBA8888
- | ABGR8888
- | BGRA8888
- | ARGB2101010
- | YV12
- | IYUV
- | YUY2
- | UYVY
- | YVYU
- newtype SurfacePixelFormat = SurfacePixelFormat (Ptr PixelFormat)
- formatPalette :: MonadIO m => SurfacePixelFormat -> m (Maybe Palette)
- setPaletteColors :: MonadIO m => Palette -> Vector (V4 Word8) -> CInt -> m ()
- pixelFormatToMasks :: MonadIO m => PixelFormat -> m (CInt, V4 Word32)
- masksToPixelFormat :: MonadIO m => CInt -> V4 Word32 -> m PixelFormat
- data Texture
- createTexture :: (Functor m, MonadIO m) => Renderer -> PixelFormat -> TextureAccess -> V2 CInt -> m Texture
- data TextureAccess
- createTextureFromSurface :: (Functor m, MonadIO m) => Renderer -> Surface -> m Texture
- updateTexture :: (Functor m, MonadIO m) => Texture -> Maybe (Rectangle CInt) -> ByteString -> CInt -> m ()
- destroyTexture :: MonadIO m => Texture -> m ()
- glBindTexture :: (Functor m, MonadIO m) => Texture -> m ()
- glUnbindTexture :: (Functor m, MonadIO m) => Texture -> m ()
- textureAlphaMod :: Texture -> StateVar Word8
- textureBlendMode :: Texture -> StateVar BlendMode
- data BlendMode
- textureColorMod :: Texture -> StateVar (V3 Word8)
- lockTexture :: MonadIO m => Texture -> Maybe (Rectangle CInt) -> m (Ptr (), CInt)
- unlockTexture :: MonadIO m => Texture -> m ()
- queryTexture :: MonadIO m => Texture -> m TextureInfo
- data TextureInfo = TextureInfo {}
- data Rectangle a = Rectangle (Point V2 a) (V2 a)
- getRendererInfo :: MonadIO m => Renderer -> m RendererInfo
- data RendererInfo = RendererInfo {}
- getRenderDriverInfo :: MonadIO m => m [RendererInfo]
Documentation
An SDL rendering device. This can be created with createRenderer
.
Instances
Data Renderer Source # | |
Defined in SDL.Internal.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Renderer -> c Renderer Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Renderer Source # toConstr :: Renderer -> Constr Source # dataTypeOf :: Renderer -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Renderer) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Renderer) Source # gmapT :: (forall b. Data b => b -> b) -> Renderer -> Renderer Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Renderer -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Renderer -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Renderer -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Renderer -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Renderer -> m Renderer Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Renderer -> m Renderer Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Renderer -> m Renderer Source # | |
Generic Renderer Source # | |
Show Renderer Source # | |
Eq Renderer Source # | |
Ord Renderer Source # | |
Defined in SDL.Internal.Types | |
type Rep Renderer Source # | |
Defined in SDL.Internal.Types |
Renderer
Configuration
These configuration options can be used with createRenderer
to create Renderer
s.
data RendererConfig Source #
The configuration data used when creating windows.
RendererConfig | |
|
Instances
defaultRenderer :: RendererConfig Source #
Default options for RendererConfig
.
defaultRenderer
=RendererConfig
{rendererType
=AcceleratedRenderer
,rendererTargetTexture
= False }
data RendererType Source #
Renderer acceleration mode
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
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.
:: MonadIO m | |
=> Renderer | The rendering context |
-> Texture | The source texture |
-> Maybe (Rectangle CInt) | The source rectangle to copy, or |
-> Maybe (Rectangle CInt) | The destination rectangle to copy to, or |
-> m () |
Copy a portion of the texture to the current rendering target.
See SDL_RenderCopy
for C documentation.
:: MonadIO m | |
=> Renderer | The rendering context |
-> Texture | The source texture |
-> Maybe (Rectangle CInt) | The source rectangle to copy, or |
-> Maybe (Rectangle CInt) | The destination rectangle to copy to, or |
-> CDouble | The angle of rotation in degrees. The rotation will be performed clockwise. |
-> Maybe (Point V2 CInt) | The point indicating the center of the rotation, or |
-> V2 Bool | Whether to flip the texture on the X and/or Y axis |
-> m () |
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.
:: (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.
:: MonadIO m | |
=> Renderer | |
-> Vector (Point V2 CInt) | A |
-> 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.
:: MonadIO m | |
=> Renderer | |
-> Maybe (Rectangle CInt) | The rectangle outline to draw. |
-> 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.
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.
copyF :: MonadIO m => Renderer -> Texture -> Maybe (Rectangle CInt) -> Maybe (Rectangle CFloat) -> m () Source #
Copy a portion of the texture to the current rendering target.
:: MonadIO m | |
=> Renderer | The rendering context |
-> Texture | The source texture |
-> Maybe (Rectangle CInt) | The source rectangle to copy, or |
-> Maybe (Rectangle CFloat) | The destination rectangle to copy to, or |
-> CDouble | The angle of rotation in degrees. The rotation will be performed clockwise. |
-> Maybe (Point V2 CFloat) | The point indicating the center of the rotation, or |
-> V2 Bool | Whether to flip the texture on the X and/or Y axis |
-> m () |
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.
drawLineF :: MonadIO m => Renderer -> Point V2 CFloat -> Point V2 CFloat -> m () Source #
Draw a line between two points on the current rendering target.
drawLinesF :: MonadIO m => Renderer -> Vector (Point V2 CFloat) -> m () Source #
Draw a series of connected lines on the current rendering target.
drawPointF :: MonadIO m => Renderer -> Point V2 CFloat -> m () Source #
Draw a point on the current rendering target.
drawPointsF :: MonadIO m => Renderer -> Vector (Point V2 CFloat) -> m () Source #
Draw a collection of points on the current rendering target.
drawRectF :: MonadIO m => Renderer -> Rectangle CFloat -> m () Source #
Draw the outline of a rectangle on the current rendering target.
drawRectsF :: MonadIO m => Renderer -> Vector (Rectangle CFloat) -> m () Source #
Draw a series of rectangle outlines on the current rendering target.
fillRectF :: MonadIO m => Renderer -> Rectangle CFloat -> m () Source #
Draw a filled rectangle on the current rendering target.
fillRectsF :: MonadIO m => Renderer -> Vector (Rectangle CFloat) -> m () Source #
Draw a series of filled rectangles on the current rendering target.
renderGeometry :: MonadIO m => Renderer -> Maybe Texture -> Vector Vertex -> Vector CInt -> m () Source #
Render a list of triangles, optionally using a texture and indices into the vertex array Color and alpha modulation is done per vertex (SDL_SetTextureColorMod and SDL_SetTextureAlphaMod are ignored).
Vertex | |
|
Instances
Storable Vertex Source # | |
Defined in SDL.Raw.Types sizeOf :: Vertex -> Int Source # alignment :: Vertex -> Int Source # peekElemOff :: Ptr Vertex -> Int -> IO Vertex Source # pokeElemOff :: Ptr Vertex -> Int -> Vertex -> IO () Source # peekByteOff :: Ptr b -> Int -> IO Vertex Source # pokeByteOff :: Ptr b -> Int -> Vertex -> IO () Source # | |
Show Vertex Source # | |
Eq Vertex Source # | |
renderGeometryRaw :: forall ix m. (Storable ix, MonadIO m) => Renderer -> Maybe Texture -> Ptr FPoint -> CInt -> Ptr Color -> CInt -> Ptr FPoint -> CInt -> CInt -> Vector ix -> m () Source #
Render a list of triangles, optionally using a texture and indices into the vertex array Color and alpha modulation is done per vertex (SDL_SetTextureColorMod and SDL_SetTextureAlphaMod are ignored).
This version allows storeing vertex data in arbitrary types, but you have to provide pointers and strides yourself.
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 Renderer
s - 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.
Surface
s
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.
:: MonadIO m | |
=> Surface | The |
-> Maybe (Rectangle CInt) | The rectangle to be copied, or |
-> Surface | The |
-> 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.
:: MonadIO m | |
=> Surface | The |
-> Maybe (Rectangle CInt) | The rectangle to be copied, or |
-> Surface | The |
-> Maybe (Rectangle CInt) | The rectangle that is copied into, or |
-> m () |
Perform a scaled surface copy to a destination surface.
See SDL_BlitScaled
for C documentation.
:: MonadIO m | |
=> Surface | The |
-> Maybe (Rectangle CInt) | The rectangle to fill, or |
-> 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.
:: MonadIO m | |
=> Surface | The |
-> Vector (Rectangle CInt) | |
-> 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 Rectangle
s.
See SDL_FillRects
for C documentation.
Creating and Destroying Surface
s
:: (Functor m, MonadIO m) | |
=> Surface | The |
-> 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.
:: (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.
:: (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.
Palette
s and pixel formats
data PixelFormat Source #
Instances
newtype SurfacePixelFormat Source #
Instances
Eq SurfacePixelFormat Source # | |
Defined in SDL.Video.Renderer (==) :: SurfacePixelFormat -> SurfacePixelFormat -> Bool Source # (/=) :: SurfacePixelFormat -> SurfacePixelFormat -> Bool Source # |
formatPalette :: MonadIO m => SurfacePixelFormat -> m (Maybe Palette) Source #
:: MonadIO m | |
=> Palette | The |
-> Vector (V4 Word8) | A |
-> 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
Creating, Using and Destroying Texture
s
:: (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.
TextureAccessStatic | Changes rarely, cannot be locked |
TextureAccessStreaming | changes frequently, can be locked |
TextureAccessTarget | Can be used as a render target |
Instances
createTextureFromSurface Source #
:: (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.
:: (Functor m, MonadIO m) | |
=> Texture | The |
-> 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 () |
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.
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.
:: (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.
Blend modes used in copy
and drawing operations.
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
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
:: MonadIO m | |
=> Texture | The |
-> Maybe (Rectangle CInt) | The area to lock for access; |
-> 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 #
TextureInfo | |
|
Instances
Instances
Available Renderer
s
These functions allow you to query the current system for available Renderer
s 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
.
RendererInfo | |
|
Instances
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.