sdl2-2.4.0.1: 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 # 
Instance details

Methods

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

HasGetter (Hint v) v Source # 
Instance details

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 # 
Instance details
Enum HintPriority Source # 
Instance details
Eq HintPriority Source # 
Instance details
Data HintPriority Source # 
Instance details

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 # 
Instance details
Read HintPriority Source # 
Instance details
Show HintPriority Source # 
Instance details
Generic HintPriority Source # 
Instance details

Associated Types

type Rep HintPriority :: * -> * #

type Rep HintPriority Source # 
Instance details
type Rep HintPriority = D1 (MetaData "HintPriority" "SDL.Hint" "sdl2-2.4.0.1-JrcuLoapSXVLRmXtawChdv" 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 # 
Instance details
Enum AccelerometerJoystickOptions Source # 
Instance details
Eq AccelerometerJoystickOptions Source # 
Instance details
Data AccelerometerJoystickOptions Source # 
Instance details

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 # 
Instance details
Read AccelerometerJoystickOptions Source # 
Instance details
Show AccelerometerJoystickOptions Source # 
Instance details
Generic AccelerometerJoystickOptions Source # 
Instance details

Associated Types

type Rep AccelerometerJoystickOptions :: * -> * #

type Rep AccelerometerJoystickOptions Source # 
Instance details
type Rep AccelerometerJoystickOptions = D1 (MetaData "AccelerometerJoystickOptions" "SDL.Hint" "sdl2-2.4.0.1-JrcuLoapSXVLRmXtawChdv" False) (C1 (MetaCons "AccelerometerNotJoystick" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "AccelerometerIsJoystick" PrefixI False) (U1 :: * -> *))

HintFramebufferAcceleration

data FramebufferAccelerationOptions Source #

A hint that specifies how 3D acceleration is used to accelerate the SDL screen surface. By default SDL tries to make a best guess whether to use acceleration or not on each platform.

Constructors

Disable3D

Disable 3D acceleration

Enable3DDefault

Enable 3D acceleration, using the default renderer

Enable3DDirect3D

Enable 3D acceleration using Direct3D

Enable3DOpenGL

Enable 3D acceleration using OpenGL

Enable3DOpenGLES

Enable 3D acceleration using OpenGLES

Enable3DOpenGLES2

Enable 3D acceleration using OpenGLES2

Enable3DSoftware

Enable 3D acceleration using software rendering

Instances
Bounded FramebufferAccelerationOptions Source # 
Instance details
Enum FramebufferAccelerationOptions Source # 
Instance details
Eq FramebufferAccelerationOptions Source # 
Instance details
Data FramebufferAccelerationOptions Source # 
Instance details

Methods

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

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

toConstr :: FramebufferAccelerationOptions -> Constr #

dataTypeOf :: FramebufferAccelerationOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FramebufferAccelerationOptions Source # 
Instance details
Read FramebufferAccelerationOptions Source # 
Instance details
Show FramebufferAccelerationOptions Source # 
Instance details
Generic FramebufferAccelerationOptions Source # 
Instance details

Associated Types

type Rep FramebufferAccelerationOptions :: * -> * #

type Rep FramebufferAccelerationOptions Source # 
Instance details
type Rep FramebufferAccelerationOptions = D1 (MetaData "FramebufferAccelerationOptions" "SDL.Hint" "sdl2-2.4.0.1-JrcuLoapSXVLRmXtawChdv" False) ((C1 (MetaCons "Disable3D" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Enable3DDefault" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Enable3DDirect3D" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "Enable3DOpenGL" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Enable3DOpenGLES" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Enable3DOpenGLES2" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Enable3DSoftware" PrefixI False) (U1 :: * -> *))))

HintMacCTRLClick

data MacCTRLClickOptions Source #

A hint that specifies whether ctrl+click should generate a right-click event on Mac. By default holding ctrl while left clicking will not generate a right click event when on Mac.

Constructors

NoRightClick

Disable emulating right click

EmulateRightClick

Enable emulating right click

Instances
Bounded MacCTRLClickOptions Source # 
Instance details
Enum MacCTRLClickOptions Source # 
Instance details
Eq MacCTRLClickOptions Source # 
Instance details
Data MacCTRLClickOptions Source # 
Instance details

Methods

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

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

toConstr :: MacCTRLClickOptions -> Constr #

dataTypeOf :: MacCTRLClickOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MacCTRLClickOptions Source # 
Instance details
Read MacCTRLClickOptions Source # 
Instance details
Show MacCTRLClickOptions Source # 
Instance details
Generic MacCTRLClickOptions Source # 
Instance details

Associated Types

type Rep MacCTRLClickOptions :: * -> * #

type Rep MacCTRLClickOptions Source # 
Instance details
type Rep MacCTRLClickOptions = D1 (MetaData "MacCTRLClickOptions" "SDL.Hint" "sdl2-2.4.0.1-JrcuLoapSXVLRmXtawChdv" False) (C1 (MetaCons "NoRightClick" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "EmulateRightClick" PrefixI False) (U1 :: * -> *))

HintMouseRelativeModeWarp

data MouseModeWarpOptions Source #

A hint that specifies whether relative mouse mode is implemented using mouse warping. By default SDL will use raw input for relative mouse mode

Constructors

MouseRawInput

Relative mouse mode uses the raw input

MouseWarping

Relative mouse mode uses mouse warping

Instances
Bounded MouseModeWarpOptions Source # 
Instance details
Enum MouseModeWarpOptions Source # 
Instance details
Eq MouseModeWarpOptions Source # 
Instance details
Data MouseModeWarpOptions Source # 
Instance details

Methods

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

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

toConstr :: MouseModeWarpOptions -> Constr #

dataTypeOf :: MouseModeWarpOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MouseModeWarpOptions Source # 
Instance details
Read MouseModeWarpOptions Source # 
Instance details
Show MouseModeWarpOptions Source # 
Instance details
Generic MouseModeWarpOptions Source # 
Instance details

Associated Types

type Rep MouseModeWarpOptions :: * -> * #

type Rep MouseModeWarpOptions Source # 
Instance details
type Rep MouseModeWarpOptions = D1 (MetaData "MouseModeWarpOptions" "SDL.Hint" "sdl2-2.4.0.1-JrcuLoapSXVLRmXtawChdv" False) (C1 (MetaCons "MouseRawInput" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MouseWarping" PrefixI False) (U1 :: * -> *))

HintRenderDriver

data RenderDrivers Source #

A hint that specifies which render driver to use. By default the first one in the list that is available on the current platform is chosen.

Instances
Bounded RenderDrivers Source # 
Instance details
Enum RenderDrivers Source # 
Instance details
Eq RenderDrivers Source # 
Instance details
Data RenderDrivers Source # 
Instance details

Methods

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

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

toConstr :: RenderDrivers -> Constr #

dataTypeOf :: RenderDrivers -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RenderDrivers Source # 
Instance details
Read RenderDrivers Source # 
Instance details
Show RenderDrivers Source # 
Instance details
Generic RenderDrivers Source # 
Instance details

Associated Types

type Rep RenderDrivers :: * -> * #

type Rep RenderDrivers Source # 
Instance details
type Rep RenderDrivers = D1 (MetaData "RenderDrivers" "SDL.Hint" "sdl2-2.4.0.1-JrcuLoapSXVLRmXtawChdv" False) ((C1 (MetaCons "Direct3D" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "OpenGL" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "OpenGLES" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "OpenGLES2" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Software" PrefixI False) (U1 :: * -> *))))

HintRenderOpenGLShaders

data RenderOpenGLShaderOptions Source #

A hint that specifies whether the OpenGL render driver uses shaders. By default shaders are used if OpenGL supports them.

Constructors

DisableShaders

Disable shaders

EnableShaders

Enable shaders, if they are available

Instances
Bounded RenderOpenGLShaderOptions Source # 
Instance details
Enum RenderOpenGLShaderOptions Source # 
Instance details
Eq RenderOpenGLShaderOptions Source # 
Instance details
Data RenderOpenGLShaderOptions Source # 
Instance details

Methods

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

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

toConstr :: RenderOpenGLShaderOptions -> Constr #

dataTypeOf :: RenderOpenGLShaderOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RenderOpenGLShaderOptions Source # 
Instance details
Read RenderOpenGLShaderOptions Source # 
Instance details
Show RenderOpenGLShaderOptions Source # 
Instance details
Generic RenderOpenGLShaderOptions Source # 
Instance details

Associated Types

type Rep RenderOpenGLShaderOptions :: * -> * #

type Rep RenderOpenGLShaderOptions Source # 
Instance details
type Rep RenderOpenGLShaderOptions = D1 (MetaData "RenderOpenGLShaderOptions" "SDL.Hint" "sdl2-2.4.0.1-JrcuLoapSXVLRmXtawChdv" False) (C1 (MetaCons "DisableShaders" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "EnableShaders" PrefixI False) (U1 :: * -> *))

HintRenderScaleQuality

data RenderScaleQuality Source #

A hint that specifies scaling quality. By default nearest pixel sampling is used.

Constructors

ScaleNearest

Nearest pixel sampling

ScaleLinear

linear filtering (supported by OpenGL and Direct3D)

ScaleBest

Anisotropic filtering (supported by Direct3D)

Instances
Bounded RenderScaleQuality Source # 
Instance details
Enum RenderScaleQuality Source # 
Instance details
Eq RenderScaleQuality Source # 
Instance details
Data RenderScaleQuality Source # 
Instance details

Methods

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

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

toConstr :: RenderScaleQuality -> Constr #

dataTypeOf :: RenderScaleQuality -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RenderScaleQuality Source # 
Instance details
Read RenderScaleQuality Source # 
Instance details
Show RenderScaleQuality Source # 
Instance details
Generic RenderScaleQuality Source # 
Instance details

Associated Types

type Rep RenderScaleQuality :: * -> * #

type Rep RenderScaleQuality Source # 
Instance details
type Rep RenderScaleQuality = D1 (MetaData "RenderScaleQuality" "SDL.Hint" "sdl2-2.4.0.1-JrcuLoapSXVLRmXtawChdv" False) (C1 (MetaCons "ScaleNearest" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ScaleLinear" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ScaleBest" PrefixI False) (U1 :: * -> *)))

HintRenderVSync

data RenderVSyncOptions Source #

A hint that specifies whether sync to vertical refresh is enabled or disabled to avoid tearing. By default SDL uses the flag passed into calls to create renderers.

Constructors

DisableVSync 
EnableVSync 
Instances
Bounded RenderVSyncOptions Source # 
Instance details
Enum RenderVSyncOptions Source # 
Instance details
Eq RenderVSyncOptions Source # 
Instance details
Data RenderVSyncOptions Source # 
Instance details

Methods

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

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

toConstr :: RenderVSyncOptions -> Constr #

dataTypeOf :: RenderVSyncOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RenderVSyncOptions Source # 
Instance details
Read RenderVSyncOptions Source # 
Instance details
Show RenderVSyncOptions Source # 
Instance details
Generic RenderVSyncOptions Source # 
Instance details

Associated Types

type Rep RenderVSyncOptions :: * -> * #

type Rep RenderVSyncOptions Source # 
Instance details
type Rep RenderVSyncOptions = D1 (MetaData "RenderVSyncOptions" "SDL.Hint" "sdl2-2.4.0.1-JrcuLoapSXVLRmXtawChdv" False) (C1 (MetaCons "DisableVSync" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "EnableVSync" PrefixI False) (U1 :: * -> *))

HintVideoWinD3DCompiler

data VideoWinD3DCompilerOptions Source #

A hint that specifies which shader compiler to preload when using the Chrome ANGLE binaries. By default d3dcompiler_46.dll will be used.

Constructors

D3DVistaOrLater

Use d3dcompiler_46.dll, best for Vista or later

D3DXPSupport

Use d3dcompiler_43.dll for XP support

D3DNone

Do not load any library, useful if you compiled ANGLE from source and included the compiler in your binaries

Instances
Bounded VideoWinD3DCompilerOptions Source # 
Instance details
Enum VideoWinD3DCompilerOptions Source # 
Instance details
Eq VideoWinD3DCompilerOptions Source # 
Instance details
Data VideoWinD3DCompilerOptions Source # 
Instance details

Methods

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

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

toConstr :: VideoWinD3DCompilerOptions -> Constr #

dataTypeOf :: VideoWinD3DCompilerOptions -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord VideoWinD3DCompilerOptions Source # 
Instance details
Read VideoWinD3DCompilerOptions Source # 
Instance details
Show VideoWinD3DCompilerOptions Source # 
Instance details
Generic VideoWinD3DCompilerOptions Source # 
Instance details

Associated Types

type Rep VideoWinD3DCompilerOptions :: * -> * #

type Rep VideoWinD3DCompilerOptions Source # 
Instance details
type Rep VideoWinD3DCompilerOptions = D1 (MetaData "VideoWinD3DCompilerOptions" "SDL.Hint" "sdl2-2.4.0.1-JrcuLoapSXVLRmXtawChdv" False) (C1 (MetaCons "D3DVistaOrLater" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "D3DXPSupport" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "D3DNone" PrefixI False) (U1 :: * -> *)))