sdl2-2.3.0: Both high- and low-level bindings to the SDL library (version 2.0.4+).

Safe HaskellSafe
LanguageHaskell2010

SDL.Init

Synopsis

Documentation

initialize :: (Foldable f, Functor m, MonadIO m) => f InitFlag -> m () Source #

Initializes SDL and the given subsystems. Do not call any SDL functions prior to this one, unless otherwise documented that you may do so.

You may call this function again with additional subsystems to initialize.

Throws SDLException if initialization fails.

initializeAll :: (Functor m, MonadIO m) => m () Source #

Equivalent to initialize [minBound .. maxBound].

data InitFlag Source #

Instances

Bounded InitFlag Source # 
Enum InitFlag Source # 
Eq InitFlag Source # 
Data InitFlag Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InitFlag -> c InitFlag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InitFlag #

toConstr :: InitFlag -> Constr #

dataTypeOf :: InitFlag -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c InitFlag) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InitFlag) #

gmapT :: (forall b. Data b => b -> b) -> InitFlag -> InitFlag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InitFlag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InitFlag -> r #

gmapQ :: (forall d. Data d => d -> u) -> InitFlag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InitFlag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InitFlag -> m InitFlag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InitFlag -> m InitFlag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InitFlag -> m InitFlag #

Ord InitFlag Source # 
Read InitFlag Source # 
Show InitFlag Source # 
Generic InitFlag Source # 

Associated Types

type Rep InitFlag :: * -> * #

Methods

from :: InitFlag -> Rep InitFlag x #

to :: Rep InitFlag x -> InitFlag #

ToNumber InitFlag Word32 Source # 
type Rep InitFlag Source # 
type Rep InitFlag = D1 (MetaData "InitFlag" "SDL.Init" "sdl2-2.3.0-HMI0z0C1LB5Ag7s770Nokw" False) ((:+:) ((:+:) (C1 (MetaCons "InitTimer" PrefixI False) U1) ((:+:) (C1 (MetaCons "InitAudio" PrefixI False) U1) (C1 (MetaCons "InitVideo" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "InitJoystick" PrefixI False) U1) (C1 (MetaCons "InitHaptic" PrefixI False) U1)) ((:+:) (C1 (MetaCons "InitGameController" PrefixI False) U1) (C1 (MetaCons "InitEvents" PrefixI False) U1))))

quit :: MonadIO m => m () Source #

Quit and shutdown SDL, freeing any resources that may have been in use. Do not call any SDL functions after you've called this function, unless otherwise documented that you may do so.

version :: (Integral a, MonadIO m) => m (a, a, a) Source #

The major, minor, and patch versions of the SDL library linked with. Does not require initialization.