glfw-group-0.1.0.0: GLFW package with window groups destroyed together
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.UI.GlfwG.Gamepad

Synopsis

Documentation

data GamepadButton #

The different types of buttons we can find on a Gamepad.

Instances

Instances details
Data GamepadButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: GamepadButton -> Constr #

dataTypeOf :: GamepadButton -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded GamepadButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum GamepadButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic GamepadButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep GamepadButton :: Type -> Type #

Read GamepadButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Show GamepadButton 
Instance details

Defined in Graphics.UI.GLFW.Types

NFData GamepadButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: GamepadButton -> () #

Eq GamepadButton 
Instance details

Defined in Graphics.UI.GLFW.Types

Ord GamepadButton 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadButton 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadButton = D1 ('MetaData "GamepadButton" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.1-CbbIOqvtyyzkbPgJI2V5g" 'False) ((((C1 ('MetaCons "GamepadButton'A" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'B" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GamepadButton'X" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'Y" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GamepadButton'LeftBumper" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'RightBumper" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GamepadButton'Back" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GamepadButton'Start" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'Guide" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "GamepadButton'LeftThumb" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'RightThumb" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GamepadButton'DpadUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GamepadButton'DpadRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'DpadDown" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "GamepadButton'DpadLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'Cross" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GamepadButton'Circle" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GamepadButton'Square" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButton'Triangle" 'PrefixI 'False) (U1 :: Type -> Type))))))

data GamepadAxis #

The different axes along which we can measure continuous input on a Gamepad

Instances

Instances details
Data GamepadAxis 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: GamepadAxis -> Constr #

dataTypeOf :: GamepadAxis -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded GamepadAxis 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum GamepadAxis 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic GamepadAxis 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep GamepadAxis :: Type -> Type #

Read GamepadAxis 
Instance details

Defined in Graphics.UI.GLFW.Types

Show GamepadAxis 
Instance details

Defined in Graphics.UI.GLFW.Types

NFData GamepadAxis 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: GamepadAxis -> () #

Eq GamepadAxis 
Instance details

Defined in Graphics.UI.GLFW.Types

Ord GamepadAxis 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadAxis 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadAxis = D1 ('MetaData "GamepadAxis" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.1-CbbIOqvtyyzkbPgJI2V5g" 'False) ((C1 ('MetaCons "GamepadAxis'LeftX" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GamepadAxis'LeftY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadAxis'RightX" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "GamepadAxis'RightY" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GamepadAxis'LeftTrigger" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadAxis'RightTrigger" 'PrefixI 'False) (U1 :: Type -> Type))))

data GamepadButtonState #

The states in which the gamepad buttons are found

Instances

Instances details
Data GamepadButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

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

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

toConstr :: GamepadButtonState -> Constr #

dataTypeOf :: GamepadButtonState -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded GamepadButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Enum GamepadButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Generic GamepadButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep GamepadButtonState :: Type -> Type #

Read GamepadButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Show GamepadButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

NFData GamepadButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: GamepadButtonState -> () #

Eq GamepadButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

Ord GamepadButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadButtonState 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadButtonState = D1 ('MetaData "GamepadButtonState" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.1-CbbIOqvtyyzkbPgJI2V5g" 'False) (C1 ('MetaCons "GamepadButtonState'Pressed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GamepadButtonState'Released" 'PrefixI 'False) (U1 :: Type -> Type))

data GamepadState #

This describes the input state of a gamepad

Constructors

GamepadState 

Fields

Instances

Instances details
Generic GamepadState 
Instance details

Defined in Graphics.UI.GLFW.Types

Associated Types

type Rep GamepadState :: Type -> Type #

NFData GamepadState 
Instance details

Defined in Graphics.UI.GLFW.Types

Methods

rnf :: GamepadState -> () #

Eq GamepadState 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadState 
Instance details

Defined in Graphics.UI.GLFW.Types

type Rep GamepadState = D1 ('MetaData "GamepadState" "Graphics.UI.GLFW.Types" "GLFW-b-3.3.9.1-CbbIOqvtyyzkbPgJI2V5g" 'False) (C1 ('MetaCons "GamepadState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getButtonState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GamepadButton -> GamepadButtonState)) :*: S1 ('MetaSel ('Just "getAxisState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GamepadAxis -> Float))))

joystickIsGamepad :: Joystick -> IO Bool #

This function returns whether the specified joystick is both present and has a gamepad mapping. See glfwJoystickIsGamepad

getGamepadName :: Joystick -> IO (Maybe String) #

This function returns the human-readable name of the gamepad from the gamepad mapping assigned to the specified joystick. See glfwGetGamepadName

getGamepadState :: Joystick -> IO (Maybe GamepadState) #

This function retrives the state of the specified joystick remapped to an Xbox-like gamepad. See glfwGetGamepadState

updateGamepadMappings :: String -> IO Bool #

Adds the specified SDL_GameControllerDB gamepad mappings. See glfwUpdateGamepadMappings