twirl-0.4.0.4: Simple 2D Game Engine
Safe HaskellSafe-Inferred
LanguageHaskell2010

Twirl.Inputs

Synopsis

Documentation

data InputState Source #

Instances

Instances details
Show InputState Source # 
Instance details

Defined in Twirl.Inputs

data ControllerButton #

Identifies a gamepad button.

Instances

Instances details
Data ControllerButton 
Instance details

Defined in SDL.Input.GameController

Methods

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

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

toConstr :: ControllerButton -> Constr #

dataTypeOf :: ControllerButton -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ControllerButton 
Instance details

Defined in SDL.Input.GameController

Associated Types

type Rep ControllerButton :: Type -> Type #

Read ControllerButton 
Instance details

Defined in SDL.Input.GameController

Show ControllerButton 
Instance details

Defined in SDL.Input.GameController

Eq ControllerButton 
Instance details

Defined in SDL.Input.GameController

Ord ControllerButton 
Instance details

Defined in SDL.Input.GameController

FromNumber ControllerButton Int32 
Instance details

Defined in SDL.Input.GameController

ToNumber ControllerButton Int32 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerButton 
Instance details

Defined in SDL.Input.GameController

type Rep ControllerButton = D1 ('MetaData "ControllerButton" "SDL.Input.GameController" "sdl2-2.5.3.2-FEL7WnoiYrz20iRHYD18CW" 'False) ((((C1 ('MetaCons "ControllerButtonInvalid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonA" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ControllerButtonB" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ControllerButtonY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonBack" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ControllerButtonGuide" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonStart" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ControllerButtonLeftStick" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonRightStick" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ControllerButtonLeftShoulder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonRightShoulder" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ControllerButtonDpadUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonDpadDown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ControllerButtonDpadLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ControllerButtonDpadRight" 'PrefixI 'False) (U1 :: Type -> Type)))))

data MouseButton #

Constructors

ButtonLeft 
ButtonMiddle 
ButtonRight 
ButtonX1 
ButtonX2 
ButtonExtra !Int

An unknown mouse button.

Instances

Instances details
Data MouseButton 
Instance details

Defined in SDL.Input.Mouse

Methods

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

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

toConstr :: MouseButton -> Constr #

dataTypeOf :: MouseButton -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic MouseButton 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep MouseButton :: Type -> Type #

Read MouseButton 
Instance details

Defined in SDL.Input.Mouse

Show MouseButton 
Instance details

Defined in SDL.Input.Mouse

Eq MouseButton 
Instance details

Defined in SDL.Input.Mouse

Ord MouseButton 
Instance details

Defined in SDL.Input.Mouse

FromNumber MouseButton Word8 
Instance details

Defined in SDL.Input.Mouse

ToNumber MouseButton Word8 
Instance details

Defined in SDL.Input.Mouse

Show (MouseButton -> Bool) Source # 
Instance details

Defined in Twirl.Inputs

type Rep MouseButton 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseButton = D1 ('MetaData "MouseButton" "SDL.Input.Mouse" "sdl2-2.5.3.2-FEL7WnoiYrz20iRHYD18CW" 'False) ((C1 ('MetaCons "ButtonLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ButtonMiddle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ButtonRight" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ButtonX1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ButtonX2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ButtonExtra" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int)))))

numControllers :: InputState -> Int Source #

Get number of controllers

Returns the maximum number of controllers that have been connected simultaneously. This means that if you connect four controllers and unplug one, this function will return 4.

isControllerButtonDown Source #

Arguments

:: InputState 
-> Int

Controller number to be queried

-> ControllerButton

The Controller button to be queried

-> Bool 

Query the state of controller buttons

Returns True if the queried button is down on the queried controller. Returns False if the controller is disconnected or doesn't exist (e.g. you query controller number 4 but there are only 2 controllers).

controllerAxis Source #

Arguments

:: InputState 
-> Int

Controller number

-> ControllerAxis

The queried axis

-> Double 

Query axes of controllers

For the stick axes, the returned value is between -1.0 and 1.0, where 0.0 is the neutral position. For triggers the value is between 0.0 and 1.0 where 0.0 is the neutral position. Bear in mind that usually the level of quality of controller sticks is so low that the sticks don't return exactly to the 0.0 position, so you have to ignore some values which are too close to zero.

isKeyDown :: InputState -> Keycode -> Bool Source #

Query keyboard state

isMouseDown :: InputState -> MouseButton -> Bool Source #

Query mouse button state

mousePosition :: InputState -> (Int, Int) Source #

Get mouse position on screen

Orphan instances

Show (MouseButton -> Bool) Source # 
Instance details