{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
module SDL.Video
( module SDL.Video.OpenGL
, module SDL.Video.Renderer
, Window
, createWindow
, defaultWindow
, WindowConfig(..)
, WindowGraphicsContext(..)
, WindowMode(..)
, WindowPosition(..)
, destroyWindow
, hideWindow
, raiseWindow
, showWindow
, windowMinimumSize
, windowMaximumSize
, windowOpacity
, windowSize
, windowBordered
, windowBrightness
, windowGammaRamp
, windowGrab
, setWindowMode
, getWindowAbsolutePosition
, getWindowBordersSize
, setWindowIcon
, setWindowPosition
, windowTitle
, windowData
, getWindowConfig
, getWindowPixelFormat
, PixelFormat(..)
, createRenderer
, createSoftwareRenderer
, destroyRenderer
, getClipboardText
, hasClipboardText
, setClipboardText
, getDisplays
, Display(..)
, DisplayMode(..)
, VideoDriver(..)
, screenSaverEnabled
, showSimpleMessageBox
, MessageKind(..)
) where
import Prelude hiding (all, foldl, foldr, mapM_)
import Data.StateVar
import Control.Applicative
import Control.Exception
import Control.Monad (forM, unless, void)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Bits
import Data.Data (Data)
import Data.Foldable
import Data.Maybe (fromMaybe)
import Data.Monoid (First(..))
import Data.Text (Text)
import Data.Typeable
import Foreign hiding (void, throwIfNull, throwIfNeg, throwIfNeg_)
import Foreign.C
import GHC.Generics (Generic)
import SDL.Vect
import SDL.Internal.Exception
import SDL.Internal.Numbered
import SDL.Internal.Types
import SDL.Video.OpenGL
import SDL.Video.Renderer
import qualified Data.ByteString as BS
import qualified Data.Text.Encoding as Text
import qualified Data.Vector.Storable as SV
import qualified SDL.Raw as Raw
createWindow :: MonadIO m => Text -> WindowConfig -> m Window
createWindow :: forall (m :: Type -> Type).
MonadIO m =>
Text -> WindowConfig -> m Window
createWindow Text
title WindowConfig
config = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
case WindowConfig -> WindowGraphicsContext
windowGraphicsContext WindowConfig
config of
OpenGLContext OpenGLConfig
glcfg -> forall {m :: Type -> Type}. MonadIO m => OpenGLConfig -> m ()
setGLAttributes OpenGLConfig
glcfg
WindowGraphicsContext
_ -> forall (m :: Type -> Type) a. Monad m => a -> m a
return ()
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString (Text -> ByteString
Text.encodeUtf8 Text
title) forall a b. (a -> b) -> a -> b
$ \CString
title' -> do
let create :: CInt -> CInt -> CInt -> CInt -> Word32 -> IO Window
create = forall (m :: Type -> Type).
MonadIO m =>
CString -> CInt -> CInt -> CInt -> CInt -> Word32 -> m Window
Raw.createWindow CString
title'
let create' :: V2 CInt -> Word32 -> IO Window
create' (V2 CInt
w CInt
h) = case WindowConfig -> WindowPosition
windowPosition WindowConfig
config of
WindowPosition
Centered -> let u :: CInt
u = forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOWPOS_CENTERED in CInt -> CInt -> CInt -> CInt -> Word32 -> IO Window
create CInt
u CInt
u CInt
w CInt
h
WindowPosition
Wherever -> let u :: CInt
u = forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOWPOS_UNDEFINED in CInt -> CInt -> CInt -> CInt -> Word32 -> IO Window
create CInt
u CInt
u CInt
w CInt
h
Absolute (P (V2 CInt
x CInt
y)) -> CInt -> CInt -> CInt -> CInt -> Word32 -> IO Window
create CInt
x CInt
y CInt
w CInt
h
V2 CInt -> Word32 -> IO Window
create' (WindowConfig -> V2 CInt
windowInitialSize WindowConfig
config) Word32
flags forall (m :: Type -> Type) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: Type -> Type) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> Window
Window
where
flags :: Word32
flags = forall (t :: Type -> Type) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Bits a => a -> a -> a
(.|.) Word32
0
[ if WindowConfig -> Bool
windowBorder WindowConfig
config then Word32
0 else forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_BORDERLESS
, if WindowConfig -> Bool
windowHighDPI WindowConfig
config then forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_ALLOW_HIGHDPI else Word32
0
, if WindowConfig -> Bool
windowInputGrabbed WindowConfig
config then forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_INPUT_GRABBED else Word32
0
, forall a b. ToNumber a b => a -> b
toNumber forall a b. (a -> b) -> a -> b
$ WindowConfig -> WindowMode
windowMode WindowConfig
config
, if WindowGraphicsContext -> Bool
ctxIsOpenGL (WindowConfig -> WindowGraphicsContext
windowGraphicsContext WindowConfig
config) then forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_OPENGL else Word32
0
, if WindowConfig -> Bool
windowResizable WindowConfig
config then forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_RESIZABLE else Word32
0
, if WindowConfig -> Bool
windowVisible WindowConfig
config then Word32
0 else forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_HIDDEN
, if WindowConfig -> WindowGraphicsContext
windowGraphicsContext WindowConfig
config forall a. Eq a => a -> a -> Bool
== WindowGraphicsContext
VulkanContext then forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_VULKAN else Word32
0
]
setGLAttributes :: OpenGLConfig -> m ()
setGLAttributes (OpenGLConfig (V4 CInt
r CInt
g CInt
b CInt
a) CInt
d CInt
s CInt
ms Profile
p) = do
let (CInt
msk, CInt
v0, CInt
v1, CInt
flg) = case Profile
p of
Core Mode
Debug CInt
v0' CInt
v1' -> (forall {a}. (Eq a, Num a) => a
Raw.SDL_GL_CONTEXT_PROFILE_CORE, CInt
v0', CInt
v1', forall {a}. (Eq a, Num a) => a
Raw.SDL_GL_CONTEXT_DEBUG_FLAG)
Core Mode
Normal CInt
v0' CInt
v1' -> (forall {a}. (Eq a, Num a) => a
Raw.SDL_GL_CONTEXT_PROFILE_CORE, CInt
v0', CInt
v1', CInt
0)
Compatibility Mode
Debug CInt
v0' CInt
v1' -> (forall {a}. (Eq a, Num a) => a
Raw.SDL_GL_CONTEXT_PROFILE_COMPATIBILITY, CInt
v0', CInt
v1', forall {a}. (Eq a, Num a) => a
Raw.SDL_GL_CONTEXT_DEBUG_FLAG)
Compatibility Mode
Normal CInt
v0' CInt
v1' -> (forall {a}. (Eq a, Num a) => a
Raw.SDL_GL_CONTEXT_PROFILE_COMPATIBILITY, CInt
v0', CInt
v1', CInt
0)
ES Mode
Debug CInt
v0' CInt
v1' -> (forall {a}. (Eq a, Num a) => a
Raw.SDL_GL_CONTEXT_PROFILE_ES, CInt
v0', CInt
v1', forall {a}. (Eq a, Num a) => a
Raw.SDL_GL_CONTEXT_DEBUG_FLAG)
ES Mode
Normal CInt
v0' CInt
v1' -> (forall {a}. (Eq a, Num a) => a
Raw.SDL_GL_CONTEXT_PROFILE_ES, CInt
v0', CInt
v1', CInt
0)
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m ()
throwIfNeg_ Text
"SDL.Video.createWindow" Text
"SDL_GL_SetAttribute" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall (m :: Type -> Type). MonadIO m => Word32 -> CInt -> m CInt
Raw.glSetAttribute) forall a b. (a -> b) -> a -> b
$
[ (Word32
Raw.SDL_GL_RED_SIZE, CInt
r)
, (Word32
Raw.SDL_GL_GREEN_SIZE, CInt
g)
, (Word32
Raw.SDL_GL_BLUE_SIZE, CInt
b)
, (Word32
Raw.SDL_GL_ALPHA_SIZE, CInt
a)
, (Word32
Raw.SDL_GL_DEPTH_SIZE, CInt
d)
, (Word32
Raw.SDL_GL_STENCIL_SIZE, CInt
s)
, (Word32
Raw.SDL_GL_MULTISAMPLEBUFFERS, if CInt
ms forall a. Ord a => a -> a -> Bool
> CInt
1 then CInt
1 else CInt
0)
, (Word32
Raw.SDL_GL_MULTISAMPLESAMPLES, if CInt
ms forall a. Ord a => a -> a -> Bool
> CInt
1 then CInt
ms else CInt
0)
, (Word32
Raw.SDL_GL_CONTEXT_PROFILE_MASK, CInt
msk)
, (Word32
Raw.SDL_GL_CONTEXT_MAJOR_VERSION, CInt
v0)
, (Word32
Raw.SDL_GL_CONTEXT_MINOR_VERSION, CInt
v1)
, (Word32
Raw.SDL_GL_CONTEXT_FLAGS, CInt
flg)
]
defaultWindow :: WindowConfig
defaultWindow :: WindowConfig
defaultWindow = WindowConfig
{ windowBorder :: Bool
windowBorder = Bool
True
, windowHighDPI :: Bool
windowHighDPI = Bool
False
, windowInputGrabbed :: Bool
windowInputGrabbed = Bool
False
, windowMode :: WindowMode
windowMode = WindowMode
Windowed
, windowGraphicsContext :: WindowGraphicsContext
windowGraphicsContext = WindowGraphicsContext
NoGraphicsContext
, windowPosition :: WindowPosition
windowPosition = WindowPosition
Wherever
, windowResizable :: Bool
windowResizable = Bool
False
, windowInitialSize :: V2 CInt
windowInitialSize = forall a. a -> a -> V2 a
V2 CInt
800 CInt
600
, windowVisible :: Bool
windowVisible = Bool
True
}
data WindowConfig = WindowConfig
{ WindowConfig -> Bool
windowBorder :: Bool
, WindowConfig -> Bool
windowHighDPI :: Bool
, WindowConfig -> Bool
windowInputGrabbed :: Bool
, WindowConfig -> WindowMode
windowMode :: WindowMode
, WindowConfig -> WindowGraphicsContext
windowGraphicsContext :: WindowGraphicsContext
, WindowConfig -> WindowPosition
windowPosition :: WindowPosition
, WindowConfig -> Bool
windowResizable :: Bool
, WindowConfig -> V2 CInt
windowInitialSize :: V2 CInt
, WindowConfig -> Bool
windowVisible :: Bool
} deriving (WindowConfig -> WindowConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowConfig -> WindowConfig -> Bool
$c/= :: WindowConfig -> WindowConfig -> Bool
== :: WindowConfig -> WindowConfig -> Bool
$c== :: WindowConfig -> WindowConfig -> Bool
Eq, forall x. Rep WindowConfig x -> WindowConfig
forall x. WindowConfig -> Rep WindowConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WindowConfig x -> WindowConfig
$cfrom :: forall x. WindowConfig -> Rep WindowConfig x
Generic, Eq WindowConfig
WindowConfig -> WindowConfig -> Bool
WindowConfig -> WindowConfig -> Ordering
WindowConfig -> WindowConfig -> WindowConfig
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WindowConfig -> WindowConfig -> WindowConfig
$cmin :: WindowConfig -> WindowConfig -> WindowConfig
max :: WindowConfig -> WindowConfig -> WindowConfig
$cmax :: WindowConfig -> WindowConfig -> WindowConfig
>= :: WindowConfig -> WindowConfig -> Bool
$c>= :: WindowConfig -> WindowConfig -> Bool
> :: WindowConfig -> WindowConfig -> Bool
$c> :: WindowConfig -> WindowConfig -> Bool
<= :: WindowConfig -> WindowConfig -> Bool
$c<= :: WindowConfig -> WindowConfig -> Bool
< :: WindowConfig -> WindowConfig -> Bool
$c< :: WindowConfig -> WindowConfig -> Bool
compare :: WindowConfig -> WindowConfig -> Ordering
$ccompare :: WindowConfig -> WindowConfig -> Ordering
Ord, ReadPrec [WindowConfig]
ReadPrec WindowConfig
Int -> ReadS WindowConfig
ReadS [WindowConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WindowConfig]
$creadListPrec :: ReadPrec [WindowConfig]
readPrec :: ReadPrec WindowConfig
$creadPrec :: ReadPrec WindowConfig
readList :: ReadS [WindowConfig]
$creadList :: ReadS [WindowConfig]
readsPrec :: Int -> ReadS WindowConfig
$creadsPrec :: Int -> ReadS WindowConfig
Read, Int -> WindowConfig -> ShowS
[WindowConfig] -> ShowS
WindowConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowConfig] -> ShowS
$cshowList :: [WindowConfig] -> ShowS
show :: WindowConfig -> String
$cshow :: WindowConfig -> String
showsPrec :: Int -> WindowConfig -> ShowS
$cshowsPrec :: Int -> WindowConfig -> ShowS
Show, Typeable)
data WindowGraphicsContext
= NoGraphicsContext
| OpenGLContext OpenGLConfig
| VulkanContext
deriving (WindowGraphicsContext -> WindowGraphicsContext -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
$c/= :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
== :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
$c== :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
Eq, forall x. Rep WindowGraphicsContext x -> WindowGraphicsContext
forall x. WindowGraphicsContext -> Rep WindowGraphicsContext x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WindowGraphicsContext x -> WindowGraphicsContext
$cfrom :: forall x. WindowGraphicsContext -> Rep WindowGraphicsContext x
Generic, Eq WindowGraphicsContext
WindowGraphicsContext -> WindowGraphicsContext -> Bool
WindowGraphicsContext -> WindowGraphicsContext -> Ordering
WindowGraphicsContext
-> WindowGraphicsContext -> WindowGraphicsContext
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WindowGraphicsContext
-> WindowGraphicsContext -> WindowGraphicsContext
$cmin :: WindowGraphicsContext
-> WindowGraphicsContext -> WindowGraphicsContext
max :: WindowGraphicsContext
-> WindowGraphicsContext -> WindowGraphicsContext
$cmax :: WindowGraphicsContext
-> WindowGraphicsContext -> WindowGraphicsContext
>= :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
$c>= :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
> :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
$c> :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
<= :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
$c<= :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
< :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
$c< :: WindowGraphicsContext -> WindowGraphicsContext -> Bool
compare :: WindowGraphicsContext -> WindowGraphicsContext -> Ordering
$ccompare :: WindowGraphicsContext -> WindowGraphicsContext -> Ordering
Ord, ReadPrec [WindowGraphicsContext]
ReadPrec WindowGraphicsContext
Int -> ReadS WindowGraphicsContext
ReadS [WindowGraphicsContext]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WindowGraphicsContext]
$creadListPrec :: ReadPrec [WindowGraphicsContext]
readPrec :: ReadPrec WindowGraphicsContext
$creadPrec :: ReadPrec WindowGraphicsContext
readList :: ReadS [WindowGraphicsContext]
$creadList :: ReadS [WindowGraphicsContext]
readsPrec :: Int -> ReadS WindowGraphicsContext
$creadsPrec :: Int -> ReadS WindowGraphicsContext
Read, Int -> WindowGraphicsContext -> ShowS
[WindowGraphicsContext] -> ShowS
WindowGraphicsContext -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowGraphicsContext] -> ShowS
$cshowList :: [WindowGraphicsContext] -> ShowS
show :: WindowGraphicsContext -> String
$cshow :: WindowGraphicsContext -> String
showsPrec :: Int -> WindowGraphicsContext -> ShowS
$cshowsPrec :: Int -> WindowGraphicsContext -> ShowS
Show, Typeable)
ctxIsOpenGL :: WindowGraphicsContext -> Bool
ctxIsOpenGL :: WindowGraphicsContext -> Bool
ctxIsOpenGL (OpenGLContext OpenGLConfig
_) = Bool
True
ctxIsOpenGL WindowGraphicsContext
_ = Bool
False
data WindowMode
= Fullscreen
| FullscreenDesktop
| Maximized
| Minimized
| Windowed
deriving (WindowMode
forall a. a -> a -> Bounded a
maxBound :: WindowMode
$cmaxBound :: WindowMode
minBound :: WindowMode
$cminBound :: WindowMode
Bounded, Typeable WindowMode
WindowMode -> DataType
WindowMode -> Constr
(forall b. Data b => b -> b) -> WindowMode -> WindowMode
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> WindowMode -> u
forall u. (forall d. Data d => d -> u) -> WindowMode -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WindowMode -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WindowMode -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> WindowMode -> m WindowMode
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WindowMode -> m WindowMode
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WindowMode
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WindowMode -> c WindowMode
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WindowMode)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WindowMode)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WindowMode -> m WindowMode
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WindowMode -> m WindowMode
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WindowMode -> m WindowMode
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WindowMode -> m WindowMode
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> WindowMode -> m WindowMode
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> WindowMode -> m WindowMode
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WindowMode -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WindowMode -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> WindowMode -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> WindowMode -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WindowMode -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WindowMode -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WindowMode -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WindowMode -> r
gmapT :: (forall b. Data b => b -> b) -> WindowMode -> WindowMode
$cgmapT :: (forall b. Data b => b -> b) -> WindowMode -> WindowMode
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WindowMode)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WindowMode)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WindowMode)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c WindowMode)
dataTypeOf :: WindowMode -> DataType
$cdataTypeOf :: WindowMode -> DataType
toConstr :: WindowMode -> Constr
$ctoConstr :: WindowMode -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WindowMode
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c WindowMode
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WindowMode -> c WindowMode
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WindowMode -> c WindowMode
Data, Int -> WindowMode
WindowMode -> Int
WindowMode -> [WindowMode]
WindowMode -> WindowMode
WindowMode -> WindowMode -> [WindowMode]
WindowMode -> WindowMode -> WindowMode -> [WindowMode]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: WindowMode -> WindowMode -> WindowMode -> [WindowMode]
$cenumFromThenTo :: WindowMode -> WindowMode -> WindowMode -> [WindowMode]
enumFromTo :: WindowMode -> WindowMode -> [WindowMode]
$cenumFromTo :: WindowMode -> WindowMode -> [WindowMode]
enumFromThen :: WindowMode -> WindowMode -> [WindowMode]
$cenumFromThen :: WindowMode -> WindowMode -> [WindowMode]
enumFrom :: WindowMode -> [WindowMode]
$cenumFrom :: WindowMode -> [WindowMode]
fromEnum :: WindowMode -> Int
$cfromEnum :: WindowMode -> Int
toEnum :: Int -> WindowMode
$ctoEnum :: Int -> WindowMode
pred :: WindowMode -> WindowMode
$cpred :: WindowMode -> WindowMode
succ :: WindowMode -> WindowMode
$csucc :: WindowMode -> WindowMode
Enum, WindowMode -> WindowMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowMode -> WindowMode -> Bool
$c/= :: WindowMode -> WindowMode -> Bool
== :: WindowMode -> WindowMode -> Bool
$c== :: WindowMode -> WindowMode -> Bool
Eq, forall x. Rep WindowMode x -> WindowMode
forall x. WindowMode -> Rep WindowMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WindowMode x -> WindowMode
$cfrom :: forall x. WindowMode -> Rep WindowMode x
Generic, Eq WindowMode
WindowMode -> WindowMode -> Bool
WindowMode -> WindowMode -> Ordering
WindowMode -> WindowMode -> WindowMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WindowMode -> WindowMode -> WindowMode
$cmin :: WindowMode -> WindowMode -> WindowMode
max :: WindowMode -> WindowMode -> WindowMode
$cmax :: WindowMode -> WindowMode -> WindowMode
>= :: WindowMode -> WindowMode -> Bool
$c>= :: WindowMode -> WindowMode -> Bool
> :: WindowMode -> WindowMode -> Bool
$c> :: WindowMode -> WindowMode -> Bool
<= :: WindowMode -> WindowMode -> Bool
$c<= :: WindowMode -> WindowMode -> Bool
< :: WindowMode -> WindowMode -> Bool
$c< :: WindowMode -> WindowMode -> Bool
compare :: WindowMode -> WindowMode -> Ordering
$ccompare :: WindowMode -> WindowMode -> Ordering
Ord, ReadPrec [WindowMode]
ReadPrec WindowMode
Int -> ReadS WindowMode
ReadS [WindowMode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WindowMode]
$creadListPrec :: ReadPrec [WindowMode]
readPrec :: ReadPrec WindowMode
$creadPrec :: ReadPrec WindowMode
readList :: ReadS [WindowMode]
$creadList :: ReadS [WindowMode]
readsPrec :: Int -> ReadS WindowMode
$creadsPrec :: Int -> ReadS WindowMode
Read, Int -> WindowMode -> ShowS
[WindowMode] -> ShowS
WindowMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowMode] -> ShowS
$cshowList :: [WindowMode] -> ShowS
show :: WindowMode -> String
$cshow :: WindowMode -> String
showsPrec :: Int -> WindowMode -> ShowS
$cshowsPrec :: Int -> WindowMode -> ShowS
Show, Typeable)
instance ToNumber WindowMode Word32 where
toNumber :: WindowMode -> Word32
toNumber WindowMode
Fullscreen = forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_FULLSCREEN
toNumber WindowMode
FullscreenDesktop = forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_FULLSCREEN_DESKTOP
toNumber WindowMode
Maximized = forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_MAXIMIZED
toNumber WindowMode
Minimized = forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_MINIMIZED
toNumber WindowMode
Windowed = Word32
0
instance FromNumber WindowMode Word32 where
fromNumber :: Word32 -> WindowMode
fromNumber Word32
n = forall a. a -> Maybe a -> a
fromMaybe WindowMode
Windowed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. First a -> Maybe a
getFirst forall a b. (a -> b) -> a -> b
$
forall (t :: Type -> Type) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall a. Maybe a -> First a
First [
Maybe WindowMode
sdlWindowFullscreenDesktop
, Maybe WindowMode
sdlWindowFullscreen
, Maybe WindowMode
sdlWindowMaximized
, Maybe WindowMode
sdlWindowMinimized
]
where
maybeBit :: a -> Word32 -> Maybe a
maybeBit a
val Word32
msk = if Word32
n forall a. Bits a => a -> a -> a
.&. Word32
msk forall a. Eq a => a -> a -> Bool
== Word32
msk then forall a. a -> Maybe a
Just a
val else forall a. Maybe a
Nothing
sdlWindowFullscreenDesktop :: Maybe WindowMode
sdlWindowFullscreenDesktop = forall {a}. a -> Word32 -> Maybe a
maybeBit WindowMode
FullscreenDesktop forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_FULLSCREEN_DESKTOP
sdlWindowFullscreen :: Maybe WindowMode
sdlWindowFullscreen = forall {a}. a -> Word32 -> Maybe a
maybeBit WindowMode
Fullscreen forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_FULLSCREEN
sdlWindowMaximized :: Maybe WindowMode
sdlWindowMaximized = forall {a}. a -> Word32 -> Maybe a
maybeBit WindowMode
Maximized forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_MAXIMIZED
sdlWindowMinimized :: Maybe WindowMode
sdlWindowMinimized = forall {a}. a -> Word32 -> Maybe a
maybeBit WindowMode
Minimized forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_MINIMIZED
data WindowPosition
= Centered
| Wherever
| Absolute (Point V2 CInt)
deriving (WindowPosition -> WindowPosition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowPosition -> WindowPosition -> Bool
$c/= :: WindowPosition -> WindowPosition -> Bool
== :: WindowPosition -> WindowPosition -> Bool
$c== :: WindowPosition -> WindowPosition -> Bool
Eq, forall x. Rep WindowPosition x -> WindowPosition
forall x. WindowPosition -> Rep WindowPosition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WindowPosition x -> WindowPosition
$cfrom :: forall x. WindowPosition -> Rep WindowPosition x
Generic, Eq WindowPosition
WindowPosition -> WindowPosition -> Bool
WindowPosition -> WindowPosition -> Ordering
WindowPosition -> WindowPosition -> WindowPosition
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WindowPosition -> WindowPosition -> WindowPosition
$cmin :: WindowPosition -> WindowPosition -> WindowPosition
max :: WindowPosition -> WindowPosition -> WindowPosition
$cmax :: WindowPosition -> WindowPosition -> WindowPosition
>= :: WindowPosition -> WindowPosition -> Bool
$c>= :: WindowPosition -> WindowPosition -> Bool
> :: WindowPosition -> WindowPosition -> Bool
$c> :: WindowPosition -> WindowPosition -> Bool
<= :: WindowPosition -> WindowPosition -> Bool
$c<= :: WindowPosition -> WindowPosition -> Bool
< :: WindowPosition -> WindowPosition -> Bool
$c< :: WindowPosition -> WindowPosition -> Bool
compare :: WindowPosition -> WindowPosition -> Ordering
$ccompare :: WindowPosition -> WindowPosition -> Ordering
Ord, ReadPrec [WindowPosition]
ReadPrec WindowPosition
Int -> ReadS WindowPosition
ReadS [WindowPosition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WindowPosition]
$creadListPrec :: ReadPrec [WindowPosition]
readPrec :: ReadPrec WindowPosition
$creadPrec :: ReadPrec WindowPosition
readList :: ReadS [WindowPosition]
$creadList :: ReadS [WindowPosition]
readsPrec :: Int -> ReadS WindowPosition
$creadsPrec :: Int -> ReadS WindowPosition
Read, Int -> WindowPosition -> ShowS
[WindowPosition] -> ShowS
WindowPosition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowPosition] -> ShowS
$cshowList :: [WindowPosition] -> ShowS
show :: WindowPosition -> String
$cshow :: WindowPosition -> String
showsPrec :: Int -> WindowPosition -> ShowS
$cshowsPrec :: Int -> WindowPosition -> ShowS
Show, Typeable)
destroyWindow :: MonadIO m => Window -> m ()
destroyWindow :: forall (m :: Type -> Type). MonadIO m => Window -> m ()
destroyWindow (Window Window
w) = forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.destroyWindow Window
w
windowBordered :: Window -> StateVar Bool
windowBordered :: Window -> StateVar Bool
windowBordered (Window Window
w) = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO Bool
getWindowBordered Bool -> IO ()
setWindowBordered
where
getWindowBordered :: IO Bool
getWindowBordered = forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap ((forall a. Eq a => a -> a -> Bool
== Word32
0) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Bits a => a -> a -> a
.&. forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_BORDERLESS)) (forall (m :: Type -> Type). MonadIO m => Window -> m Word32
Raw.getWindowFlags Window
w)
setWindowBordered :: Bool -> IO ()
setWindowBordered = forall (m :: Type -> Type). MonadIO m => Window -> Bool -> m ()
Raw.setWindowBordered Window
w
windowBrightness :: Window -> StateVar Float
windowBrightness :: Window -> StateVar Float
windowBrightness (Window Window
w) = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO Float
getWindowBrightness forall {m :: Type -> Type} {a}. (MonadIO m, Real a) => a -> m ()
setWindowBrightness
where
setWindowBrightness :: a -> m ()
setWindowBrightness a
brightness = do
forall a (m :: Type -> Type).
(Eq a, MonadIO m, Num a) =>
Text -> Text -> m a -> m ()
throwIfNot0_ Text
"SDL.Video.setWindowBrightness" Text
"SDL_SetWindowBrightness" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => Window -> CFloat -> m CInt
Raw.setWindowBrightness Window
w forall a b. (a -> b) -> a -> b
$ forall a b. (Real a, Fractional b) => a -> b
realToFrac a
brightness
getWindowBrightness :: IO Float
getWindowBrightness =
forall (m :: Type -> Type) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Real a, Fractional b) => a -> b
realToFrac forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: Type -> Type). MonadIO m => Window -> m CFloat
Raw.getWindowBrightness Window
w
windowGrab :: Window -> StateVar Bool
windowGrab :: Window -> StateVar Bool
windowGrab (Window Window
w) = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO Bool
getWindowGrab Bool -> IO ()
setWindowGrab
where
setWindowGrab :: Bool -> IO ()
setWindowGrab = forall (m :: Type -> Type). MonadIO m => Window -> Bool -> m ()
Raw.setWindowGrab Window
w
getWindowGrab :: IO Bool
getWindowGrab = forall (m :: Type -> Type). MonadIO m => Window -> m Bool
Raw.getWindowGrab Window
w
setWindowMode :: MonadIO m => Window -> WindowMode -> m ()
setWindowMode :: forall (m :: Type -> Type).
MonadIO m =>
Window -> WindowMode -> m ()
setWindowMode (Window Window
w) WindowMode
mode =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (m :: Type -> Type).
(Eq a, MonadIO m, Num a) =>
Text -> Text -> m a -> m ()
throwIfNot0_ Text
"SDL.Video.setWindowMode" Text
"SDL_SetWindowFullscreen" forall a b. (a -> b) -> a -> b
$
case WindowMode
mode of
WindowMode
Fullscreen -> forall (m :: Type -> Type). MonadIO m => Window -> Word32 -> m CInt
Raw.setWindowFullscreen Window
w forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_FULLSCREEN forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.raiseWindow Window
w
WindowMode
FullscreenDesktop -> forall (m :: Type -> Type). MonadIO m => Window -> Word32 -> m CInt
Raw.setWindowFullscreen Window
w forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_FULLSCREEN_DESKTOP forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.raiseWindow Window
w
WindowMode
Maximized -> forall (m :: Type -> Type). MonadIO m => Window -> Word32 -> m CInt
Raw.setWindowFullscreen Window
w Word32
0 forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.maximizeWindow Window
w
WindowMode
Minimized -> forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.minimizeWindow Window
w forall (m :: Type -> Type) a b. Monad m => m a -> m b -> m b
>> forall (m :: Type -> Type) a. Monad m => a -> m a
return CInt
0
WindowMode
Windowed -> forall (m :: Type -> Type). MonadIO m => Window -> Word32 -> m CInt
Raw.setWindowFullscreen Window
w Word32
0 forall (f :: Type -> Type) a b. Applicative f => f a -> f b -> f a
<* forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.restoreWindow Window
w
setWindowIcon :: MonadIO m => Window -> Surface -> m ()
setWindowIcon :: forall (m :: Type -> Type). MonadIO m => Window -> Surface -> m ()
setWindowIcon (Window Window
win) (Surface Ptr Surface
sfc Maybe (IOVector Word8)
_) =
forall (m :: Type -> Type).
MonadIO m =>
Window -> Ptr Surface -> m ()
Raw.setWindowIcon Window
win Ptr Surface
sfc
setWindowPosition :: MonadIO m => Window -> WindowPosition -> m ()
setWindowPosition :: forall (m :: Type -> Type).
MonadIO m =>
Window -> WindowPosition -> m ()
setWindowPosition (Window Window
w) WindowPosition
pos = case WindowPosition
pos of
WindowPosition
Centered -> let u :: CInt
u = forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOWPOS_CENTERED in forall (m :: Type -> Type).
MonadIO m =>
Window -> CInt -> CInt -> m ()
Raw.setWindowPosition Window
w CInt
u CInt
u
WindowPosition
Wherever -> let u :: CInt
u = forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOWPOS_UNDEFINED in forall (m :: Type -> Type).
MonadIO m =>
Window -> CInt -> CInt -> m ()
Raw.setWindowPosition Window
w CInt
u CInt
u
Absolute (P (V2 CInt
x CInt
y)) -> forall (m :: Type -> Type).
MonadIO m =>
Window -> CInt -> CInt -> m ()
Raw.setWindowPosition Window
w CInt
x CInt
y
getWindowAbsolutePosition :: MonadIO m => Window -> m (V2 CInt)
getWindowAbsolutePosition :: forall (m :: Type -> Type). MonadIO m => Window -> m (V2 CInt)
getWindowAbsolutePosition (Window Window
w) =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
wPtr ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
hPtr -> do
forall (m :: Type -> Type).
MonadIO m =>
Window -> Ptr CInt -> Ptr CInt -> m ()
Raw.getWindowPosition Window
w Ptr CInt
wPtr Ptr CInt
hPtr
forall a. a -> a -> V2 a
V2 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
wPtr forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
hPtr
getWindowBordersSize :: MonadIO m => Window -> m (Maybe (V4 CInt))
(Window Window
win) =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
tPtr ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
lPtr ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
bPtr ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
rPtr -> do
CInt
n <- forall (m :: Type -> Type).
MonadIO m =>
Window -> Ptr CInt -> Ptr CInt -> Ptr CInt -> Ptr CInt -> m CInt
Raw.getWindowBordersSize Window
win Ptr CInt
tPtr Ptr CInt
lPtr Ptr CInt
bPtr Ptr CInt
rPtr
if CInt
n forall a. Eq a => a -> a -> Bool
/= CInt
0
then forall (m :: Type -> Type) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
else forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a -> a -> V4 a
V4 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
tPtr forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
lPtr forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
bPtr forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
rPtr
windowSize :: Window -> StateVar (V2 CInt)
windowSize :: Window -> StateVar (V2 CInt)
windowSize (Window Window
win) = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO (V2 CInt)
getWindowSize forall {m :: Type -> Type}. MonadIO m => V2 CInt -> m ()
setWindowSize
where
setWindowSize :: V2 CInt -> m ()
setWindowSize (V2 CInt
w CInt
h) = forall (m :: Type -> Type).
MonadIO m =>
Window -> CInt -> CInt -> m ()
Raw.setWindowSize Window
win CInt
w CInt
h
getWindowSize :: IO (V2 CInt)
getWindowSize =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
wptr ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
hptr -> do
forall (m :: Type -> Type).
MonadIO m =>
Window -> Ptr CInt -> Ptr CInt -> m ()
Raw.getWindowSize Window
win Ptr CInt
wptr Ptr CInt
hptr
forall a. a -> a -> V2 a
V2 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
wptr forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
hptr
windowTitle :: Window -> StateVar Text
windowTitle :: Window -> StateVar Text
windowTitle (Window Window
w) = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO Text
getWindowTitle forall {m :: Type -> Type}. MonadIO m => Text -> m ()
setWindowTitle
where
setWindowTitle :: Text -> m ()
setWindowTitle Text
title =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString (Text -> ByteString
Text.encodeUtf8 Text
title) forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => Window -> CString -> m ()
Raw.setWindowTitle Window
w
getWindowTitle :: IO Text
getWindowTitle = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
CString
cstr <- forall (m :: Type -> Type). MonadIO m => Window -> m CString
Raw.getWindowTitle Window
w
ByteString -> Text
Text.decodeUtf8 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> CString -> IO ByteString
BS.packCString CString
cstr
windowData :: Window -> CString -> StateVar (Ptr ())
windowData :: Window -> CString -> StateVar Window
windowData (Window Window
w) CString
key = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO Window
getWindowData Window -> IO ()
setWindowData
where
setWindowData :: Window -> IO ()
setWindowData = forall (f :: Type -> Type) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: Type -> Type).
MonadIO m =>
Window -> CString -> Window -> m Window
Raw.setWindowData Window
w CString
key
getWindowData :: IO Window
getWindowData = forall (m :: Type -> Type).
MonadIO m =>
Window -> CString -> m Window
Raw.getWindowData Window
w CString
key
getWindowConfig :: MonadIO m => Window -> m WindowConfig
getWindowConfig :: forall (m :: Type -> Type). MonadIO m => Window -> m WindowConfig
getWindowConfig (Window Window
w) = do
Word32
wFlags <- forall (m :: Type -> Type). MonadIO m => Window -> m Word32
Raw.getWindowFlags Window
w
V2 CInt
wSize <- forall t a (m :: Type -> Type).
(HasGetter t a, MonadIO m) =>
t -> m a
get (Window -> StateVar (V2 CInt)
windowSize (Window -> Window
Window Window
w))
V2 CInt
wPos <- forall (m :: Type -> Type). MonadIO m => Window -> m (V2 CInt)
getWindowAbsolutePosition (Window -> Window
Window Window
w)
forall (m :: Type -> Type) a. Monad m => a -> m a
return WindowConfig {
windowBorder :: Bool
windowBorder = Word32
wFlags forall a. Bits a => a -> a -> a
.&. forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_BORDERLESS forall a. Eq a => a -> a -> Bool
== Word32
0
, windowHighDPI :: Bool
windowHighDPI = Word32
wFlags forall a. Bits a => a -> a -> a
.&. forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_ALLOW_HIGHDPI forall a. Ord a => a -> a -> Bool
> Word32
0
, windowInputGrabbed :: Bool
windowInputGrabbed = Word32
wFlags forall a. Bits a => a -> a -> a
.&. forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_INPUT_GRABBED forall a. Ord a => a -> a -> Bool
> Word32
0
, windowMode :: WindowMode
windowMode = forall a b. FromNumber a b => b -> a
fromNumber Word32
wFlags
, windowGraphicsContext :: WindowGraphicsContext
windowGraphicsContext = if Word32
wFlags forall a. Bits a => a -> a -> a
.&. forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_VULKAN forall a. Ord a => a -> a -> Bool
> Word32
0
then WindowGraphicsContext
VulkanContext else WindowGraphicsContext
NoGraphicsContext
, windowPosition :: WindowPosition
windowPosition = Point V2 CInt -> WindowPosition
Absolute (forall (f :: Type -> Type) a. f a -> Point f a
P V2 CInt
wPos)
, windowResizable :: Bool
windowResizable = Word32
wFlags forall a. Bits a => a -> a -> a
.&. forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_RESIZABLE forall a. Ord a => a -> a -> Bool
> Word32
0
, windowInitialSize :: V2 CInt
windowInitialSize = V2 CInt
wSize
, windowVisible :: Bool
windowVisible = Word32
wFlags forall a. Bits a => a -> a -> a
.&. forall {a}. (Eq a, Num a) => a
Raw.SDL_WINDOW_SHOWN forall a. Ord a => a -> a -> Bool
> Word32
0
}
getWindowPixelFormat :: MonadIO m => Window -> m PixelFormat
getWindowPixelFormat :: forall (m :: Type -> Type). MonadIO m => Window -> m PixelFormat
getWindowPixelFormat (Window Window
w) = forall (m :: Type -> Type) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. FromNumber a b => b -> a
fromNumber forall (m :: Type -> Type) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall (m :: Type -> Type). MonadIO m => Window -> m Word32
Raw.getWindowPixelFormat Window
w
getClipboardText :: MonadIO m => m Text
getClipboardText :: forall (m :: Type -> Type). MonadIO m => m Text
getClipboardText = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ do
CString
cstr <- forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Video.getClipboardText" Text
"SDL_GetClipboardText"
forall (m :: Type -> Type). MonadIO m => m CString
Raw.getClipboardText
forall a b. IO a -> IO b -> IO a
finally (ByteString -> Text
Text.decodeUtf8 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> CString -> IO ByteString
BS.packCString CString
cstr) (forall a. Ptr a -> IO ()
free CString
cstr)
hasClipboardText :: MonadIO m => m Bool
hasClipboardText :: forall (m :: Type -> Type). MonadIO m => m Bool
hasClipboardText = forall (m :: Type -> Type). MonadIO m => m Bool
Raw.hasClipboardText
setClipboardText :: MonadIO m => Text -> m ()
setClipboardText :: forall {m :: Type -> Type}. MonadIO m => Text -> m ()
setClipboardText Text
str = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
forall a (m :: Type -> Type).
(Eq a, MonadIO m, Num a) =>
Text -> Text -> m a -> m ()
throwIfNot0_ Text
"SDL.Video.setClipboardText" Text
"SDL_SetClipboardText" forall a b. (a -> b) -> a -> b
$
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString (Text -> ByteString
Text.encodeUtf8 Text
str) forall (m :: Type -> Type). MonadIO m => CString -> m CInt
Raw.setClipboardText
hideWindow :: MonadIO m => Window -> m ()
hideWindow :: forall (m :: Type -> Type). MonadIO m => Window -> m ()
hideWindow (Window Window
w) = forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.hideWindow Window
w
raiseWindow :: MonadIO m => Window -> m ()
raiseWindow :: forall (m :: Type -> Type). MonadIO m => Window -> m ()
raiseWindow (Window Window
w) = forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.raiseWindow Window
w
screenSaverEnabled :: StateVar Bool
screenSaverEnabled :: StateVar Bool
screenSaverEnabled = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar (IO Bool
isScreenSaverEnabled) (forall {m :: Type -> Type}. MonadIO m => Bool -> m ()
setScreenSaverEnabled)
where
isScreenSaverEnabled :: IO Bool
isScreenSaverEnabled = forall (m :: Type -> Type). MonadIO m => m Bool
Raw.isScreenSaverEnabled
setScreenSaverEnabled :: Bool -> m ()
setScreenSaverEnabled Bool
True = forall (m :: Type -> Type). MonadIO m => m ()
Raw.enableScreenSaver
setScreenSaverEnabled Bool
False = forall (m :: Type -> Type). MonadIO m => m ()
Raw.disableScreenSaver
showWindow :: MonadIO m => Window -> m ()
showWindow :: forall (m :: Type -> Type). MonadIO m => Window -> m ()
showWindow (Window Window
w) = forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.showWindow Window
w
windowGammaRamp :: Window -> StateVar (V3 (SV.Vector Word16))
windowGammaRamp :: Window -> StateVar (V3 (Vector Word16))
windowGammaRamp (Window Window
w) = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO (V3 (Vector Word16))
getWindowGammaRamp forall {m :: Type -> Type}. MonadIO m => V3 (Vector Word16) -> m ()
setWindowGammaRamp
where
getWindowGammaRamp :: IO (V3 (Vector Word16))
getWindowGammaRamp =
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
256 forall a b. (a -> b) -> a -> b
$ \Ptr Word16
rPtr ->
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
256 forall a b. (a -> b) -> a -> b
$ \Ptr Word16
gPtr ->
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
256 forall a b. (a -> b) -> a -> b
$ \Ptr Word16
bPtr -> do
forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m ()
throwIfNeg_ Text
"SDL.Video.getWindowGammaRamp" Text
"SDL_GetWindowGammaRamp"
(forall (m :: Type -> Type).
MonadIO m =>
Window -> Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> m CInt
Raw.getWindowGammaRamp Window
w Ptr Word16
rPtr Ptr Word16
gPtr Ptr Word16
bPtr)
forall (f :: Type -> Type) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 forall a. a -> a -> a -> V3 a
V3 (forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Storable a => [a] -> Vector a
SV.fromList (forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
256 Ptr Word16
rPtr))
(forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Storable a => [a] -> Vector a
SV.fromList (forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
256 Ptr Word16
gPtr))
(forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Storable a => [a] -> Vector a
SV.fromList (forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
256 Ptr Word16
bPtr))
setWindowGammaRamp :: V3 (Vector Word16) -> m ()
setWindowGammaRamp (V3 Vector Word16
r Vector Word16
g Vector Word16
b) = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
forall (f :: Type -> Type). Applicative f => Bool -> f () -> f ()
unless (forall (t :: Type -> Type) a.
Foldable t =>
(a -> Bool) -> t a -> Bool
all ((forall a. Eq a => a -> a -> Bool
== Int
256) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Storable a => Vector a -> Int
SV.length) [Vector Word16
r,Vector Word16
g,Vector Word16
b]) forall a b. (a -> b) -> a -> b
$
forall a. HasCallStack => String -> a
error String
"setWindowGammaRamp requires 256 element in each colour channel"
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
SV.unsafeWith Vector Word16
r forall a b. (a -> b) -> a -> b
$ \Ptr Word16
rPtr ->
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
SV.unsafeWith Vector Word16
b forall a b. (a -> b) -> a -> b
$ \Ptr Word16
bPtr ->
forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
SV.unsafeWith Vector Word16
g forall a b. (a -> b) -> a -> b
$ \Ptr Word16
gPtr ->
forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m ()
throwIfNeg_ Text
"SDL.Video.setWindowGammaRamp" Text
"SDL_SetWindowGammaRamp" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type).
MonadIO m =>
Window -> Ptr Word16 -> Ptr Word16 -> Ptr Word16 -> m CInt
Raw.setWindowGammaRamp Window
w Ptr Word16
rPtr Ptr Word16
gPtr Ptr Word16
bPtr
data Display = Display {
Display -> String
displayName :: String
, Display -> Point V2 CInt
displayBoundsPosition :: Point V2 CInt
, Display -> V2 CInt
displayBoundsSize :: V2 CInt
, Display -> [DisplayMode]
displayModes :: [DisplayMode]
}
deriving (Display -> Display -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Display -> Display -> Bool
$c/= :: Display -> Display -> Bool
== :: Display -> Display -> Bool
$c== :: Display -> Display -> Bool
Eq, forall x. Rep Display x -> Display
forall x. Display -> Rep Display x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Display x -> Display
$cfrom :: forall x. Display -> Rep Display x
Generic, Eq Display
Display -> Display -> Bool
Display -> Display -> Ordering
Display -> Display -> Display
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Display -> Display -> Display
$cmin :: Display -> Display -> Display
max :: Display -> Display -> Display
$cmax :: Display -> Display -> Display
>= :: Display -> Display -> Bool
$c>= :: Display -> Display -> Bool
> :: Display -> Display -> Bool
$c> :: Display -> Display -> Bool
<= :: Display -> Display -> Bool
$c<= :: Display -> Display -> Bool
< :: Display -> Display -> Bool
$c< :: Display -> Display -> Bool
compare :: Display -> Display -> Ordering
$ccompare :: Display -> Display -> Ordering
Ord, ReadPrec [Display]
ReadPrec Display
Int -> ReadS Display
ReadS [Display]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Display]
$creadListPrec :: ReadPrec [Display]
readPrec :: ReadPrec Display
$creadPrec :: ReadPrec Display
readList :: ReadS [Display]
$creadList :: ReadS [Display]
readsPrec :: Int -> ReadS Display
$creadsPrec :: Int -> ReadS Display
Read, Int -> Display -> ShowS
[Display] -> ShowS
Display -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Display] -> ShowS
$cshowList :: [Display] -> ShowS
show :: Display -> String
$cshow :: Display -> String
showsPrec :: Int -> Display -> ShowS
$cshowsPrec :: Int -> Display -> ShowS
Show, Typeable)
data DisplayMode = DisplayMode {
DisplayMode -> PixelFormat
displayModeFormat :: PixelFormat
, DisplayMode -> V2 CInt
displayModeSize :: V2 CInt
, DisplayMode -> CInt
displayModeRefreshRate :: CInt
}
deriving (DisplayMode -> DisplayMode -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplayMode -> DisplayMode -> Bool
$c/= :: DisplayMode -> DisplayMode -> Bool
== :: DisplayMode -> DisplayMode -> Bool
$c== :: DisplayMode -> DisplayMode -> Bool
Eq, forall x. Rep DisplayMode x -> DisplayMode
forall x. DisplayMode -> Rep DisplayMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisplayMode x -> DisplayMode
$cfrom :: forall x. DisplayMode -> Rep DisplayMode x
Generic, Eq DisplayMode
DisplayMode -> DisplayMode -> Bool
DisplayMode -> DisplayMode -> Ordering
DisplayMode -> DisplayMode -> DisplayMode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DisplayMode -> DisplayMode -> DisplayMode
$cmin :: DisplayMode -> DisplayMode -> DisplayMode
max :: DisplayMode -> DisplayMode -> DisplayMode
$cmax :: DisplayMode -> DisplayMode -> DisplayMode
>= :: DisplayMode -> DisplayMode -> Bool
$c>= :: DisplayMode -> DisplayMode -> Bool
> :: DisplayMode -> DisplayMode -> Bool
$c> :: DisplayMode -> DisplayMode -> Bool
<= :: DisplayMode -> DisplayMode -> Bool
$c<= :: DisplayMode -> DisplayMode -> Bool
< :: DisplayMode -> DisplayMode -> Bool
$c< :: DisplayMode -> DisplayMode -> Bool
compare :: DisplayMode -> DisplayMode -> Ordering
$ccompare :: DisplayMode -> DisplayMode -> Ordering
Ord, ReadPrec [DisplayMode]
ReadPrec DisplayMode
Int -> ReadS DisplayMode
ReadS [DisplayMode]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DisplayMode]
$creadListPrec :: ReadPrec [DisplayMode]
readPrec :: ReadPrec DisplayMode
$creadPrec :: ReadPrec DisplayMode
readList :: ReadS [DisplayMode]
$creadList :: ReadS [DisplayMode]
readsPrec :: Int -> ReadS DisplayMode
$creadsPrec :: Int -> ReadS DisplayMode
Read, Int -> DisplayMode -> ShowS
[DisplayMode] -> ShowS
DisplayMode -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisplayMode] -> ShowS
$cshowList :: [DisplayMode] -> ShowS
show :: DisplayMode -> String
$cshow :: DisplayMode -> String
showsPrec :: Int -> DisplayMode -> ShowS
$cshowsPrec :: Int -> DisplayMode -> ShowS
Show, Typeable)
data VideoDriver = VideoDriver {
VideoDriver -> String
videoDriverName :: String
}
deriving (Typeable VideoDriver
VideoDriver -> DataType
VideoDriver -> Constr
(forall b. Data b => b -> b) -> VideoDriver -> VideoDriver
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> VideoDriver -> u
forall u. (forall d. Data d => d -> u) -> VideoDriver -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VideoDriver -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VideoDriver -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VideoDriver
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VideoDriver -> c VideoDriver
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VideoDriver)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VideoDriver)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> VideoDriver -> m VideoDriver
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VideoDriver -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> VideoDriver -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> VideoDriver -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> VideoDriver -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VideoDriver -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> VideoDriver -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VideoDriver -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> VideoDriver -> r
gmapT :: (forall b. Data b => b -> b) -> VideoDriver -> VideoDriver
$cgmapT :: (forall b. Data b => b -> b) -> VideoDriver -> VideoDriver
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VideoDriver)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c VideoDriver)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VideoDriver)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c VideoDriver)
dataTypeOf :: VideoDriver -> DataType
$cdataTypeOf :: VideoDriver -> DataType
toConstr :: VideoDriver -> Constr
$ctoConstr :: VideoDriver -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VideoDriver
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c VideoDriver
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VideoDriver -> c VideoDriver
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> VideoDriver -> c VideoDriver
Data, VideoDriver -> VideoDriver -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VideoDriver -> VideoDriver -> Bool
$c/= :: VideoDriver -> VideoDriver -> Bool
== :: VideoDriver -> VideoDriver -> Bool
$c== :: VideoDriver -> VideoDriver -> Bool
Eq, forall x. Rep VideoDriver x -> VideoDriver
forall x. VideoDriver -> Rep VideoDriver x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VideoDriver x -> VideoDriver
$cfrom :: forall x. VideoDriver -> Rep VideoDriver x
Generic, Eq VideoDriver
VideoDriver -> VideoDriver -> Bool
VideoDriver -> VideoDriver -> Ordering
VideoDriver -> VideoDriver -> VideoDriver
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VideoDriver -> VideoDriver -> VideoDriver
$cmin :: VideoDriver -> VideoDriver -> VideoDriver
max :: VideoDriver -> VideoDriver -> VideoDriver
$cmax :: VideoDriver -> VideoDriver -> VideoDriver
>= :: VideoDriver -> VideoDriver -> Bool
$c>= :: VideoDriver -> VideoDriver -> Bool
> :: VideoDriver -> VideoDriver -> Bool
$c> :: VideoDriver -> VideoDriver -> Bool
<= :: VideoDriver -> VideoDriver -> Bool
$c<= :: VideoDriver -> VideoDriver -> Bool
< :: VideoDriver -> VideoDriver -> Bool
$c< :: VideoDriver -> VideoDriver -> Bool
compare :: VideoDriver -> VideoDriver -> Ordering
$ccompare :: VideoDriver -> VideoDriver -> Ordering
Ord, ReadPrec [VideoDriver]
ReadPrec VideoDriver
Int -> ReadS VideoDriver
ReadS [VideoDriver]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VideoDriver]
$creadListPrec :: ReadPrec [VideoDriver]
readPrec :: ReadPrec VideoDriver
$creadPrec :: ReadPrec VideoDriver
readList :: ReadS [VideoDriver]
$creadList :: ReadS [VideoDriver]
readsPrec :: Int -> ReadS VideoDriver
$creadsPrec :: Int -> ReadS VideoDriver
Read, Int -> VideoDriver -> ShowS
[VideoDriver] -> ShowS
VideoDriver -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VideoDriver] -> ShowS
$cshowList :: [VideoDriver] -> ShowS
show :: VideoDriver -> String
$cshow :: VideoDriver -> String
showsPrec :: Int -> VideoDriver -> ShowS
$cshowsPrec :: Int -> VideoDriver -> ShowS
Show, Typeable)
getDisplays :: MonadIO m => m [Display]
getDisplays :: forall (m :: Type -> Type). MonadIO m => m [Display]
getDisplays = forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
CInt
numDisplays <- forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m a
throwIfNeg Text
"SDL.Video.getDisplays" Text
"SDL_GetNumVideoDisplays"
forall (m :: Type -> Type). MonadIO m => m CInt
Raw.getNumVideoDisplays
forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [CInt
0..CInt
numDisplays forall a. Num a => a -> a -> a
- CInt
1] forall a b. (a -> b) -> a -> b
$ \CInt
displayId -> do
CString
name <- forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Video.getDisplays" Text
"SDL_GetDisplayName" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => CInt -> m CString
Raw.getDisplayName CInt
displayId
String
name' <- CString -> IO String
peekCString CString
name
Raw.Rect CInt
x CInt
y CInt
w CInt
h <- forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr Rect
rect -> do
forall a (m :: Type -> Type).
(Eq a, MonadIO m, Num a) =>
Text -> Text -> m a -> m ()
throwIfNot0_ Text
"SDL.Video.getDisplays" Text
"SDL_GetDisplayBounds" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => CInt -> Ptr Rect -> m CInt
Raw.getDisplayBounds CInt
displayId Ptr Rect
rect
forall a. Storable a => Ptr a -> IO a
peek Ptr Rect
rect
CInt
numModes <- forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m a
throwIfNeg Text
"SDL.Video.getDisplays" Text
"SDL_GetNumDisplayModes" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => CInt -> m CInt
Raw.getNumDisplayModes CInt
displayId
[DisplayMode]
modes <- forall (t :: Type -> Type) (m :: Type -> Type) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [CInt
0..CInt
numModes forall a. Num a => a -> a -> a
- CInt
1] forall a b. (a -> b) -> a -> b
$ \CInt
modeId -> do
Raw.DisplayMode Word32
format CInt
w' CInt
h' CInt
refreshRate Window
_ <- forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr DisplayMode
mode -> do
forall a (m :: Type -> Type).
(Eq a, MonadIO m, Num a) =>
Text -> Text -> m a -> m ()
throwIfNot0_ Text
"SDL.Video.getDisplays" Text
"SDL_GetDisplayMode" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type).
MonadIO m =>
CInt -> CInt -> Ptr DisplayMode -> m CInt
Raw.getDisplayMode CInt
displayId CInt
modeId Ptr DisplayMode
mode
forall a. Storable a => Ptr a -> IO a
peek Ptr DisplayMode
mode
forall (m :: Type -> Type) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ DisplayMode {
displayModeFormat :: PixelFormat
displayModeFormat = forall a b. FromNumber a b => b -> a
fromNumber Word32
format
, displayModeSize :: V2 CInt
displayModeSize = forall a. a -> a -> V2 a
V2 CInt
w' CInt
h'
, displayModeRefreshRate :: CInt
displayModeRefreshRate = CInt
refreshRate
}
forall (m :: Type -> Type) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Display {
displayName :: String
displayName = String
name'
, displayBoundsPosition :: Point V2 CInt
displayBoundsPosition = forall (f :: Type -> Type) a. f a -> Point f a
P (forall a. a -> a -> V2 a
V2 CInt
x CInt
y)
, displayBoundsSize :: V2 CInt
displayBoundsSize = forall a. a -> a -> V2 a
V2 CInt
w CInt
h
, displayModes :: [DisplayMode]
displayModes = [DisplayMode]
modes
}
showSimpleMessageBox :: MonadIO m => Maybe Window -> MessageKind -> Text -> Text -> m ()
showSimpleMessageBox :: forall (m :: Type -> Type).
MonadIO m =>
Maybe Window -> MessageKind -> Text -> Text -> m ()
showSimpleMessageBox Maybe Window
window MessageKind
kind Text
title Text
message =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a (m :: Type -> Type).
(Eq a, MonadIO m, Num a) =>
Text -> Text -> m a -> m ()
throwIfNot0_ Text
"SDL.Video.showSimpleMessageBox" Text
"SDL_ShowSimpleMessageBox" forall a b. (a -> b) -> a -> b
$ do
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString (Text -> ByteString
Text.encodeUtf8 Text
title) forall a b. (a -> b) -> a -> b
$ \CString
title' ->
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString (Text -> ByteString
Text.encodeUtf8 Text
message) forall a b. (a -> b) -> a -> b
$ \CString
message' ->
forall (m :: Type -> Type).
MonadIO m =>
Word32 -> CString -> CString -> Window -> m CInt
Raw.showSimpleMessageBox (forall a b. ToNumber a b => a -> b
toNumber MessageKind
kind) CString
title' CString
message' forall a b. (a -> b) -> a -> b
$
Maybe Window -> Window
windowId Maybe Window
window
where
windowId :: Maybe Window -> Window
windowId (Just (Window Window
w)) = Window
w
windowId Maybe Window
Nothing = forall a. Ptr a
nullPtr
data MessageKind
= Error
| Warning
| Information
deriving (MessageKind
forall a. a -> a -> Bounded a
maxBound :: MessageKind
$cmaxBound :: MessageKind
minBound :: MessageKind
$cminBound :: MessageKind
Bounded, Typeable MessageKind
MessageKind -> DataType
MessageKind -> Constr
(forall b. Data b => b -> b) -> MessageKind -> MessageKind
forall a.
Typeable a
-> (forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> MessageKind -> u
forall u. (forall d. Data d => d -> u) -> MessageKind -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MessageKind -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MessageKind -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> MessageKind -> m MessageKind
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MessageKind -> m MessageKind
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MessageKind
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MessageKind -> c MessageKind
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MessageKind)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MessageKind)
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MessageKind -> m MessageKind
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MessageKind -> m MessageKind
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MessageKind -> m MessageKind
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MessageKind -> m MessageKind
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> MessageKind -> m MessageKind
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> MessageKind -> m MessageKind
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MessageKind -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MessageKind -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> MessageKind -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MessageKind -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MessageKind -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MessageKind -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MessageKind -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MessageKind -> r
gmapT :: (forall b. Data b => b -> b) -> MessageKind -> MessageKind
$cgmapT :: (forall b. Data b => b -> b) -> MessageKind -> MessageKind
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MessageKind)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MessageKind)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MessageKind)
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MessageKind)
dataTypeOf :: MessageKind -> DataType
$cdataTypeOf :: MessageKind -> DataType
toConstr :: MessageKind -> Constr
$ctoConstr :: MessageKind -> Constr
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MessageKind
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MessageKind
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MessageKind -> c MessageKind
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MessageKind -> c MessageKind
Data, Int -> MessageKind
MessageKind -> Int
MessageKind -> [MessageKind]
MessageKind -> MessageKind
MessageKind -> MessageKind -> [MessageKind]
MessageKind -> MessageKind -> MessageKind -> [MessageKind]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: MessageKind -> MessageKind -> MessageKind -> [MessageKind]
$cenumFromThenTo :: MessageKind -> MessageKind -> MessageKind -> [MessageKind]
enumFromTo :: MessageKind -> MessageKind -> [MessageKind]
$cenumFromTo :: MessageKind -> MessageKind -> [MessageKind]
enumFromThen :: MessageKind -> MessageKind -> [MessageKind]
$cenumFromThen :: MessageKind -> MessageKind -> [MessageKind]
enumFrom :: MessageKind -> [MessageKind]
$cenumFrom :: MessageKind -> [MessageKind]
fromEnum :: MessageKind -> Int
$cfromEnum :: MessageKind -> Int
toEnum :: Int -> MessageKind
$ctoEnum :: Int -> MessageKind
pred :: MessageKind -> MessageKind
$cpred :: MessageKind -> MessageKind
succ :: MessageKind -> MessageKind
$csucc :: MessageKind -> MessageKind
Enum, MessageKind -> MessageKind -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageKind -> MessageKind -> Bool
$c/= :: MessageKind -> MessageKind -> Bool
== :: MessageKind -> MessageKind -> Bool
$c== :: MessageKind -> MessageKind -> Bool
Eq, forall x. Rep MessageKind x -> MessageKind
forall x. MessageKind -> Rep MessageKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MessageKind x -> MessageKind
$cfrom :: forall x. MessageKind -> Rep MessageKind x
Generic, Eq MessageKind
MessageKind -> MessageKind -> Bool
MessageKind -> MessageKind -> Ordering
MessageKind -> MessageKind -> MessageKind
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MessageKind -> MessageKind -> MessageKind
$cmin :: MessageKind -> MessageKind -> MessageKind
max :: MessageKind -> MessageKind -> MessageKind
$cmax :: MessageKind -> MessageKind -> MessageKind
>= :: MessageKind -> MessageKind -> Bool
$c>= :: MessageKind -> MessageKind -> Bool
> :: MessageKind -> MessageKind -> Bool
$c> :: MessageKind -> MessageKind -> Bool
<= :: MessageKind -> MessageKind -> Bool
$c<= :: MessageKind -> MessageKind -> Bool
< :: MessageKind -> MessageKind -> Bool
$c< :: MessageKind -> MessageKind -> Bool
compare :: MessageKind -> MessageKind -> Ordering
$ccompare :: MessageKind -> MessageKind -> Ordering
Ord, ReadPrec [MessageKind]
ReadPrec MessageKind
Int -> ReadS MessageKind
ReadS [MessageKind]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MessageKind]
$creadListPrec :: ReadPrec [MessageKind]
readPrec :: ReadPrec MessageKind
$creadPrec :: ReadPrec MessageKind
readList :: ReadS [MessageKind]
$creadList :: ReadS [MessageKind]
readsPrec :: Int -> ReadS MessageKind
$creadsPrec :: Int -> ReadS MessageKind
Read, Int -> MessageKind -> ShowS
[MessageKind] -> ShowS
MessageKind -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageKind] -> ShowS
$cshowList :: [MessageKind] -> ShowS
show :: MessageKind -> String
$cshow :: MessageKind -> String
showsPrec :: Int -> MessageKind -> ShowS
$cshowsPrec :: Int -> MessageKind -> ShowS
Show, Typeable)
instance ToNumber MessageKind Word32 where
toNumber :: MessageKind -> Word32
toNumber MessageKind
Error = forall {a}. (Eq a, Num a) => a
Raw.SDL_MESSAGEBOX_ERROR
toNumber MessageKind
Warning = forall {a}. (Eq a, Num a) => a
Raw.SDL_MESSAGEBOX_WARNING
toNumber MessageKind
Information = forall {a}. (Eq a, Num a) => a
Raw.SDL_MESSAGEBOX_INFORMATION
windowMaximumSize :: Window -> StateVar (V2 CInt)
windowMaximumSize :: Window -> StateVar (V2 CInt)
windowMaximumSize (Window Window
win) = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO (V2 CInt)
getWindowMaximumSize forall {m :: Type -> Type}. MonadIO m => V2 CInt -> m ()
setWindowMaximumSize
where
setWindowMaximumSize :: V2 CInt -> m ()
setWindowMaximumSize (V2 CInt
w CInt
h) = forall (m :: Type -> Type).
MonadIO m =>
Window -> CInt -> CInt -> m ()
Raw.setWindowMaximumSize Window
win CInt
w CInt
h
getWindowMaximumSize :: IO (V2 CInt)
getWindowMaximumSize =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
wptr ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
hptr -> do
forall (m :: Type -> Type).
MonadIO m =>
Window -> Ptr CInt -> Ptr CInt -> m ()
Raw.getWindowMaximumSize Window
win Ptr CInt
wptr Ptr CInt
hptr
forall a. a -> a -> V2 a
V2 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
wptr forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
hptr
windowMinimumSize :: Window -> StateVar (V2 CInt)
windowMinimumSize :: Window -> StateVar (V2 CInt)
windowMinimumSize (Window Window
win) = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO (V2 CInt)
getWindowMinimumSize forall {m :: Type -> Type}. MonadIO m => V2 CInt -> m ()
setWindowMinimumSize
where
setWindowMinimumSize :: V2 CInt -> m ()
setWindowMinimumSize (V2 CInt
w CInt
h) = forall (m :: Type -> Type).
MonadIO m =>
Window -> CInt -> CInt -> m ()
Raw.setWindowMinimumSize Window
win CInt
w CInt
h
getWindowMinimumSize :: IO (V2 CInt)
getWindowMinimumSize =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
wptr ->
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CInt
hptr -> do
forall (m :: Type -> Type).
MonadIO m =>
Window -> Ptr CInt -> Ptr CInt -> m ()
Raw.getWindowMinimumSize Window
win Ptr CInt
wptr Ptr CInt
hptr
forall a. a -> a -> V2 a
V2 forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
wptr forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
hptr
windowOpacity :: Window -> StateVar CFloat
windowOpacity :: Window -> StateVar CFloat
windowOpacity (Window Window
win) = forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO CFloat
getWindowOpacity forall {m :: Type -> Type}. MonadIO m => CFloat -> m ()
setWindowOpacity
where
setWindowOpacity :: CFloat -> m ()
setWindowOpacity CFloat
opacity = forall (m :: Type -> Type). MonadIO m => Window -> CFloat -> m ()
Raw.setWindowOpacity Window
win CFloat
opacity
getWindowOpacity :: IO CFloat
getWindowOpacity =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca forall a b. (a -> b) -> a -> b
$ \Ptr CFloat
optr -> do
forall (m :: Type -> Type).
MonadIO m =>
Window -> Ptr CFloat -> m ()
Raw.getWindowOpacity Window
win Ptr CFloat
optr
forall a. Storable a => Ptr a -> IO a
peek Ptr CFloat
optr
createRenderer :: MonadIO m => Window -> CInt -> RendererConfig -> m Renderer
createRenderer :: forall (m :: Type -> Type).
MonadIO m =>
Window -> CInt -> RendererConfig -> m Renderer
createRenderer (Window Window
w) CInt
driver RendererConfig
config =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Window -> Renderer
Renderer forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Video.createRenderer" Text
"SDL_CreateRenderer" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type).
MonadIO m =>
Window -> CInt -> Word32 -> m Window
Raw.createRenderer Window
w CInt
driver (forall a b. ToNumber a b => a -> b
toNumber RendererConfig
config)
createSoftwareRenderer :: MonadIO m => Surface -> m Renderer
createSoftwareRenderer :: forall (m :: Type -> Type). MonadIO m => Surface -> m Renderer
createSoftwareRenderer (Surface Ptr Surface
ptr Maybe (IOVector Word8)
_) =
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap Window -> Renderer
Renderer forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Video.createSoftwareRenderer" Text
"SDL_CreateSoftwareRenderer" forall a b. (a -> b) -> a -> b
$
forall (m :: Type -> Type). MonadIO m => Ptr Surface -> m Window
Raw.createSoftwareRenderer Ptr Surface
ptr
destroyRenderer :: MonadIO m => Renderer -> m ()
destroyRenderer :: forall (m :: Type -> Type). MonadIO m => Renderer -> m ()
destroyRenderer (Renderer Window
r) = forall (m :: Type -> Type). MonadIO m => Window -> m ()
Raw.destroyRenderer Window
r