module Graphics.UI.SDL.WindowManagement
( GrabMode (..)
, setCaption
, rawSetCaption
, getCaption
, iconifyWindow
, tryToggleFullscreen
, toggleFullscreen
, grabInput
, queryGrabMode
) where
import Foreign (Int32, Ptr, Storable(peek), nullPtr, toBool, maybePeek,
void, alloca, withForeignPtr)
import Foreign.C (withCString, peekCString, CString)
import Graphics.UI.SDL.Types (Surface, SurfaceStruct)
import Graphics.UI.SDL.General (unwrapBool)
data GrabMode
= GrabQuery
| GrabOff
| GrabOn
deriving (Show,Eq)
toGrabMode :: Int32 -> GrabMode
toGrabMode (1) = GrabQuery
toGrabMode (0) = GrabOff
toGrabMode (1) = GrabOn
toGrabMode _ = error "Graphics.UI.SDL.WindowManagement.toGrabMode: bad argument"
fromGrabMode :: GrabMode -> Int32
fromGrabMode GrabQuery = (1)
fromGrabMode GrabOff = (0)
fromGrabMode GrabOn = (1)
foreign import ccall unsafe "SDL_WM_SetCaption" sdlSetCaption :: CString -> CString -> IO ()
setCaption :: String -> String -> IO ()
setCaption title icon
= withCString title $ \titlePtr ->
withCString icon $ \iconPtr ->
sdlSetCaption titlePtr iconPtr
rawSetCaption :: Maybe String -> Maybe String -> IO ()
rawSetCaption title icon
= maybeStr title $ \titlePtr ->
maybeStr icon $ \iconPtr ->
sdlSetCaption titlePtr iconPtr
where maybeStr Nothing action = action nullPtr
maybeStr (Just s) action = withCString s action
foreign import ccall unsafe "SDL_WM_GetCaption" sdlGetCaption :: Ptr CString -> Ptr CString -> IO ()
getCaption :: IO (Maybe String,Maybe String)
getCaption
= alloca $ \cTitle ->
alloca $ \cIcon ->
do sdlGetCaption cTitle cIcon
title <- maybePeek ((peekCString =<<).peek) cTitle
icon <- maybePeek ((peekCString =<<).peek) cIcon
return (title,icon)
foreign import ccall unsafe "SDL_WM_IconifyWindow" sdlIconifyWindow :: IO Int
iconifyWindow :: IO Bool
iconifyWindow = fmap toBool sdlIconifyWindow
foreign import ccall unsafe "SDL_WM_ToggleFullScreen" sdlToggleFullScreen :: Ptr SurfaceStruct -> IO Int
tryToggleFullscreen :: Surface -> IO Bool
tryToggleFullscreen surface
= withForeignPtr surface $ fmap toBool . sdlToggleFullScreen
toggleFullscreen :: Surface -> IO ()
toggleFullscreen = unwrapBool "SDL_WM_ToggleFullScreen" . tryToggleFullscreen
foreign import ccall unsafe "SDL_WM_GrabInput" sdlGrabInput :: Int32 -> IO Int32
grabInput :: Bool -> IO ()
grabInput = void . sdlGrabInput . fromGrabMode . mkGrabMode
where mkGrabMode True = GrabOn
mkGrabMode False = GrabOff
queryGrabMode :: IO GrabMode
queryGrabMode = fmap toGrabMode . sdlGrabInput . fromGrabMode $ GrabQuery