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

Safe HaskellSafe
LanguageHaskell2010

SDL.Hint

Contents

Synopsis

Getting and setting hints

data Hint :: * -> * where Source #

The Hint type exports a well-typed interface to SDL's concept of hints. This type has instances for both HasGetter and HasSetter, allowing you to get and set hints. Note that the HasSetter interface is fairly relaxed - if a hint cannot be set, the failure will be silently discarded. For more feedback and control when setting hints, see setHintWithPriority.

Instances

HasSetter (Hint v) v Source # 

Methods

($=) :: MonadIO m => Hint v -> v -> m () #

HasGetter (Hint v) v Source # 

Methods

get :: MonadIO m => Hint v -> m v #

setHintWithPriority :: MonadIO m => HintPriority -> Hint v -> v -> m Bool Source #

Set the value of a hint, applying priority rules for when there is a conflict. Ordinarily, a hint will not be set if there is an existing override hint or environment variable that takes precedence.

data HintPriority Source #

How to deal with setting hints when an existing override or environment variable is present.

Constructors

DefaultPriority

Low priority, used for default values

NormalPriority

Medium priority

OverridePriority

High priority

Instances

Bounded HintPriority Source # 
Enum HintPriority Source # 
Eq HintPriority Source # 
Data HintPriority Source # 

Methods

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

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

toConstr :: HintPriority -> Constr #

dataTypeOf :: HintPriority -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HintPriority Source # 
Read HintPriority Source # 
Show HintPriority Source # 
Generic HintPriority Source # 

Associated Types

type Rep HintPriority :: * -> * #

type Rep HintPriority Source # 
type Rep HintPriority = D1 * (MetaData "HintPriority" "SDL.Hint" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) ((:+:) * (C1 * (MetaCons "DefaultPriority" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NormalPriority" PrefixI False) (U1 *)) (C1 * (MetaCons "OverridePriority" PrefixI False) (U1 *))))

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

Hint Information

HintAccelerometerAsJoystick

data AccelerometerJoystickOptions Source #

A hint that specifies whether the Android/iOS built-in accelerometer should be listed as a joystick device, rather than listing actual joysticks only. By default SDL will list real joysticks along with the accelerometer as if it were a 3 axis joystick.

Constructors

AccelerometerNotJoystick

List only real joysticks and accept input from them

AccelerometerIsJoystick

List real joysticks along with the accelerometer as if it were a 3 axis joystick (the default)

Instances

Bounded AccelerometerJoystickOptions Source # 
Enum AccelerometerJoystickOptions Source # 
Eq AccelerometerJoystickOptions Source # 
Data AccelerometerJoystickOptions Source # 

Methods

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

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

toConstr :: AccelerometerJoystickOptions -> Constr #

dataTypeOf :: AccelerometerJoystickOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AccelerometerJoystickOptions Source # 
Read AccelerometerJoystickOptions Source # 
Show AccelerometerJoystickOptions Source # 
Generic AccelerometerJoystickOptions Source # 
type Rep AccelerometerJoystickOptions Source # 
type Re