Copyright | (c) David Himmelstrup 2005 |
---|---|
License | BSD-like |
Maintainer | [email protected] |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Graphics.UI.SDL.Video
Description
- data Palette
- data Toggle
- fromToggle :: Num a => Toggle -> a
- toToggle :: (Eq a, Num a) => a -> Toggle
- tryGetVideoSurface :: IO (Maybe Surface)
- getVideoSurface :: IO Surface
- tryVideoDriverName :: IO (Maybe String)
- videoDriverName :: IO String
- getVideoInfo :: IO VideoInfo
- data ListModes
- = Modes [Rect]
- | NonAvailable
- | AnyOK
- listModes :: Maybe PixelFormat -> [SurfaceFlag] -> IO ListModes
- videoModeOK :: Int -> Int -> Int -> [SurfaceFlag] -> IO (Maybe Int)
- trySetVideoMode :: Int -> Int -> Int -> [SurfaceFlag] -> IO (Maybe Surface)
- setVideoMode :: Int -> Int -> Int -> [SurfaceFlag] -> IO Surface
- updateRect :: Surface -> Rect -> IO ()
- updateRects :: Surface -> [Rect] -> IO ()
- tryFlip :: Surface -> IO Bool
- flip :: Surface -> IO ()
- setColors :: Surface -> [Color] -> Int -> IO Bool
- setPalette :: Surface -> [Palette] -> [Color] -> Int -> IO Bool
- setGamma :: Float -> Float -> Float -> IO Bool
- tryGetGammaRamp :: IO (Maybe ([Word16], [Word16], [Word16]))
- getGammaRamp :: IO ([Word16], [Word16], [Word16])
- trySetGammaRamp :: [Word16] -> [Word16] -> [Word16] -> IO Bool
- setGammaRamp :: [Word16] -> [Word16] -> [Word16] -> IO ()
- mapRGB :: PixelFormat -> Word8 -> Word8 -> Word8 -> IO Pixel
- mapRGBA :: PixelFormat -> Word8 -> Word8 -> Word8 -> Word8 -> IO Pixel
- getRGB :: Pixel -> PixelFormat -> IO (Word8, Word8, Word8)
- getRGBA :: Pixel -> PixelFormat -> IO (Word8, Word8, Word8, Word8)
- tryCreateRGBSurface :: [SurfaceFlag] -> Int -> Int -> Int -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Maybe Surface)
- createRGBSurface :: [SurfaceFlag] -> Int -> Int -> Int -> Word32 -> Word32 -> Word32 -> Word32 -> IO Surface
- tryCreateRGBSurfaceEndian :: [SurfaceFlag] -> Int -> Int -> Int -> IO (Maybe Surface)
- createRGBSurfaceEndian :: [SurfaceFlag] -> Int -> Int -> Int -> IO Surface
- tryCreateRGBSurfaceFrom :: Ptr a -> Int -> Int -> Int -> Int -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Maybe Surface)
- createRGBSurfaceFrom :: Ptr a -> Int -> Int -> Int -> Int -> Word32 -> Word32 -> Word32 -> Word32 -> IO Surface
- freeSurface :: Surface -> IO ()
- lockSurface :: Surface -> IO Bool
- unlockSurface :: Surface -> IO ()
- loadBMP :: FilePath -> IO Surface
- saveBMP :: Surface -> FilePath -> IO Bool
- setColorKey :: Surface -> [SurfaceFlag] -> Pixel -> IO Bool
- setAlpha :: Surface -> [SurfaceFlag] -> Word8 -> IO Bool
- setClipRect :: Surface -> Maybe Rect -> IO ()
- getClipRect :: Surface -> IO Rect
- withClipRect :: Surface -> Maybe Rect -> IO a -> IO a
- tryConvertSurface :: Surface -> PixelFormat -> [SurfaceFlag] -> IO (Maybe Surface)
- convertSurface :: Surface -> PixelFormat -> [SurfaceFlag] -> IO Surface
- blitSurface :: Surface -> Maybe Rect -> Surface -> Maybe Rect -> IO Bool
- fillRect :: Surface -> Maybe Rect -> Pixel -> IO Bool
- tryDisplayFormat :: Surface -> IO (Maybe Surface)
- displayFormat :: Surface -> IO Surface
- tryDisplayFormatAlpha :: Surface -> IO (Maybe Surface)
- displayFormatAlpha :: Surface -> IO Surface
- warpMouse :: Word16 -> Word16 -> IO ()
- showCursor :: Bool -> IO ()
- queryCursorState :: IO Bool
- type GLAttr = CInt
- type GLValue = CInt
- glRedSize :: GLAttr
- glGreenSize :: GLAttr
- glBlueSize :: GLAttr
- glAlphaSize :: GLAttr
- glBufferSize :: GLAttr
- glDoubleBuffer :: GLAttr
- glDepthSize :: GLAttr
- glStencilSize :: GLAttr
- glAccumRedSize :: GLAttr
- glAccumGreenSize :: GLAttr
- glAccumBlueSize :: GLAttr
- glAccumAlphaSize :: GLAttr
- glStereo :: GLAttr
- glMultiSampleBuffers :: GLAttr
- glMultiSampleSamples :: GLAttr
- tryGLGetAttribute :: GLAttr -> IO (Maybe GLValue)
- glGetAttribute :: GLAttr -> IO GLValue
- tryGLSetAttribute :: GLAttr -> GLValue -> IO Bool
- glSetAttribute :: GLAttr -> GLValue -> IO ()
- glSwapBuffers :: IO ()
- mkFinalizedSurface :: Ptr SurfaceStruct -> IO Surface
Documentation
fromToggle :: Num a => Toggle -> a 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
.
Constructors
Modes [Rect] | List of available resolutions. |
NonAvailable | No modes available! |
AnyOK | All resolutions available. |
Arguments
:: Maybe PixelFormat | Will use SDL_GetVideoInfo()->vfmt when |
-> [SurfaceFlag] | |
-> IO ListModes |
Returns the available screen resolutions for the given format and video flags.
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.
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.
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.
Map a RGB color value to a pixel format.
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.
tryCreateRGBSurfaceFrom :: Ptr a -> Int -> Int -> Int -> Int -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Maybe Surface) Source
createRGBSurfaceFrom :: Ptr a -> Int -> Int -> Int -> Int -> Word32 -> Word32 -> Word32 -> Word32 -> IO Surface Source
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.
setColorKey :: Surface -> [SurfaceFlag] -> Pixel -> IO Bool Source
setAlpha :: Surface -> [SurfaceFlag] -> Word8 -> IO Bool Source
Adjusts the alpha properties of 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.
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.