SDL-0.6.5.1: Binding to libSDL

Copyright(c) David Himmelstrup 2005
LicenseBSD-like
Maintainerlemmih@gmail.com
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Graphics.UI.SDL.Video

Description

 

Synopsis

Documentation

toToggle :: (Eq a, Num a) => a -> Toggle Source

tryGetVideoSurface :: IO (Maybe Surface) Source

Returns the video surface or Nothing on error.

getVideoSurface :: IO Surface Source

Returns the video surface, throwing an exception on error.

tryVideoDriverName :: IO (Maybe String) Source

Returns the video driver name or Nothing on error. Notice, the driver name is limited to 256 chars.

videoDriverName :: IO String Source

Returns the video driver name, throwing an exception on error. See also tryVideoDriverName.

data ListModes Source

Constructors

Modes [Rect]

List of available resolutions.

NonAvailable

No modes available!

AnyOK

All resolutions available.

listModes Source

Arguments

:: Maybe PixelFormat

Will use SDL_GetVideoInfo()->vfmt when Nothing.

-> [SurfaceFlag] 
-> IO ListModes 

Returns the available screen resolutions for the given format and video flags.

videoModeOK Source

Arguments

:: Int

Width.

-> Int

Height.

-> Int

Bits-per-pixel.

-> [SurfaceFlag]

Flags.

-> IO (Maybe Int) 

Check to see if a particular video mode is supported. Returns the bits-per-pixel of the closest available mode with the given width, height and requested surface flags, or Nothing on error.

trySetVideoMode Source

Arguments

:: Int

Width.

-> Int

Height.

-> Int

Bits-per-pixel.

-> [SurfaceFlag]

Flags.

-> IO (Maybe Surface) 

Set up a video mode with the specified width, height and bits-per-pixel. Returns Nothing on error.

setVideoMode :: Int -> Int -> Int -> [SurfaceFlag] -> IO Surface Source

Same as trySetVideoMode except it throws an exception on error.

updateRect :: Surface -> Rect -> IO () Source

Makes sure the given area is updated on the given screen.

updateRects :: Surface -> [Rect] -> IO () Source

Makes sure the given list of rectangles is updated on the given screen. The rectangles are not automatically merged or checked for overlap. In general, the programmer can use his knowledge about his particular rectangles to merge them in an efficient way, to avoid overdraw.

tryFlip :: Surface -> IO Bool Source

Swaps screen buffers.

flip :: Surface -> IO () Source

Same as tryFlip but throws an exception on error.

setColors :: Surface -> [Color] -> Int -> IO Bool Source

Sets a portion of the colormap for the given 8-bit surface.

setPalette :: Surface -> [Palette] -> [Color] -> Int -> IO Bool Source

Sets the colors in the palette of an 8-bit surface.

setGammaRamp :: [Word16] -> [Word16] -> [Word16] -> IO () Source

mapRGB Source

Arguments

:: PixelFormat 
-> Word8

Red value.

-> Word8

Green value.

-> Word8

Blue value.

-> IO Pixel 

Map a RGB color value to a pixel format.

mapRGBA Source

Arguments

:: PixelFormat 
-> Word8

Red value.

-> Word8

Green value.

-> Word8

Blue value.

-> Word8

Alpha value.

-> IO Pixel 

Map a RGBA color value to a pixel format.

getRGB :: Pixel -> PixelFormat -> IO (Word8, Word8, Word8) Source

Get RGB values from a pixel in the specified pixel format.

getRGBA :: Pixel -> PixelFormat -> IO (Word8, Word8, Word8, Word8) Source

Gets RGBA values from a pixel in the specified pixel format.

tryCreateRGBSurface :: [SurfaceFlag] -> Int -> Int -> Int -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Maybe Surface) Source

Creates an empty Surface. Returns Nothing on error.

createRGBSurface :: [SurfaceFlag] -> Int -> Int -> Int -> Word32 -> Word32 -> Word32 -> Word32 -> IO Surface Source

Creates an empty Surface. Throws an exception on error.

tryCreateRGBSurfaceEndian :: [SurfaceFlag] -> Int -> Int -> Int -> IO (Maybe Surface) Source

Creates an empty Surface with (r/g/b/a)mask determined from the local endian. Returns Nothing on error.

createRGBSurfaceEndian :: [SurfaceFlag] -> Int -> Int -> Int -> IO Surface Source

Creates an empty Surface with (r/g/b/a)mask determined from the local endian. Throws an exception on error.

freeSurface :: Surface -> IO () Source

Forces the finalization of a Surface. Only supported with GHC.

lockSurface :: Surface -> IO Bool Source

Locks a surface for direct access.

unlockSurface :: Surface -> IO () Source

Unlocks a previously locked surface.

setAlpha :: Surface -> [SurfaceFlag] -> Word8 -> IO Bool Source

Adjusts the alpha properties of a surface.

setClipRect :: Surface -> Maybe Rect -> IO () Source

Sets the clipping rectangle for a surface.

getClipRect :: Surface -> IO Rect Source

Gets the clipping rectangle for a surface.

withClipRect :: Surface -> Maybe Rect -> IO a -> IO a Source

Run an action with a given clipping rect applied. If an exception is raised, then withClipRect will re-raise the exception (after resetting the original clipping rect).

tryConvertSurface :: Surface -> PixelFormat -> [SurfaceFlag] -> IO (Maybe Surface) Source

Converts a surface to the same format as another surface. Returns Nothing on error.

convertSurface :: Surface -> PixelFormat -> [SurfaceFlag] -> IO Surface Source

Converts a surface to the same format as another surface. Throws an exception on error.

blitSurface :: Surface -> Maybe Rect -> Surface -> Maybe Rect -> IO Bool Source

This function performs a fast blit from the source surface to the destination surface.

fillRect :: Surface -> Maybe Rect -> Pixel -> IO Bool Source

This function performs a fast fill of the given rectangle with some color.

tryDisplayFormat :: Surface -> IO (Maybe Surface) Source

Converts a surface to the display format. Returns Nothing on error.

displayFormat :: Surface -> IO Surface Source

Converts a surface to the display format. Throws an exception on error.

tryDisplayFormatAlpha :: Surface -> IO (Maybe Surface) Source

Converts a surface to the display format. Returns Nothing on error.

displayFormatAlpha :: Surface -> IO Surface Source

Converts a surface to the display format. Throws an exception on error.

warpMouse Source

Arguments

:: Word16

Mouse X position.

-> Word16

Mouse Y position.

-> IO () 

Sets the position of the mouse cursor.

showCursor :: Bool -> IO () Source

Toggle whether or not the cursor is shown on the screen.

queryCursorState :: IO Bool Source

Returns True when the cursor is set to visible. See also showCursor.

tryGLGetAttribute :: GLAttr -> IO (Maybe GLValue) Source

Gets the value of a special SDL/OpenGL attribute. Returns Nothing on error.

glGetAttribute :: GLAttr -> IO GLValue Source

Gets the value of a special SDL/OpenGL attribute. Throws an exception on error.

tryGLSetAttribute :: GLAttr -> GLValue -> IO Bool Source

Sets a special SDL/OpenGL attribute. Returns False on error.

glSetAttribute :: GLAttr -> GLValue -> IO () Source

Sets a special SDL/OpenGL attribute. Throws an exception on error.

glSwapBuffers :: IO () Source

Swaps OpenGL framebuffers/Update Display.