{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
module SDL.Video.OpenGL
(
defaultOpenGL
, OpenGLConfig(..)
, GLContext
, glCreateContext
, Profile(..)
, Mode(..)
, glMakeCurrent
, glDeleteContext
, glGetDrawableSize
, glSwapWindow
, SwapInterval(..)
, swapInterval
, Raw.glGetProcAddress
) where
import Control.Monad.IO.Class (MonadIO, liftIO)
import Data.Data (Data)
import Data.StateVar
import Data.Typeable
import Foreign hiding (void, throwIfNull, throwIfNeg, throwIfNeg_)
import Foreign.C.Types
import GHC.Generics (Generic)
import SDL.Vect
import SDL.Internal.Exception
import SDL.Internal.Numbered
import SDL.Internal.Types
import qualified SDL.Raw as Raw
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
defaultOpenGL :: OpenGLConfig
defaultOpenGL :: OpenGLConfig
defaultOpenGL = OpenGLConfig
{ glColorPrecision :: V4 CInt
glColorPrecision = CInt -> CInt -> CInt -> CInt -> V4 CInt
forall a. a -> a -> a -> a -> V4 a
V4 CInt
8 CInt
8 CInt
8 CInt
0
, glDepthPrecision :: CInt
glDepthPrecision = CInt
24
, glStencilPrecision :: CInt
glStencilPrecision = CInt
8
, glMultisampleSamples :: CInt
glMultisampleSamples = CInt
1
, glProfile :: Profile
glProfile = Mode -> CInt -> CInt -> Profile
Compatibility Mode
Normal CInt
2 CInt
1
}
data OpenGLConfig = OpenGLConfig
{ OpenGLConfig -> V4 CInt
glColorPrecision :: V4 CInt
, OpenGLConfig -> CInt
glDepthPrecision :: CInt
, OpenGLConfig -> CInt
glStencilPrecision :: CInt
, OpenGLConfig -> CInt
glMultisampleSamples :: CInt
, OpenGLConfig -> Profile
glProfile :: Profile
} deriving (OpenGLConfig -> OpenGLConfig -> Bool
(OpenGLConfig -> OpenGLConfig -> Bool)
-> (OpenGLConfig -> OpenGLConfig -> Bool) -> Eq OpenGLConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpenGLConfig -> OpenGLConfig -> Bool
== :: OpenGLConfig -> OpenGLConfig -> Bool
$c/= :: OpenGLConfig -> OpenGLConfig -> Bool
/= :: OpenGLConfig -> OpenGLConfig -> Bool
Eq, (forall x. OpenGLConfig -> Rep OpenGLConfig x)
-> (forall x. Rep OpenGLConfig x -> OpenGLConfig)
-> Generic OpenGLConfig
forall x. Rep OpenGLConfig x -> OpenGLConfig
forall x. OpenGLConfig -> Rep OpenGLConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OpenGLConfig -> Rep OpenGLConfig x
from :: forall x. OpenGLConfig -> Rep OpenGLConfig x
$cto :: forall x. Rep OpenGLConfig x -> OpenGLConfig
to :: forall x. Rep OpenGLConfig x -> OpenGLConfig
Generic, Eq OpenGLConfig
Eq OpenGLConfig =>
(OpenGLConfig -> OpenGLConfig -> Ordering)
-> (OpenGLConfig -> OpenGLConfig -> Bool)
-> (OpenGLConfig -> OpenGLConfig -> Bool)
-> (OpenGLConfig -> OpenGLConfig -> Bool)
-> (OpenGLConfig -> OpenGLConfig -> Bool)
-> (OpenGLConfig -> OpenGLConfig -> OpenGLConfig)
-> (OpenGLConfig -> OpenGLConfig -> OpenGLConfig)
-> Ord OpenGLConfig
OpenGLConfig -> OpenGLConfig -> Bool
OpenGLConfig -> OpenGLConfig -> Ordering
OpenGLConfig -> OpenGLConfig -> OpenGLConfig
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
$ccompare :: OpenGLConfig -> OpenGLConfig -> Ordering
compare :: OpenGLConfig -> OpenGLConfig -> Ordering
$c< :: OpenGLConfig -> OpenGLConfig -> Bool
< :: OpenGLConfig -> OpenGLConfig -> Bool
$c<= :: OpenGLConfig -> OpenGLConfig -> Bool
<= :: OpenGLConfig -> OpenGLConfig -> Bool
$c> :: OpenGLConfig -> OpenGLConfig -> Bool
> :: OpenGLConfig -> OpenGLConfig -> Bool
$c>= :: OpenGLConfig -> OpenGLConfig -> Bool
>= :: OpenGLConfig -> OpenGLConfig -> Bool
$cmax :: OpenGLConfig -> OpenGLConfig -> OpenGLConfig
max :: OpenGLConfig -> OpenGLConfig -> OpenGLConfig
$cmin :: OpenGLConfig -> OpenGLConfig -> OpenGLConfig
min :: OpenGLConfig -> OpenGLConfig -> OpenGLConfig
Ord, ReadPrec [OpenGLConfig]
ReadPrec OpenGLConfig
Int -> ReadS OpenGLConfig
ReadS [OpenGLConfig]
(Int -> ReadS OpenGLConfig)
-> ReadS [OpenGLConfig]
-> ReadPrec OpenGLConfig
-> ReadPrec [OpenGLConfig]
-> Read OpenGLConfig
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OpenGLConfig
readsPrec :: Int -> ReadS OpenGLConfig
$creadList :: ReadS [OpenGLConfig]
readList :: ReadS [OpenGLConfig]
$creadPrec :: ReadPrec OpenGLConfig
readPrec :: ReadPrec OpenGLConfig
$creadListPrec :: ReadPrec [OpenGLConfig]
readListPrec :: ReadPrec [OpenGLConfig]
Read, Int -> OpenGLConfig -> ShowS
[OpenGLConfig] -> ShowS
OpenGLConfig -> String
(Int -> OpenGLConfig -> ShowS)
-> (OpenGLConfig -> String)
-> ([OpenGLConfig] -> ShowS)
-> Show OpenGLConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpenGLConfig -> ShowS
showsPrec :: Int -> OpenGLConfig -> ShowS
$cshow :: OpenGLConfig -> String
show :: OpenGLConfig -> String
$cshowList :: [OpenGLConfig] -> ShowS
showList :: [OpenGLConfig] -> ShowS
Show, Typeable)
data Profile
= Core Mode CInt CInt
| Compatibility Mode CInt CInt
| ES Mode CInt CInt
deriving (Profile -> Profile -> Bool
(Profile -> Profile -> Bool)
-> (Profile -> Profile -> Bool) -> Eq Profile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Profile -> Profile -> Bool
== :: Profile -> Profile -> Bool
$c/= :: Profile -> Profile -> Bool
/= :: Profile -> Profile -> Bool
Eq, (forall x. Profile -> Rep Profile x)
-> (forall x. Rep Profile x -> Profile) -> Generic Profile
forall x. Rep Profile x -> Profile
forall x. Profile -> Rep Profile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Profile -> Rep Profile x
from :: forall x. Profile -> Rep Profile x
$cto :: forall x. Rep Profile x -> Profile
to :: forall x. Rep Profile x -> Profile
Generic, Eq Profile
Eq Profile =>
(Profile -> Profile -> Ordering)
-> (Profile -> Profile -> Bool)
-> (Profile -> Profile -> Bool)
-> (Profile -> Profile -> Bool)
-> (Profile -> Profile -> Bool)
-> (Profile -> Profile -> Profile)
-> (Profile -> Profile -> Profile)
-> Ord Profile
Profile -> Profile -> Bool
Profile -> Profile -> Ordering
Profile -> Profile -> Profile
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
$ccompare :: Profile -> Profile -> Ordering
compare :: Profile -> Profile -> Ordering
$c< :: Profile -> Profile -> Bool
< :: Profile -> Profile -> Bool
$c<= :: Profile -> Profile -> Bool
<= :: Profile -> Profile -> Bool
$c> :: Profile -> Profile -> Bool
> :: Profile -> Profile -> Bool
$c>= :: Profile -> Profile -> Bool
>= :: Profile -> Profile -> Bool
$cmax :: Profile -> Profile -> Profile
max :: Profile -> Profile -> Profile
$cmin :: Profile -> Profile -> Profile
min :: Profile -> Profile -> Profile
Ord, ReadPrec [Profile]
ReadPrec Profile
Int -> ReadS Profile
ReadS [Profile]
(Int -> ReadS Profile)
-> ReadS [Profile]
-> ReadPrec Profile
-> ReadPrec [Profile]
-> Read Profile
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Profile
readsPrec :: Int -> ReadS Profile
$creadList :: ReadS [Profile]
readList :: ReadS [Profile]
$creadPrec :: ReadPrec Profile
readPrec :: ReadPrec Profile
$creadListPrec :: ReadPrec [Profile]
readListPrec :: ReadPrec [Profile]
Read, Int -> Profile -> ShowS
[Profile] -> ShowS
Profile -> String
(Int -> Profile -> ShowS)
-> (Profile -> String) -> ([Profile] -> ShowS) -> Show Profile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Profile -> ShowS
showsPrec :: Int -> Profile -> ShowS
$cshow :: Profile -> String
show :: Profile -> String
$cshowList :: [Profile] -> ShowS
showList :: [Profile] -> ShowS
Show, Typeable)
data Mode
= Normal
| Debug
deriving (Mode
Mode -> Mode -> Bounded Mode
forall a. a -> a -> Bounded a
$cminBound :: Mode
minBound :: Mode
$cmaxBound :: Mode
maxBound :: Mode
Bounded, Typeable Mode
Typeable Mode =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Mode -> c Mode)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Mode)
-> (Mode -> Constr)
-> (Mode -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Mode))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mode))
-> ((forall b. Data b => b -> b) -> Mode -> Mode)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r)
-> (forall u. (forall d. Data d => d -> u) -> Mode -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Mode -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode)
-> Data Mode
Mode -> Constr
Mode -> DataType
(forall b. Data b => b -> b) -> Mode -> Mode
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) -> Mode -> u
forall u. (forall d. Data d => d -> u) -> Mode -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Mode
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Mode -> c Mode
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Mode)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mode)
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Mode -> c Mode
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Mode -> c Mode
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Mode
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Mode
$ctoConstr :: Mode -> Constr
toConstr :: Mode -> Constr
$cdataTypeOf :: Mode -> DataType
dataTypeOf :: Mode -> DataType
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Mode)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Mode)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mode)
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mode)
$cgmapT :: (forall b. Data b => b -> b) -> Mode -> Mode
gmapT :: (forall b. Data b => b -> b) -> Mode -> Mode
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mode -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Mode -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Mode -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Mode -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Mode -> u
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Mode -> m Mode
Data, Int -> Mode
Mode -> Int
Mode -> [Mode]
Mode -> Mode
Mode -> Mode -> [Mode]
Mode -> Mode -> Mode -> [Mode]
(Mode -> Mode)
-> (Mode -> Mode)
-> (Int -> Mode)
-> (Mode -> Int)
-> (Mode -> [Mode])
-> (Mode -> Mode -> [Mode])
-> (Mode -> Mode -> [Mode])
-> (Mode -> Mode -> Mode -> [Mode])
-> Enum Mode
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Mode -> Mode
succ :: Mode -> Mode
$cpred :: Mode -> Mode
pred :: Mode -> Mode
$ctoEnum :: Int -> Mode
toEnum :: Int -> Mode
$cfromEnum :: Mode -> Int
fromEnum :: Mode -> Int
$cenumFrom :: Mode -> [Mode]
enumFrom :: Mode -> [Mode]
$cenumFromThen :: Mode -> Mode -> [Mode]
enumFromThen :: Mode -> Mode -> [Mode]
$cenumFromTo :: Mode -> Mode -> [Mode]
enumFromTo :: Mode -> Mode -> [Mode]
$cenumFromThenTo :: Mode -> Mode -> Mode -> [Mode]
enumFromThenTo :: Mode -> Mode -> Mode -> [Mode]
Enum, Mode -> Mode -> Bool
(Mode -> Mode -> Bool) -> (Mode -> Mode -> Bool) -> Eq Mode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Mode -> Mode -> Bool
== :: Mode -> Mode -> Bool
$c/= :: Mode -> Mode -> Bool
/= :: Mode -> Mode -> Bool
Eq, (forall x. Mode -> Rep Mode x)
-> (forall x. Rep Mode x -> Mode) -> Generic Mode
forall x. Rep Mode x -> Mode
forall x. Mode -> Rep Mode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Mode -> Rep Mode x
from :: forall x. Mode -> Rep Mode x
$cto :: forall x. Rep Mode x -> Mode
to :: forall x. Rep Mode x -> Mode
Generic, Eq Mode
Eq Mode =>
(Mode -> Mode -> Ordering)
-> (Mode -> Mode -> Bool)
-> (Mode -> Mode -> Bool)
-> (Mode -> Mode -> Bool)
-> (Mode -> Mode -> Bool)
-> (Mode -> Mode -> Mode)
-> (Mode -> Mode -> Mode)
-> Ord Mode
Mode -> Mode -> Bool
Mode -> Mode -> Ordering
Mode -> Mode -> Mode
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
$ccompare :: Mode -> Mode -> Ordering
compare :: Mode -> Mode -> Ordering
$c< :: Mode -> Mode -> Bool
< :: Mode -> Mode -> Bool
$c<= :: Mode -> Mode -> Bool
<= :: Mode -> Mode -> Bool
$c> :: Mode -> Mode -> Bool
> :: Mode -> Mode -> Bool
$c>= :: Mode -> Mode -> Bool
>= :: Mode -> Mode -> Bool
$cmax :: Mode -> Mode -> Mode
max :: Mode -> Mode -> Mode
$cmin :: Mode -> Mode -> Mode
min :: Mode -> Mode -> Mode
Ord, ReadPrec [Mode]
ReadPrec Mode
Int -> ReadS Mode
ReadS [Mode]
(Int -> ReadS Mode)
-> ReadS [Mode] -> ReadPrec Mode -> ReadPrec [Mode] -> Read Mode
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Mode
readsPrec :: Int -> ReadS Mode
$creadList :: ReadS [Mode]
readList :: ReadS [Mode]
$creadPrec :: ReadPrec Mode
readPrec :: ReadPrec Mode
$creadListPrec :: ReadPrec [Mode]
readListPrec :: ReadPrec [Mode]
Read, Int -> Mode -> ShowS
[Mode] -> ShowS
Mode -> String
(Int -> Mode -> ShowS)
-> (Mode -> String) -> ([Mode] -> ShowS) -> Show Mode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Mode -> ShowS
showsPrec :: Int -> Mode -> ShowS
$cshow :: Mode -> String
show :: Mode -> String
$cshowList :: [Mode] -> ShowS
showList :: [Mode] -> ShowS
Show, Typeable)
newtype GLContext = GLContext Raw.GLContext
deriving (GLContext -> GLContext -> Bool
(GLContext -> GLContext -> Bool)
-> (GLContext -> GLContext -> Bool) -> Eq GLContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GLContext -> GLContext -> Bool
== :: GLContext -> GLContext -> Bool
$c/= :: GLContext -> GLContext -> Bool
/= :: GLContext -> GLContext -> Bool
Eq, Typeable)
glCreateContext :: (Functor m, MonadIO m) => Window -> m GLContext
glCreateContext :: forall (m :: Type -> Type).
(Functor m, MonadIO m) =>
Window -> m GLContext
glCreateContext (Window GLContext
w) =
GLContext -> GLContext
GLContext (GLContext -> GLContext) -> m GLContext -> m GLContext
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> m GLContext -> m GLContext
forall (m :: Type -> Type) a.
MonadIO m =>
Text -> Text -> m (Ptr a) -> m (Ptr a)
throwIfNull Text
"SDL.Video.glCreateContext" Text
"SDL_GL_CreateContext"
(GLContext -> m GLContext
forall (m :: Type -> Type). MonadIO m => GLContext -> m GLContext
Raw.glCreateContext GLContext
w)
glMakeCurrent :: (Functor m, MonadIO m) => Window -> GLContext -> m ()
glMakeCurrent :: forall (m :: Type -> Type).
(Functor m, MonadIO m) =>
Window -> GLContext -> m ()
glMakeCurrent (Window GLContext
w) (GLContext GLContext
ctx) =
Text -> Text -> m CInt -> m ()
forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m ()
throwIfNeg_ Text
"SDL.Video.OpenGL.glMakeCurrent" Text
"SDL_GL_MakeCurrent" (m CInt -> m ()) -> m CInt -> m ()
forall a b. (a -> b) -> a -> b
$
GLContext -> GLContext -> m CInt
forall (m :: Type -> Type).
MonadIO m =>
GLContext -> GLContext -> m CInt
Raw.glMakeCurrent GLContext
w GLContext
ctx
glDeleteContext :: MonadIO m => GLContext -> m ()
glDeleteContext :: forall (m :: Type -> Type). MonadIO m => GLContext -> m ()
glDeleteContext (GLContext GLContext
ctx) = GLContext -> m ()
forall (m :: Type -> Type). MonadIO m => GLContext -> m ()
Raw.glDeleteContext GLContext
ctx
glSwapWindow :: MonadIO m => Window -> m ()
glSwapWindow :: forall (m :: Type -> Type). MonadIO m => Window -> m ()
glSwapWindow (Window GLContext
w) = GLContext -> m ()
forall (m :: Type -> Type). MonadIO m => GLContext -> m ()
Raw.glSwapWindow GLContext
w
data SwapInterval
= ImmediateUpdates
| SynchronizedUpdates
| LateSwapTearing
deriving (SwapInterval
SwapInterval -> SwapInterval -> Bounded SwapInterval
forall a. a -> a -> Bounded a
$cminBound :: SwapInterval
minBound :: SwapInterval
$cmaxBound :: SwapInterval
maxBound :: SwapInterval
Bounded, Typeable SwapInterval
Typeable SwapInterval =>
(forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SwapInterval -> c SwapInterval)
-> (forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SwapInterval)
-> (SwapInterval -> Constr)
-> (SwapInterval -> DataType)
-> (forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SwapInterval))
-> (forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SwapInterval))
-> ((forall b. Data b => b -> b) -> SwapInterval -> SwapInterval)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SwapInterval -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SwapInterval -> r)
-> (forall u. (forall d. Data d => d -> u) -> SwapInterval -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> SwapInterval -> u)
-> (forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval)
-> (forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval)
-> Data SwapInterval
SwapInterval -> Constr
SwapInterval -> DataType
(forall b. Data b => b -> b) -> SwapInterval -> SwapInterval
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) -> SwapInterval -> u
forall u. (forall d. Data d => d -> u) -> SwapInterval -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SwapInterval -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SwapInterval -> r
forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval
forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval
forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SwapInterval
forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SwapInterval -> c SwapInterval
forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SwapInterval)
forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SwapInterval)
$cgfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SwapInterval -> c SwapInterval
gfoldl :: forall (c :: Type -> Type).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> SwapInterval -> c SwapInterval
$cgunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SwapInterval
gunfold :: forall (c :: Type -> Type).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c SwapInterval
$ctoConstr :: SwapInterval -> Constr
toConstr :: SwapInterval -> Constr
$cdataTypeOf :: SwapInterval -> DataType
dataTypeOf :: SwapInterval -> DataType
$cdataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SwapInterval)
dataCast1 :: forall (t :: Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c SwapInterval)
$cdataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SwapInterval)
dataCast2 :: forall (t :: Type -> Type -> Type) (c :: Type -> Type).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c SwapInterval)
$cgmapT :: (forall b. Data b => b -> b) -> SwapInterval -> SwapInterval
gmapT :: (forall b. Data b => b -> b) -> SwapInterval -> SwapInterval
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SwapInterval -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> SwapInterval -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SwapInterval -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> SwapInterval -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> SwapInterval -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> SwapInterval -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SwapInterval -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> SwapInterval -> u
$cgmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval
gmapM :: forall (m :: Type -> Type).
Monad m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval
$cgmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval
gmapMp :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval
$cgmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval
gmapMo :: forall (m :: Type -> Type).
MonadPlus m =>
(forall d. Data d => d -> m d) -> SwapInterval -> m SwapInterval
Data, Int -> SwapInterval
SwapInterval -> Int
SwapInterval -> [SwapInterval]
SwapInterval -> SwapInterval
SwapInterval -> SwapInterval -> [SwapInterval]
SwapInterval -> SwapInterval -> SwapInterval -> [SwapInterval]
(SwapInterval -> SwapInterval)
-> (SwapInterval -> SwapInterval)
-> (Int -> SwapInterval)
-> (SwapInterval -> Int)
-> (SwapInterval -> [SwapInterval])
-> (SwapInterval -> SwapInterval -> [SwapInterval])
-> (SwapInterval -> SwapInterval -> [SwapInterval])
-> (SwapInterval -> SwapInterval -> SwapInterval -> [SwapInterval])
-> Enum SwapInterval
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: SwapInterval -> SwapInterval
succ :: SwapInterval -> SwapInterval
$cpred :: SwapInterval -> SwapInterval
pred :: SwapInterval -> SwapInterval
$ctoEnum :: Int -> SwapInterval
toEnum :: Int -> SwapInterval
$cfromEnum :: SwapInterval -> Int
fromEnum :: SwapInterval -> Int
$cenumFrom :: SwapInterval -> [SwapInterval]
enumFrom :: SwapInterval -> [SwapInterval]
$cenumFromThen :: SwapInterval -> SwapInterval -> [SwapInterval]
enumFromThen :: SwapInterval -> SwapInterval -> [SwapInterval]
$cenumFromTo :: SwapInterval -> SwapInterval -> [SwapInterval]
enumFromTo :: SwapInterval -> SwapInterval -> [SwapInterval]
$cenumFromThenTo :: SwapInterval -> SwapInterval -> SwapInterval -> [SwapInterval]
enumFromThenTo :: SwapInterval -> SwapInterval -> SwapInterval -> [SwapInterval]
Enum, SwapInterval -> SwapInterval -> Bool
(SwapInterval -> SwapInterval -> Bool)
-> (SwapInterval -> SwapInterval -> Bool) -> Eq SwapInterval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SwapInterval -> SwapInterval -> Bool
== :: SwapInterval -> SwapInterval -> Bool
$c/= :: SwapInterval -> SwapInterval -> Bool
/= :: SwapInterval -> SwapInterval -> Bool
Eq, (forall x. SwapInterval -> Rep SwapInterval x)
-> (forall x. Rep SwapInterval x -> SwapInterval)
-> Generic SwapInterval
forall x. Rep SwapInterval x -> SwapInterval
forall x. SwapInterval -> Rep SwapInterval x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SwapInterval -> Rep SwapInterval x
from :: forall x. SwapInterval -> Rep SwapInterval x
$cto :: forall x. Rep SwapInterval x -> SwapInterval
to :: forall x. Rep SwapInterval x -> SwapInterval
Generic, Eq SwapInterval
Eq SwapInterval =>
(SwapInterval -> SwapInterval -> Ordering)
-> (SwapInterval -> SwapInterval -> Bool)
-> (SwapInterval -> SwapInterval -> Bool)
-> (SwapInterval -> SwapInterval -> Bool)
-> (SwapInterval -> SwapInterval -> Bool)
-> (SwapInterval -> SwapInterval -> SwapInterval)
-> (SwapInterval -> SwapInterval -> SwapInterval)
-> Ord SwapInterval
SwapInterval -> SwapInterval -> Bool
SwapInterval -> SwapInterval -> Ordering
SwapInterval -> SwapInterval -> SwapInterval
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
$ccompare :: SwapInterval -> SwapInterval -> Ordering
compare :: SwapInterval -> SwapInterval -> Ordering
$c< :: SwapInterval -> SwapInterval -> Bool
< :: SwapInterval -> SwapInterval -> Bool
$c<= :: SwapInterval -> SwapInterval -> Bool
<= :: SwapInterval -> SwapInterval -> Bool
$c> :: SwapInterval -> SwapInterval -> Bool
> :: SwapInterval -> SwapInterval -> Bool
$c>= :: SwapInterval -> SwapInterval -> Bool
>= :: SwapInterval -> SwapInterval -> Bool
$cmax :: SwapInterval -> SwapInterval -> SwapInterval
max :: SwapInterval -> SwapInterval -> SwapInterval
$cmin :: SwapInterval -> SwapInterval -> SwapInterval
min :: SwapInterval -> SwapInterval -> SwapInterval
Ord, ReadPrec [SwapInterval]
ReadPrec SwapInterval
Int -> ReadS SwapInterval
ReadS [SwapInterval]
(Int -> ReadS SwapInterval)
-> ReadS [SwapInterval]
-> ReadPrec SwapInterval
-> ReadPrec [SwapInterval]
-> Read SwapInterval
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SwapInterval
readsPrec :: Int -> ReadS SwapInterval
$creadList :: ReadS [SwapInterval]
readList :: ReadS [SwapInterval]
$creadPrec :: ReadPrec SwapInterval
readPrec :: ReadPrec SwapInterval
$creadListPrec :: ReadPrec [SwapInterval]
readListPrec :: ReadPrec [SwapInterval]
Read, Int -> SwapInterval -> ShowS
[SwapInterval] -> ShowS
SwapInterval -> String
(Int -> SwapInterval -> ShowS)
-> (SwapInterval -> String)
-> ([SwapInterval] -> ShowS)
-> Show SwapInterval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SwapInterval -> ShowS
showsPrec :: Int -> SwapInterval -> ShowS
$cshow :: SwapInterval -> String
show :: SwapInterval -> String
$cshowList :: [SwapInterval] -> ShowS
showList :: [SwapInterval] -> ShowS
Show, Typeable)
instance ToNumber SwapInterval CInt where
toNumber :: SwapInterval -> CInt
toNumber SwapInterval
ImmediateUpdates = CInt
0
toNumber SwapInterval
SynchronizedUpdates = CInt
1
toNumber SwapInterval
LateSwapTearing = -CInt
1
instance FromNumber SwapInterval CInt where
fromNumber :: CInt -> SwapInterval
fromNumber CInt
n' =
case CInt
n' of
CInt
0 -> SwapInterval
ImmediateUpdates
CInt
1 -> SwapInterval
SynchronizedUpdates
-1 -> SwapInterval
LateSwapTearing
CInt
_ ->
String -> SwapInterval
forall a. HasCallStack => String -> a
error (String
"Unknown SwapInterval: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ CInt -> String
forall a. Show a => a -> String
show CInt
n')
swapInterval :: StateVar SwapInterval
swapInterval :: StateVar SwapInterval
swapInterval = IO SwapInterval -> (SwapInterval -> IO ()) -> StateVar SwapInterval
forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar IO SwapInterval
glGetSwapInterval SwapInterval -> IO ()
forall {m :: Type -> Type} {a}.
(MonadIO m, ToNumber a CInt) =>
a -> m ()
glSetSwapInterval
where
glGetSwapInterval :: IO SwapInterval
glGetSwapInterval = (CInt -> SwapInterval) -> IO CInt -> IO SwapInterval
forall a b. (a -> b) -> IO a -> IO b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap CInt -> SwapInterval
forall a b. FromNumber a b => b -> a
fromNumber (IO CInt -> IO SwapInterval) -> IO CInt -> IO SwapInterval
forall a b. (a -> b) -> a -> b
$ IO CInt
forall (m :: Type -> Type). MonadIO m => m CInt
Raw.glGetSwapInterval
glSetSwapInterval :: a -> m ()
glSetSwapInterval a
i =
Text -> Text -> m CInt -> m ()
forall (m :: Type -> Type) a.
(MonadIO m, Num a, Ord a) =>
Text -> Text -> m a -> m ()
throwIfNeg_ Text
"SDL.Video.glSetSwapInterval" Text
"SDL_GL_SetSwapInterval" (m CInt -> m ()) -> m CInt -> m ()
forall a b. (a -> b) -> a -> b
$
CInt -> m CInt
forall (m :: Type -> Type). MonadIO m => CInt -> m CInt
Raw.glSetSwapInterval (a -> CInt
forall a b. ToNumber a b => a -> b
toNumber a
i)
glGetDrawableSize :: MonadIO m => Window -> m (V2 CInt)
glGetDrawableSize :: forall (m :: Type -> Type). MonadIO m => Window -> m (V2 CInt)
glGetDrawableSize (Window GLContext
w) =
IO (V2 CInt) -> m (V2 CInt)
forall a. IO a -> m a
forall (m :: Type -> Type) a. MonadIO m => IO a -> m a
liftIO (IO (V2 CInt) -> m (V2 CInt)) -> IO (V2 CInt) -> m (V2 CInt)
forall a b. (a -> b) -> a -> b
$
(Ptr CInt -> IO (V2 CInt)) -> IO (V2 CInt)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (V2 CInt)) -> IO (V2 CInt))
-> (Ptr CInt -> IO (V2 CInt)) -> IO (V2 CInt)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
wptr ->
(Ptr CInt -> IO (V2 CInt)) -> IO (V2 CInt)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr CInt -> IO (V2 CInt)) -> IO (V2 CInt))
-> (Ptr CInt -> IO (V2 CInt)) -> IO (V2 CInt)
forall a b. (a -> b) -> a -> b
$ \Ptr CInt
hptr -> do
GLContext -> Ptr CInt -> Ptr CInt -> IO ()
forall (m :: Type -> Type).
MonadIO m =>
GLContext -> Ptr CInt -> Ptr CInt -> m ()
Raw.glGetDrawableSize GLContext
w Ptr CInt
wptr Ptr CInt
hptr
CInt -> CInt -> V2 CInt
forall a. a -> a -> V2 a
V2 (CInt -> CInt -> V2 CInt) -> IO CInt -> IO (CInt -> V2 CInt)
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
wptr IO (CInt -> V2 CInt) -> IO CInt -> IO (V2 CInt)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: Type -> Type) a b.
Applicative f =>
f (a -> b) -> f a -> f b
<*> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
hptr