module Graphics.UI.SDL.Video
    ( Palette
    , Toggle (..)
    , fromToggle
    , toToggle
    , tryGetVideoSurface
    , getVideoSurface
    , tryVideoDriverName
    , videoDriverName
    , getVideoInfo
    , ListModes(..)
    , listModes
    , videoModeOK
    , trySetVideoMode
    , setVideoMode
    , updateRect
    , updateRects
    , tryFlip
    , flip
    , setColors
    , setPalette
    , setGamma
    , tryGetGammaRamp
    , getGammaRamp
    , trySetGammaRamp
    , setGammaRamp
    , mapRGB
    , mapRGBA
    , getRGB
    , getRGBA
    , tryCreateRGBSurface
    , createRGBSurface
    , tryCreateRGBSurfaceEndian
    , createRGBSurfaceEndian
    , tryCreateRGBSurfaceFrom
    , createRGBSurfaceFrom
    , freeSurface
    , lockSurface
    , unlockSurface
    , loadBMP
    , saveBMP
    , setColorKey
    , setAlpha
    , setClipRect
    , getClipRect
    , withClipRect
    , tryConvertSurface
    , convertSurface
    , blitSurface
    , fillRect
    , tryDisplayFormat
    , displayFormat
    , tryDisplayFormatAlpha
    , displayFormatAlpha
    , warpMouse
    , showCursor
    , queryCursorState
    , GLAttr, GLValue
    , glRedSize, glGreenSize, glBlueSize, glAlphaSize, glBufferSize, glDoubleBuffer
    , glDepthSize, glStencilSize, glAccumRedSize, glAccumGreenSize, glAccumBlueSize
    , glAccumAlphaSize, glStereo, glMultiSampleBuffers, glMultiSampleSamples
    , tryGLGetAttribute, glGetAttribute
    , tryGLSetAttribute, glSetAttribute
    , glSwapBuffers
    , mkFinalizedSurface
    ) where
import Foreign (Ptr, FunPtr, Storable(peek), castPtr, plusPtr, nullPtr, newForeignPtr_,
               finalizeForeignPtr, alloca, withForeignPtr, newForeignPtr)
import Foreign.C (peekCString, CString, CInt(..))
import Foreign.Marshal.Array (withArrayLen, peekArray0, peekArray, allocaArray)
import Foreign.Marshal.Utils (with, toBool, maybeWith, maybePeek, fromBool)
import Control.Exception (bracket)
import Data.Word (Word8, Word16, Word32)
import Data.Int (Int32)
import Graphics.UI.SDL.Utilities (Enum(..), intToBool, toBitmask, fromCInt, toCInt)
import Graphics.UI.SDL.General (unwrapMaybe, unwrapBool)
import Graphics.UI.SDL.Rect (Rect(rectY, rectX, rectW, rectH))
import Graphics.UI.SDL.Color (Pixel(..), Color)
import Graphics.UI.SDL.Types (SurfaceFlag, PixelFormat, PixelFormatStruct, RWops,
                              RWopsStruct, VideoInfo, VideoInfoStruct, Surface, SurfaceStruct)
import qualified Graphics.UI.SDL.RWOps as RW
import Prelude hiding (flip,Enum(..))
data Palette
    = Logical
    | Physical
      deriving (Show,Eq,Ord)
instance Bounded Palette where
    minBound = Logical
    maxBound = Physical
instance Enum Palette Int where
    fromEnum Logical = 1
    fromEnum Physical = 2
    toEnum 1 = Logical
    toEnum 2 = Physical
    toEnum _ = error "Graphics.UI.SDL.Video.toEnum: bad argument"
    succ Logical = Physical
    succ _ = error "Graphics.UI.SDL.Video.succ: bad argument"
    pred Physical = Logical
    pred _ = error "Graphics.UI.SDL.Video.pred: bad argument"
    enumFromTo x y | x > y = []
                   | x == y = [y]
                   | True = x : enumFromTo (succ x) y
data Toggle = Disable | Enable | Query
    deriving (Eq, Ord, Show)
toToggle :: (Eq a, Num a) => a -> Toggle
toToggle (0) = Disable
toToggle (1) = Enable
toToggle (1) = Query
toToggle _ = error "Graphics.UI.SDL.Video.toToggle: bad argument"
fromToggle :: (Num a) => Toggle -> a
fromToggle Disable = 0
fromToggle Enable = 1
fromToggle Query = (1)
foreign import ccall unsafe "SDL_GetVideoSurface" sdlGetVideoSurface :: IO (Ptr SurfaceStruct)
tryGetVideoSurface :: IO (Maybe Surface)
tryGetVideoSurface =
    sdlGetVideoSurface >>= maybePeek newForeignPtr_
getVideoSurface :: IO Surface
getVideoSurface = unwrapMaybe "SDL_GetVideoSurface" tryGetVideoSurface
foreign import ccall unsafe "SDL_VideoDriverName" sdlVideoDriverName :: CString -> CInt -> IO CString
tryVideoDriverName :: IO (Maybe String)
tryVideoDriverName 
    = allocaArray size (\ptr -> sdlVideoDriverName ptr (toCInt size) >>= maybePeek peekCString)
    where size = 256
videoDriverName :: IO String
videoDriverName = unwrapMaybe "SDL_VideoDriverName" tryVideoDriverName
foreign import ccall unsafe "SDL_GetVideoInfo" sdlGetVideoInfo :: IO (Ptr VideoInfoStruct)
getVideoInfo :: IO VideoInfo
getVideoInfo = sdlGetVideoInfo >>= newForeignPtr_
data ListModes
    = Modes [Rect] 
    | NonAvailable 
    | AnyOK 
      deriving (Show,Eq,Ord)
foreign import ccall unsafe "SDL_ListModes" sdlListModes :: Ptr PixelFormatStruct -> Word32 -> IO (Ptr (Ptr Rect))
listModes :: Maybe PixelFormat 
          -> [SurfaceFlag]
          -> IO ListModes
listModes mbFormat flags
    = do ret <- getFormat (\ptr -> sdlListModes ptr (toBitmask flags))
         if ret == nullPtr `plusPtr` (1)
            then return AnyOK
            else if ret == nullPtr
                    then return NonAvailable
                    else do array <- peekArray0 nullPtr ret
                            fmap Modes (mapM peek array)
    where getFormat = maybe (\action -> action nullPtr) withForeignPtr mbFormat
foreign import ccall unsafe "SDL_VideoModeOK" sdlVideoModeOK :: CInt -> CInt -> CInt -> Word32 -> IO CInt
videoModeOK :: Int 
            -> Int 
            -> Int 
            -> [SurfaceFlag] 
            -> IO (Maybe Int)
videoModeOK width height bpp flags
    = do ret <- sdlVideoModeOK (toCInt width) (toCInt height) (toCInt bpp) (toBitmask flags)
         case ret of
           0 -> return Nothing
           x -> return (Just $ fromCInt x)
foreign import ccall unsafe "SDL_SetVideoMode" sdlSetVideoMode :: CInt -> CInt -> CInt -> Word32 -> IO (Ptr SurfaceStruct)
trySetVideoMode :: Int 
                -> Int 
                -> Int 
                -> [SurfaceFlag] 
                -> IO (Maybe Surface)
trySetVideoMode width height bpp flags
    = sdlSetVideoMode (toCInt width) (toCInt height) (toCInt bpp) (toBitmask flags) >>= maybePeek newForeignPtr_
setVideoMode :: Int -> Int -> Int -> [SurfaceFlag] -> IO Surface
setVideoMode width height bpp flags
    = unwrapMaybe "SDL_SetVideoMode" (trySetVideoMode width height bpp flags)
foreign import ccall unsafe "SDL_UpdateRect" sdlUpdateRect :: Ptr SurfaceStruct
                                                           -> Int32 -> Int32 -> Word32 -> Word32 -> IO ()
updateRect :: Surface -> Rect -> IO ()
updateRect surface rect
    = withForeignPtr surface (\ptr -> sdlUpdateRect ptr x y w h)
    where x = fromIntegral (rectX rect)
          y = fromIntegral (rectY rect)
          w = fromIntegral (rectW rect)
          h = fromIntegral (rectH rect)
foreign import ccall unsafe "SDL_UpdateRects" sdlUpdateRects :: Ptr SurfaceStruct -> CInt -> Ptr Rect -> IO ()
updateRects :: Surface -> [Rect] -> IO ()
updateRects surface rects
    = withForeignPtr surface $ \ptr ->
      withArrayLen rects $ \len array ->
      sdlUpdateRects ptr (toCInt len) array
foreign import ccall unsafe "SDL_Flip" sdlFlip :: Ptr SurfaceStruct -> IO CInt
tryFlip :: Surface -> IO Bool
tryFlip surface
    = withForeignPtr surface $ \ptr ->
      do ret <- sdlFlip ptr
         case ret of
           (1) -> return False
           _    -> return True
flip :: Surface -> IO ()
flip = unwrapBool "SDL_Flip" . tryFlip
foreign import ccall unsafe "SDL_SetColors" sdlSetColors :: Ptr SurfaceStruct -> Ptr Color -> CInt -> CInt -> IO CInt
setColors :: Surface -> [Color] -> Int -> IO Bool
setColors surface colors start
    = withForeignPtr surface $ \ptr ->
      withArrayLen colors $ \len array ->
      fmap toBool (sdlSetColors ptr array (toCInt start) (toCInt len))
foreign import ccall unsafe "SDL_SetPalette" sdlSetPalette
    :: Ptr SurfaceStruct -> CInt -> Ptr Color -> CInt -> CInt -> IO CInt
setPalette :: Surface -> [Palette] -> [Color] -> Int -> IO Bool
setPalette surface flags colors start
    = withForeignPtr surface $ \ptr ->
      withArrayLen colors $ \len array ->
      fmap toBool (sdlSetPalette ptr (toCInt $ toBitmask flags) array (toCInt start) (toCInt len))
foreign import ccall unsafe "SDL_SetGamma" sdlSetGamma :: Float -> Float -> Float -> IO CInt
setGamma :: Float -> Float -> Float -> IO Bool
setGamma red green blue
    = intToBool (1) (fmap fromCInt $ sdlSetGamma red green blue)
foreign import ccall unsafe "SDL_GetGammaRamp" sdlGetGammaRamp :: Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> IO CInt
tryGetGammaRamp :: IO (Maybe ([Word16],[Word16],[Word16]))
tryGetGammaRamp
    = allocaArray size $ \red ->
      allocaArray size $ \green ->
      allocaArray size $ \blue ->
      do ret <- sdlGetGammaRamp red green blue
         case ret of
           (1) -> return Nothing
           _ -> do [r,g,b] <- mapM (peekArray size) [red,green,blue]
                   return (Just (r,g,b))
    where size = 256
getGammaRamp :: IO ([Word16],[Word16],[Word16])
getGammaRamp = unwrapMaybe "SDL_GetGammaRamp" tryGetGammaRamp
foreign import ccall unsafe "SDL_SetGammaRamp" sdlSetGammaRamp :: Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> IO CInt
trySetGammaRamp :: [Word16] -> [Word16] -> [Word16] -> IO Bool
trySetGammaRamp red green blue
    = withArrayLen red $ check $ \ptrRed ->
      withArrayLen green $ check $ \ptrGreen ->
      withArrayLen blue $ check $ \ptrBlue ->
      intToBool (1) (fmap fromCInt $ sdlSetGammaRamp ptrRed ptrGreen ptrBlue)
    where check action 256 ptr = action ptr
          check _ _ _ = return False
setGammaRamp :: [Word16] -> [Word16] -> [Word16] -> IO ()
setGammaRamp red green blue = unwrapBool "setGammaRamp_" (trySetGammaRamp red green blue)
foreign import ccall unsafe "SDL_MapRGB" sdlMapRGB :: Ptr PixelFormatStruct -> Word8 -> Word8 -> Word8 -> IO Word32
mapRGB :: PixelFormat
       -> Word8 
       -> Word8 
       -> Word8 
       -> IO Pixel
mapRGB format r g b
    = withForeignPtr format $ \ptr ->
      fmap Pixel (sdlMapRGB ptr r g b)
foreign import ccall unsafe "SDL_MapRGBA" sdlMapRGBA
    :: Ptr PixelFormatStruct -> Word8 -> Word8 -> Word8 -> Word8 -> IO Word32
mapRGBA :: PixelFormat
        -> Word8 
        -> Word8 
        -> Word8 
        -> Word8 
        -> IO Pixel
mapRGBA format r g b a
    = withForeignPtr format $ \ptr ->
      fmap Pixel (sdlMapRGBA ptr r g b a)
foreign import ccall unsafe "SDL_GetRGB" sdlGetRGB
    :: Word32 -> Ptr PixelFormatStruct -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ()
getRGB :: Pixel -> PixelFormat -> IO (Word8,Word8,Word8)
getRGB (Pixel p) format
    = alloca $ \red ->
      alloca $ \green ->
      alloca $ \blue ->
      withForeignPtr format $ \ptr ->
      do sdlGetRGB p ptr red green blue
         [r,g,b] <- mapM peek [red,green,blue]
         return (r,g,b)
foreign import ccall unsafe "SDL_GetRGBA" sdlGetRGBA
    :: Word32 -> Ptr PixelFormatStruct -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ()
getRGBA :: Pixel -> PixelFormat -> IO (Word8,Word8,Word8,Word8)
getRGBA (Pixel p) format
    = alloca $ \red ->
      alloca $ \green ->
      alloca $ \blue ->
      alloca $ \alpha -> 
      withForeignPtr format $ \ptr ->
      do sdlGetRGBA p ptr red green blue alpha
         [r,g,b,a] <- mapM peek [red,green,blue,alpha]
         return (r,g,b,a)
foreign import ccall unsafe "SDL_CreateRGBSurface" sdlCreateRGBSurface
    :: Word32 -> CInt -> CInt -> CInt -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Ptr SurfaceStruct)
tryCreateRGBSurface :: [SurfaceFlag] -> Int -> Int -> Int
                  -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Maybe Surface)
tryCreateRGBSurface flags width height bpp rmask gmask bmask amask
    = sdlCreateRGBSurface (toBitmask flags) (toCInt width) (toCInt height) (toCInt bpp) rmask gmask bmask amask >>=
      maybePeek mkFinalizedSurface
createRGBSurface :: [SurfaceFlag] -> Int -> Int -> Int
                 -> Word32 -> Word32 -> Word32 -> Word32 -> IO Surface
createRGBSurface flags width height bpp rmask gmask bmask amask
    = unwrapMaybe "SDL_CreateRGBSurface" (tryCreateRGBSurface flags width height bpp rmask gmask bmask amask)
tryCreateRGBSurfaceEndian :: [SurfaceFlag] -> Int -> Int -> Int -> IO (Maybe Surface)
tryCreateRGBSurfaceEndian flags width height bpp
    = tryCreateRGBSurface flags width height bpp
        0x000000FF 0x0000FF00 0x00FF0000 0xFF000000
createRGBSurfaceEndian :: [SurfaceFlag] -> Int -> Int -> Int -> IO Surface
createRGBSurfaceEndian flags width height bpp
    = unwrapMaybe "SDL_CreateRGBSurface" (tryCreateRGBSurfaceEndian flags width height bpp)
foreign import ccall unsafe "SDL_CreateRGBSurfaceFrom" sdlCreateRGBSurfaceFrom
    :: Ptr Word8 -> CInt -> CInt -> CInt -> CInt -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Ptr SurfaceStruct)
tryCreateRGBSurfaceFrom :: Ptr a -> Int -> Int -> Int -> Int
                        -> Word32 -> Word32 -> Word32 -> Word32 -> IO (Maybe Surface)
tryCreateRGBSurfaceFrom pixels width height depth pitch rmask gmask bmask amask
    = sdlCreateRGBSurfaceFrom (castPtr pixels) (toCInt width) (toCInt height) (toCInt depth) (toCInt pitch) rmask gmask bmask amask >>=
      maybePeek mkFinalizedSurface
createRGBSurfaceFrom :: Ptr a -> Int -> Int -> Int -> Int
                     -> Word32 -> Word32 -> Word32 -> Word32 -> IO Surface
createRGBSurfaceFrom pixels width height depth pitch rmask gmask bmask amask
    = unwrapMaybe "SDL_CreateRGBSurfaceFrom"
                  (tryCreateRGBSurfaceFrom pixels width height depth pitch rmask gmask bmask amask)
freeSurface :: Surface -> IO ()
freeSurface =
  finalizeForeignPtr
foreign import ccall unsafe "SDL_LockSurface" sdlLockSurface :: Ptr SurfaceStruct -> IO CInt
lockSurface :: Surface -> IO Bool
lockSurface surface
    = withForeignPtr surface $ \ptr ->
      intToBool (1) (fmap fromCInt $ sdlLockSurface ptr)
foreign import ccall unsafe "SDL_UnlockSurface" sdlUnlockSurface :: Ptr SurfaceStruct -> IO ()
unlockSurface :: Surface -> IO ()
unlockSurface surface = withForeignPtr surface sdlUnlockSurface
foreign import ccall unsafe "SDL_LoadBMP_RW" sdlLoadBMP_RW :: Ptr RWopsStruct -> CInt -> IO (Ptr SurfaceStruct)
tryLoadBMPRW :: RWops -> Bool -> IO (Maybe Surface)
tryLoadBMPRW rw freesrc
    = withForeignPtr rw $ \rwPtr ->
      sdlLoadBMP_RW rwPtr (fromBool freesrc) >>= maybePeek mkFinalizedSurface
loadBMPRW :: RWops -> Bool -> IO Surface
loadBMPRW rw freesrc = unwrapMaybe "SDL_LoadBMP_RW" (tryLoadBMPRW rw freesrc)
loadBMP :: FilePath -> IO Surface
loadBMP filepath
    = RW.with filepath "rb" $ \rw ->
      loadBMPRW rw False
foreign import ccall unsafe "SDL_SaveBMP_RW" sdlSaveBMP_RW :: Ptr SurfaceStruct -> Ptr RWopsStruct -> CInt -> IO CInt
saveBMPRW :: Surface -> RWops -> Bool -> IO Bool
saveBMPRW surface rw freedst
    = withForeignPtr surface $ \ptr ->
      withForeignPtr rw $ \rwPtr ->
      intToBool (1) (fmap fromCInt $ sdlSaveBMP_RW ptr rwPtr (fromBool freedst))
saveBMP :: Surface -> FilePath -> IO Bool
saveBMP surface filepath
    = RW.with filepath "wb" $ \rw ->
      saveBMPRW surface rw False
foreign import ccall unsafe "SDL_SetColorKey" sdlSetColorKey :: Ptr SurfaceStruct -> Word32 -> Word32 -> IO CInt
setColorKey :: Surface -> [SurfaceFlag] -> Pixel -> IO Bool
setColorKey surface flags (Pixel w)
    = withForeignPtr surface $ \ptr ->
      intToBool (1) (fmap fromCInt $ sdlSetColorKey ptr (toBitmask flags) w)
foreign import ccall unsafe "SDL_SetAlpha" sdlSetAlpha :: Ptr SurfaceStruct -> Word32 -> Word8 -> IO CInt
setAlpha :: Surface -> [SurfaceFlag] -> Word8 -> IO Bool
setAlpha surface flags alpha
    = withForeignPtr surface $ \ptr ->
      intToBool (1) (fmap fromCInt $ sdlSetAlpha ptr (toBitmask flags) alpha)
foreign import ccall unsafe "SDL_SetClipRect" sdlSetClipRect :: Ptr SurfaceStruct -> Ptr Rect -> IO ()
setClipRect :: Surface -> Maybe Rect -> IO ()
setClipRect surface mbRect
    = withForeignPtr surface $ \ptr ->
      maybeWith with mbRect $ \rect ->
      sdlSetClipRect ptr rect
foreign import ccall unsafe "SDL_GetClipRect" sdlGetClipRect :: Ptr SurfaceStruct -> Ptr Rect -> IO ()
getClipRect :: Surface -> IO Rect
getClipRect surface
    = withForeignPtr surface $ \ptr ->
      alloca $ \rectPtr ->
      do sdlGetClipRect ptr rectPtr
         peek rectPtr
withClipRect :: Surface -> Maybe Rect -> IO a -> IO a
withClipRect surface rect action
    = bracket (getClipRect surface) 
              (setClipRect surface . Just) 
              (const (setClipRect surface rect >> action)) 
foreign import ccall unsafe "SDL_ConvertSurface" sdlConvertSurface
    :: Ptr SurfaceStruct -> Ptr PixelFormatStruct -> Word32 -> IO (Ptr SurfaceStruct)
tryConvertSurface :: Surface -> PixelFormat -> [SurfaceFlag] -> IO (Maybe Surface)
tryConvertSurface surface format flags
    = withForeignPtr surface $ \ptr ->
      withForeignPtr format $ \formatPtr ->
      sdlConvertSurface ptr formatPtr (toBitmask flags) >>= maybePeek mkFinalizedSurface
convertSurface :: Surface -> PixelFormat -> [SurfaceFlag] -> IO Surface
convertSurface surface format flags
    = unwrapMaybe "SDL_ConvertSurface"
                  (tryConvertSurface surface format flags)
foreign import ccall unsafe "SDL_UpperBlit" sdlBlitSurface
    :: Ptr SurfaceStruct -> Ptr Rect -> Ptr SurfaceStruct -> Ptr Rect -> IO CInt
blitSurface :: Surface -> Maybe Rect -> Surface -> Maybe Rect -> IO Bool
blitSurface src srcRect dst dstRect
    = withForeignPtr src $ \srcPtr ->
      withForeignPtr dst $ \dstPtr ->
      maybeWith with srcRect $ \srcRectPtr ->
      maybeWith with dstRect $ \dstRectPtr ->
      intToBool (1) (fmap fromCInt $ sdlBlitSurface srcPtr srcRectPtr dstPtr dstRectPtr)
foreign import ccall unsafe "SDL_FillRect" sdlFillRect :: Ptr SurfaceStruct -> Ptr Rect -> Word32 -> IO CInt
fillRect :: Surface -> Maybe Rect -> Pixel -> IO Bool
fillRect surface mbRect (Pixel w)
    = withForeignPtr surface $ \ptr ->
      maybeWith with mbRect $ \rect ->
      intToBool (1) (fmap fromCInt $ sdlFillRect ptr rect w)
foreign import ccall unsafe "SDL_DisplayFormat" sdlDisplayFormat :: Ptr SurfaceStruct -> IO (Ptr SurfaceStruct)
tryDisplayFormat :: Surface -> IO (Maybe Surface)
tryDisplayFormat surface
    = withForeignPtr surface $ \ptr ->
      sdlDisplayFormat ptr >>= maybePeek mkFinalizedSurface
displayFormat :: Surface -> IO Surface
displayFormat = unwrapMaybe "SDL_DisplayFormat" . tryDisplayFormat
foreign import ccall unsafe "SDL_DisplayFormatAlpha" sdlDisplayFormatAlpha :: Ptr SurfaceStruct -> IO (Ptr SurfaceStruct)
tryDisplayFormatAlpha :: Surface -> IO (Maybe Surface)
tryDisplayFormatAlpha surface
    = withForeignPtr surface $ \ptr ->
      sdlDisplayFormatAlpha ptr >>= maybePeek mkFinalizedSurface
displayFormatAlpha :: Surface -> IO Surface
displayFormatAlpha = unwrapMaybe "SDL_DisplayFormatAlpha" . tryDisplayFormatAlpha
foreign import ccall unsafe "SDL_WarpMouse" sdlWarpMouse :: Word16 -> Word16 -> IO ()
warpMouse :: Word16 
          -> Word16 
          -> IO ()
warpMouse = sdlWarpMouse
foreign import ccall unsafe "SDL_ShowCursor" sdlShowCursor :: CInt -> IO CInt
showCursor :: Bool -> IO ()
showCursor enable
    = sdlShowCursor (fromToggle toggle) >>
      return ()
    where toggle = case enable of
                     True -> Enable
                     False -> Disable
queryCursorState :: IO Bool
queryCursorState = fmap toBool (sdlShowCursor (fromToggle Query))
type GLAttr = CInt
type GLValue = CInt
glRedSize, glGreenSize, glBlueSize, glAlphaSize, glBufferSize, glDoubleBuffer :: GLAttr
glDepthSize, glStencilSize, glAccumRedSize, glAccumGreenSize, glAccumBlueSize :: GLAttr
glAccumAlphaSize, glStereo, glMultiSampleBuffers, glMultiSampleSamples :: GLAttr
glRedSize = 0
glGreenSize = 1
glBlueSize = 2
glAlphaSize = 3
glBufferSize = 4
glDoubleBuffer = 5
glDepthSize  = 6
glStencilSize = 7
glAccumRedSize = 8
glAccumGreenSize = 9
glAccumBlueSize = 10
glAccumAlphaSize = 11
glStereo = 12
glMultiSampleBuffers = 13
glMultiSampleSamples = 14
foreign import ccall unsafe "SDL_GL_SetAttribute" sdlGLSetAttribute :: CInt -> CInt -> IO CInt
tryGLSetAttribute :: GLAttr -> GLValue -> IO Bool
tryGLSetAttribute attr value = fmap (==0) (sdlGLSetAttribute attr value)
glSetAttribute :: GLAttr -> GLValue -> IO ()
glSetAttribute attr value = unwrapBool "SDL_GL_SetAttribute" (tryGLSetAttribute attr value)
foreign import ccall unsafe "SDL_GL_GetAttribute" sdlGLGetAttribute :: CInt -> Ptr CInt -> IO CInt
tryGLGetAttribute :: GLAttr -> IO (Maybe GLValue)
tryGLGetAttribute attr
    = alloca $ \valuePtr ->
      do ret <- sdlGLGetAttribute attr valuePtr
         case ret of
           0 -> fmap Just (peek valuePtr)
           _ -> return Nothing
glGetAttribute :: GLAttr -> IO GLValue
glGetAttribute = unwrapMaybe "SDL_GL_GetAttribute" . tryGLGetAttribute
foreign import ccall unsafe "SDL_GL_SwapBuffers" glSwapBuffers :: IO ()
foreign import ccall unsafe "&SDL_FreeSurface" sdlFreeSurfaceFinal :: FunPtr (Ptr SurfaceStruct -> IO ())
mkFinalizedSurface :: Ptr SurfaceStruct -> IO Surface
mkFinalizedSurface = newForeignPtr sdlFreeSurfaceFinal