Copyright | (c) Michael Szvetits 2021 |
---|---|
License | BSD3 (see the file LICENSE) |
Maintainer | typedbyte@qualified.name |
Stability | stable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Types and functions for connecting to Nintendo Switch controllers, reading input (e.g., buttons, sensors) and sending commands (e.g., rumble).
Synopsis
- data Console
- init :: IO Console
- exit :: Console -> IO ()
- withConsole :: (Console -> IO a) -> IO a
- data ControllerType
- data ControllerInfo (t :: ControllerType)
- data Controller (t :: ControllerType)
- getControllerInfos :: forall t. IsController t => Console -> IO [ControllerInfo t]
- connect :: forall t. HasCalibration t => ControllerInfo t -> IO (Controller t)
- disconnect :: Controller t -> IO ()
- withController :: HasCalibration t => ControllerInfo t -> (Controller t -> IO a) -> IO a
- data InputMode
- setInputMode :: HasInputMode t => InputMode -> Controller t -> IO ()
- setInertialMeasurement :: Bool -> Controller t -> IO ()
- getInput :: HasInput t => Controller t -> IO Input
- getTimeoutInput :: HasInput t => Int -> Controller t -> IO (Maybe Input)
- type Input = ControllerInput Float Float
- data ControllerInput s e = Input {
- btnL :: Bool
- btnZL :: Bool
- btnMinus :: Bool
- btnLeftStick :: Bool
- btnUp :: Bool
- btnLeft :: Bool
- btnRight :: Bool
- btnDown :: Bool
- btnCapture :: Bool
- btnLeftSL :: Bool
- btnLeftSR :: Bool
- btnR :: Bool
- btnZR :: Bool
- btnPlus :: Bool
- btnX :: Bool
- btnY :: Bool
- btnA :: Bool
- btnB :: Bool
- btnRightStick :: Bool
- btnHome :: Bool
- btnRightSL :: Bool
- btnRightSR :: Bool
- stickLeft :: StickDirection s
- stickRight :: StickDirection s
- extras :: ExtraInput e
- battery :: Maybe BatteryInfo
- data StickDirection a
- data Direction
- data BatteryInfo = BatteryInfo {}
- data BatteryStatus
- data ExtraInput a
- = CommandReply ReplyData
- | Inertial (Accelerometer a) (Gyroscope a)
- | Unavailable
- type Accelerometer a = ((a, a, a), (a, a, a), (a, a, a))
- type Gyroscope a = ((a, a, a), (a, a, a), (a, a, a))
- data ReplyData
- = SetHomeLight (Acknowledgement ())
- | SetInertialMeasurement (Acknowledgement ())
- | SetInputMode (Acknowledgement ())
- | SetPlayerLights (Acknowledgement ())
- | SetVibration (Acknowledgement ())
- data Acknowledgement a
- noInput :: ControllerInput s e
- coordinates :: StickDirection Float -> (Float, Float)
- mergeInputs :: Input -> Input -> Input
- withCommandReply :: Int -> Int -> Controller t -> (ReplyData -> Maybe a) -> IO a
- setHomeLight :: HasHomeLight t => HomeLightConfig -> Controller t -> IO ()
- data HomeLightConfig
- type CycleConfig = (Intensity, FadeFactor, LightFactor)
- type BaseDuration = Word8
- type Intensity = Word8
- type FadeFactor = Word8
- type LightFactor = Word8
- data RepeatBehaviour
- endlessPulse :: HomeLightConfig
- setPlayerLights :: HasPlayerLights t => PlayerLightsConfig -> Controller t -> IO ()
- data PlayerLightsConfig = PlayerLightsConfig {}
- data LightMode
- noPlayerLights :: PlayerLightsConfig
- playerOne :: PlayerLightsConfig
- playerTwo :: PlayerLightsConfig
- playerThree :: PlayerLightsConfig
- playerFour :: PlayerLightsConfig
- flashAll :: PlayerLightsConfig
- setVibration :: Bool -> Controller t -> IO ()
- setLeftRumble :: HasLeftRumble t => RumbleConfig -> Controller t -> IO ()
- setRightRumble :: HasRightRumble t => RumbleConfig -> Controller t -> IO ()
- setRumble :: (HasLeftRumble t, HasRightRumble t) => RumbleConfig -> RumbleConfig -> Controller t -> IO ()
- data RumbleConfig = RumbleConfig {}
- normalRumble :: RumbleConfig
- noRumble :: RumbleConfig
- data ConnectionException
- data InputException
- data OutputException = WriteException
- class IsController (t :: ControllerType)
- class HasCalibration (t :: ControllerType)
- class HasInputMode t
- class HasInput t
- class HasHomeLight t
- class HasPlayerLights t
- class HasLeftRumble t
- class HasRightRumble t
Connection
Switch Console
A handle which represents a virtual Nintendo Switch console. The handle is used to detect controllers and manage their connections.
Initializes a Nintendo Switch console handle. In other words, it lets us pretend to be Nintendo Switch console in order to detect controllers and manage their connections. You must call this first before doing anything else.
exit :: Console -> IO () Source #
Destroys a virtual Nintendo Switch handle. You must call this when you are finished talking to the controllers.
Switch Controllers
data ControllerType Source #
The types of Nintendo Switch controllers that are currently supported by this library.
Note that this type is mostly used on the type level (using DataKinds
)
in order to prevent programming mistakes at compile-time (e.g., to prevent
sending a rumble command to a controller which has no rumble feature).
Chances are very high that you don't need this type on the value level, but
rather on the type level, for example via TypeApplications
(see getControllerInfos
).
Instances
data ControllerInfo (t :: ControllerType) Source #
A handle which represents an unconnected Nintendo Switch controller.
Instances
Show (ControllerInfo t) Source # | |
Defined in Device.Nintendo.Switch.Connection showsPrec :: Int -> ControllerInfo t -> ShowS # show :: ControllerInfo t -> String # showList :: [ControllerInfo t] -> ShowS # |
data Controller (t :: ControllerType) Source #
A handle which represents a connected Nintendo Switch controller.
getControllerInfos :: forall t. IsController t => Console -> IO [ControllerInfo t] Source #
Detects all Nintendo Switch controllers of a specific ControllerType
,
usually connected via Bluetooth.
You may want to use this function with TypeApplications
if the controller
type cannot be inferred, like:
getControllerInfos
@'LeftJoyCon
console
:: forall t. HasCalibration t | |
=> ControllerInfo t | The detected Nintendo Switch controller. |
-> IO (Controller t) | The connected Nintendo Switch controller. |
Connects to a detected Nintendo Switch controller.
Can throw a ConnectionException
if something is very wrong with your
internal controller memory (i.e., if you have tampered with it).
disconnect :: Controller t -> IO () Source #
Disconnects a Nintendo Switch controller. You must not use the controller handle after disconnecting.
withController :: HasCalibration t => ControllerInfo t -> (Controller t -> IO a) -> IO a Source #
A convenient wrapper around connect
and disconnect
.
Controller Input
Input Mode
The input mode of a Nintendo Switch controller determines the frequency and
amount of information received by getInput
.
Standard | The default input mode. In this mode, controllers push |
Simple | A simple input mode where a controller only pushes its |
setInputMode :: HasInputMode t => InputMode -> Controller t -> IO () Source #
Sets the input mode of a Nintendo Switch controller.
Note: After sending a command like this to a controller, it is highly advised
to check its corresponding CommandReply
(SetInputMode
, to be exact) or at least call
getInput
once before sending another command to
that controller. The function withCommandReply
is a
convenient way to wait for a specific command reply from the controller.
setInertialMeasurement :: Bool -> Controller t -> IO () Source #
Enables (True
) or disables (False
) the inertial measurement unit (i.e.,
accelerometer, gyroscope) of a Nintendo Switch controller. Inertial measurement
is disabled by default.
Note: After sending a command like this to a controller, it is highly advised
to check its corresponding CommandReply
(SetInertialMeasurement
, to be exact) or at least call
getInput
once before sending another command to
that controller. The function withCommandReply
is a
convenient way to wait for a specific command reply from the controller.
Getting Input
getInput :: HasInput t => Controller t -> IO Input Source #
Reads input from a Nintendo Switch controller. Blocks until controller input is available.
:: HasInput t | |
=> Int | The time interval in milliseconds. |
-> Controller t | The controller to read the input from. |
-> IO (Maybe Input) | Returns |
Reads input from a Nintendo Switch controller. Blocks until controller input is available or a given time interval elapses.
Input Types
type Input = ControllerInput Float Float Source #
The input provided by a Nintendo Switch controller.
data ControllerInput s e Source #
The input provided by a Nintendo Switch controller, where s
is the
numeric type of the analog stick direction and e
is the numeric type
of the sensor readings (i.e., accelerometer and gyroscope).
Input | |
|
Instances
(Eq s, Eq e) => Eq (ControllerInput s e) Source # | |
Defined in Device.Nintendo.Switch.Input (==) :: ControllerInput s e -> ControllerInput s e -> Bool # (/=) :: ControllerInput s e -> ControllerInput s e -> Bool # | |
(Read s, Read e) => Read (ControllerInput s e) Source # | |
Defined in Device.Nintendo.Switch.Input readsPrec :: Int -> ReadS (ControllerInput s e) # readList :: ReadS [ControllerInput s e] # readPrec :: ReadPrec (ControllerInput s e) # readListPrec :: ReadPrec [ControllerInput s e] # | |
(Show s, Show e) => Show (ControllerInput s e) Source # | |
Defined in Device.Nintendo.Switch.Input showsPrec :: Int -> ControllerInput s e -> ShowS # show :: ControllerInput s e -> String # showList :: [ControllerInput s e] -> ShowS # |
data StickDirection a Source #
The direction of the left (stickLeft
) and right (stickRight
) analog sticks.
Discrete Direction | In |
Analog a a | In |
Instances
Functor StickDirection Source # | |
Defined in Device.Nintendo.Switch.Input fmap :: (a -> b) -> StickDirection a -> StickDirection b # (<$) :: a -> StickDirection b -> StickDirection a # | |
Eq a => Eq (StickDirection a) Source # | |
Defined in Device.Nintendo.Switch.Input (==) :: StickDirection a -> StickDirection a -> Bool # (/=) :: StickDirection a -> StickDirection a -> Bool # | |
Read a => Read (StickDirection a) Source # | |
Defined in Device.Nintendo.Switch.Input readsPrec :: Int -> ReadS (StickDirection a) # readList :: ReadS [StickDirection a] # readPrec :: ReadPrec (StickDirection a) # readListPrec :: ReadPrec [StickDirection a] # | |
Show a => Show (StickDirection a) Source # | |
Defined in Device.Nintendo.Switch.Input showsPrec :: Int -> StickDirection a -> ShowS # show :: StickDirection a -> String # showList :: [StickDirection a] -> ShowS # |
The nine possible discrete positions of the analog stick in
Simple
input mode.
data BatteryInfo Source #
Information about the battery of a Nintendo Switch controller. It is only
returned by getInput
(see battery
) if the controller sends a command reply
or the input mode of the controller is Standard
.
Instances
Eq BatteryInfo Source # | |
Defined in Device.Nintendo.Switch.Input (==) :: BatteryInfo -> BatteryInfo -> Bool # (/=) :: BatteryInfo -> BatteryInfo -> Bool # | |
Read BatteryInfo Source # | |
Defined in Device.Nintendo.Switch.Input readsPrec :: Int -> ReadS BatteryInfo # readList :: ReadS [BatteryInfo] # readPrec :: ReadPrec BatteryInfo # readListPrec :: ReadPrec [BatteryInfo] # | |
Show BatteryInfo Source # | |
Defined in Device.Nintendo.Switch.Input showsPrec :: Int -> BatteryInfo -> ShowS # show :: BatteryInfo -> String # showList :: [BatteryInfo] -> ShowS # |
data BatteryStatus Source #
The battery status of a Nintendo Switch controller.
Instances
Eq BatteryStatus Source # | |
Defined in Device.Nintendo.Switch.Input (==) :: BatteryStatus -> BatteryStatus -> Bool # (/=) :: BatteryStatus -> BatteryStatus -> Bool # | |
Ord BatteryStatus Source # | |
Defined in Device.Nintendo.Switch.Input compare :: BatteryStatus -> BatteryStatus -> Ordering # (<) :: BatteryStatus -> BatteryStatus -> Bool # (<=) :: BatteryStatus -> BatteryStatus -> Bool # (>) :: BatteryStatus -> BatteryStatus -> Bool # (>=) :: BatteryStatus -> BatteryStatus -> Bool # max :: BatteryStatus -> BatteryStatus -> BatteryStatus # min :: BatteryStatus -> BatteryStatus -> BatteryStatus # | |
Read BatteryStatus Source # | |
Defined in Device.Nintendo.Switch.Input readsPrec :: Int -> ReadS BatteryStatus # readList :: ReadS [BatteryStatus] # | |
Show BatteryStatus Source # | |
Defined in Device.Nintendo.Switch.Input showsPrec :: Int -> BatteryStatus -> ShowS # show :: BatteryStatus -> String # showList :: [BatteryStatus] -> ShowS # |
data ExtraInput a Source #
Depending on the InputMode
, Input
can contain
additional information: Replies to commands (e.g., an acknowledgement when
sending a rumble command) and inertial sensor data (i.e., accelerometer and
gyroscope).
CommandReply ReplyData | After sending commands to the controller (e.g., setting the
|
Inertial (Accelerometer a) (Gyroscope a) | A controller provides inertial sensor data (i.e., accelerometer and
gyroscope) only if it is in Regarding the x/y/z coordinate system, consider the left Joy-Con lying flat on a table, the analog stick pointing up. The x-axis then points towards the Z/ZL shoulder buttons (or alternatively: to where the up arrow button is pointing), the y-axis points to the opposite side of the SL/SR buttons (or alternatively: to where the left arrow button is pointing), and the z-axis points up in the air. The coordinate system is the same for all controller types. |
Unavailable | Indicates that there is no additional input data. |
Instances
Functor ExtraInput Source # | |
Defined in Device.Nintendo.Switch.Input fmap :: (a -> b) -> ExtraInput a -> ExtraInput b # (<$) :: a -> ExtraInput b -> ExtraInput a # | |
Eq a => Eq (ExtraInput a) Source # | |
Defined in Device.Nintendo.Switch.Input (==) :: ExtraInput a -> ExtraInput a -> Bool # (/=) :: ExtraInput a -> ExtraInput a -> Bool # | |
Read a => Read (ExtraInput a) Source # | |
Defined in Device.Nintendo.Switch.Input readsPrec :: Int -> ReadS (ExtraInput a) # readList :: ReadS [ExtraInput a] # readPrec :: ReadPrec (ExtraInput a) # readListPrec :: ReadPrec [ExtraInput a] # | |
Show a => Show (ExtraInput a) Source # | |
Defined in Device.Nintendo.Switch.Input showsPrec :: Int -> ExtraInput a -> ShowS # show :: ExtraInput a -> String # showList :: [ExtraInput a] -> ShowS # |
type Accelerometer a = ((a, a, a), (a, a, a), (a, a, a)) Source #
Accelerometer data consists of three measurements recorded in 15ms (i.e., the precision is 5ms). Each measurement is an x/y/z triple measured in Gs.
type Gyroscope a = ((a, a, a), (a, a, a), (a, a, a)) Source #
Gyroscope data consists of three measurements recorded in 15ms (i.e., the precision is 5ms). Each measurement is an x/y/z triple measured in radians per second.
Data type that combines the command type and its corresponding acknowledgement.
SetHomeLight (Acknowledgement ()) | |
SetInertialMeasurement (Acknowledgement ()) | |
SetInputMode (Acknowledgement ()) | |
SetPlayerLights (Acknowledgement ()) | |
SetVibration (Acknowledgement ()) |
data Acknowledgement a Source #
Whenever a command is sent to a controller (e.g., setting the
InputMode
), the controller replies with an
Acknowledgement
.
ACK a | The command was executed successfully, possibly holding some response data (e.g., if the command was a query of the internal SPI flash memory). |
NACK | The command was not executed successfully. |
Instances
Functor Acknowledgement Source # | |
Defined in Device.Nintendo.Switch.Input fmap :: (a -> b) -> Acknowledgement a -> Acknowledgement b # (<$) :: a -> Acknowledgement b -> Acknowledgement a # | |
Eq a => Eq (Acknowledgement a) Source # | |
Defined in Device.Nintendo.Switch.Input (==) :: Acknowledgement a -> Acknowledgement a -> Bool # (/=) :: Acknowledgement a -> Acknowledgement a -> Bool # | |
Read a => Read (Acknowledgement a) Source # | |
Defined in Device.Nintendo.Switch.Input readsPrec :: Int -> ReadS (Acknowledgement a) # readList :: ReadS [Acknowledgement a] # readPrec :: ReadPrec (Acknowledgement a) # readListPrec :: ReadPrec [Acknowledgement a] # | |
Show a => Show (Acknowledgement a) Source # | |
Defined in Device.Nintendo.Switch.Input showsPrec :: Int -> Acknowledgement a -> ShowS # show :: Acknowledgement a -> String # showList :: [Acknowledgement a] -> ShowS # |
Convenience
noInput :: ControllerInput s e Source #
coordinates :: StickDirection Float -> (Float, Float) Source #
Merges the inputs of two Nintendo Switch controllers. The resulting input contains the left button states and left analog stick direction from one input, and the right button states and right analog stick direction from the other input. This can be used to unify the inputs of two controllers that belong together (e.g., a pair of left and right Joy-Cons).
Note that the extras
and battery
information of the original inputs are
discarded in the merged input (they are set to Unavailable
and Nothing
,
respectively).
:: Int | The maximum count of inputs that should be consumed. |
-> Int | The timeout per input read (see |
-> Controller t | The controller to read the input from. |
-> (ReplyData -> Maybe a) | The function which checks the command reply. It must return |
-> IO a | The data extracted from the expected command reply. |
Consumes inputs from a Nintendo Switch controller until a specific command
reply is encountered. Throws a NoReplyException
if the expected command
reply is not encountered within a specified count of inputs.
This function can be used to make sure that the controller is in an expected
state after sending commands (e.g., to wait for an Acknowledgement
after
switching its InputMode
).
Controller Output
Home Light
setHomeLight :: HasHomeLight t => HomeLightConfig -> Controller t -> IO () Source #
Sets the home light (i.e., the LED ring around the home button) of a Nintendo Switch controller.
Note: After sending a command like this to a controller, it is highly advised
to check its corresponding CommandReply
(SetHomeLight
, to be exact) or at least call
getInput
once before sending another command to
that controller. The function withCommandReply
is a
convenient way to wait for a specific command reply from the controller.
data HomeLightConfig Source #
The home light of a Nintendo Switch Controller can be controlled using repeatable
configuration cycles. See endlessPulse
for an example configuration.
Off | Turn off the home light. |
Once BaseDuration Intensity CycleConfig | Given a start intensity of the home light LED, fade to a target LED intensity in a given time, and then keep this LED intensity up for a given amount of time. The fade duration in milliseconds is calculated by multiplying the Example - fade from a switched off LED ( |
Cyclic BaseDuration Intensity [CycleConfig] RepeatBehaviour | Given a start intensity of the home light LED, repeatedly fade to a
target LED intensity in a given time, and then keep this LED intensity up
for a given amount of time. The fade durations and light upkeep durations
are calculated per cycle configuration as described for |
Instances
Eq HomeLightConfig Source # | |
Defined in Device.Nintendo.Switch.Output (==) :: HomeLightConfig -> HomeLightConfig -> Bool # (/=) :: HomeLightConfig -> HomeLightConfig -> Bool # | |
Read HomeLightConfig Source # | |
Defined in Device.Nintendo.Switch.Output | |
Show HomeLightConfig Source # | |
Defined in Device.Nintendo.Switch.Output showsPrec :: Int -> HomeLightConfig -> ShowS # show :: HomeLightConfig -> String # showList :: [HomeLightConfig] -> ShowS # |
type CycleConfig = (Intensity, FadeFactor, LightFactor) Source #
A home light cycle consists of a target LED intensity, a fade factor which controls the time needed to reach that LED intensity, and a light factor which controls how long to keep the target LED intensity up.
type BaseDuration = Word8 Source #
The base duration of a home light configuration in milliseconds. It will always be limited to an interval between 8ms and 175ms. It is called base duration because it will be multiplied with other factors in order to obtain the overall durations of fadings within home light configurations.
type Intensity = Word8 Source #
The LED intensity of the home light. It will always be limited to an interval between 0 and 100.
type FadeFactor = Word8 Source #
The fade duration factor of the home light. It will always be limited to an
interval between 0 and 15 and is multiplied with the BaseDuration
to obtain
the overall fade duration in milliseconds.
type LightFactor = Word8 Source #
The light duration factor of the home light. It will always be limited to an
interval between 0 and 15 and is multiplied with the BaseDuration
to obtain
the overall light duration in milliseconds.
data RepeatBehaviour Source #
Defines the repeat behaviour after all the home light configuration cycles have ended.
Instances
Eq RepeatBehaviour Source # | |
Defined in Device.Nintendo.Switch.Output (==) :: RepeatBehaviour -> RepeatBehaviour -> Bool # (/=) :: RepeatBehaviour -> RepeatBehaviour -> Bool # | |
Read RepeatBehaviour Source # | |
Defined in Device.Nintendo.Switch.Output | |
Show RepeatBehaviour Source # | |
Defined in Device.Nintendo.Switch.Output showsPrec :: Int -> RepeatBehaviour -> ShowS # show :: RepeatBehaviour -> String # showList :: [RepeatBehaviour] -> ShowS # |
endlessPulse :: HomeLightConfig Source #
A convenient home light configuration which pulsates the home light LED:
Cyclic
( 100 ) -- Base duration factor is 100ms.
( 0 ) -- LED is turned off at the beginning (intensity 0).
[ (100, 5, 1) -- Fade to LED intensity 100 in 500ms (100ms * 5) and stay there for 100ms (100ms * 1).
, ( 0, 5, 1) ] -- Fade to LED intensity 0 in 500ms (100ms * 5) and stay there for 100ms (100ms * 1).
( Forever ) -- Repeat these two cycles forever, thus generating a pulse-like LED.
Player Lights
setPlayerLights :: HasPlayerLights t => PlayerLightsConfig -> Controller t -> IO () Source #
Sets the player lights of a Nintendo Switch controller.
Note: After sending a command like this to a controller, it is highly advised
to check its corresponding CommandReply
(SetPlayerLights
, to be exact) or at least call
getInput
once before sending another command to
that controller. The function withCommandReply
is a
convenient way to wait for a specific command reply from the controller.
data PlayerLightsConfig Source #
Nintendo Switch controllers have four LEDs that can be used to indicate
various things, for example the player number or the Bluetooth pairing status.
The LEDs are numbered from left to right (i.e., led0
is the leftmost LED,
led3
is the rightmost LED).
Instances
Eq PlayerLightsConfig Source # | |
Defined in Device.Nintendo.Switch.Output (==) :: PlayerLightsConfig -> PlayerLightsConfig -> Bool # (/=) :: PlayerLightsConfig -> PlayerLightsConfig -> Bool # | |
Read PlayerLightsConfig Source # | |
Defined in Device.Nintendo.Switch.Output | |
Show PlayerLightsConfig Source # | |
Defined in Device.Nintendo.Switch.Output showsPrec :: Int -> PlayerLightsConfig -> ShowS # show :: PlayerLightsConfig -> String # showList :: [PlayerLightsConfig] -> ShowS # |
Each player light LED can be individually turned on, turned off or used in a pulsating manner (i.e., flashing).
noPlayerLights :: PlayerLightsConfig Source #
A convenient player lights configuration where all LEDs are turned off.
playerOne :: PlayerLightsConfig Source #
A convenient player lights configuration indicating player one (i.e., led0
is set).
playerTwo :: PlayerLightsConfig Source #
A convenient player lights configuration indicating player two (i.e., led1
is set).
playerThree :: PlayerLightsConfig Source #
A convenient player lights configuration indicating player three (i.e., led2
is set).
playerFour :: PlayerLightsConfig Source #
A convenient player lights configuration indicating player four (i.e., led3
is set).
flashAll :: PlayerLightsConfig Source #
A convenient player lights configuration where all LEDs are flashing.
Rumble
setVibration :: Bool -> Controller t -> IO () Source #
Enables (True
) or disables (False
) the rumble feature of a Nintendo
Switch controller. The rumble feature is disabled by default.
Note: After sending a command like this to a controller, it is highly advised
to check its corresponding CommandReply
(SetVibration
, to be exact) or at least call
getInput
once before sending another command to
that controller. The function withCommandReply
is a
convenient way to wait for a specific command reply from the controller.
setLeftRumble :: HasLeftRumble t => RumbleConfig -> Controller t -> IO () Source #
Sets the left rumble of a Nintendo Switch controller.
setRightRumble :: HasRightRumble t => RumbleConfig -> Controller t -> IO () Source #
Sets the right rumble of a Nintendo Switch controller.
:: (HasLeftRumble t, HasRightRumble t) | |
=> RumbleConfig | The left-side rumble configuration. |
-> RumbleConfig | The right-side rumble configuration. |
-> Controller t | The controller which should rumble. |
-> IO () |
Sets both the left rumble and right rumble of a Nintendo Switch controller.
Note that this is more efficient than setting the left rumble and right rumble
separately via setLeftRumble
and setRightRumble
.
data RumbleConfig Source #
Nintendo Switch controllers have a HD rumble feature which allows fine-grained control of rumble strengths and directions. As a consequence, a rumble is not configured by a mere numeric value, but by two (high and low) pairs of frequencies and amplitudes. This library constrains the value ranges of frequencies and amplitudes in order to always obtain sane configurations. However, sending extreme values for these pairs over an extended period of time may still damage a controller, so experiment wisely with rather short rumbles.
For technical discussions and the meaning of these values, one can read
this,
for example. A sample rumble configuration is provided by normalRumble
.
RumbleConfig | |
|
Instances
Eq RumbleConfig Source # | |
Defined in Device.Nintendo.Switch.Output (==) :: RumbleConfig -> RumbleConfig -> Bool # (/=) :: RumbleConfig -> RumbleConfig -> Bool # | |
Read RumbleConfig Source # | |
Defined in Device.Nintendo.Switch.Output readsPrec :: Int -> ReadS RumbleConfig # readList :: ReadS [RumbleConfig] # | |
Show RumbleConfig Source # | |
Defined in Device.Nintendo.Switch.Output showsPrec :: Int -> RumbleConfig -> ShowS # show :: RumbleConfig -> String # showList :: [RumbleConfig] -> ShowS # |
normalRumble :: RumbleConfig Source #
A convenient rumble configuration indicating a medium rumble strength.
RumbleConfig
{highFrequency
= 800 ,highAmplitude
= 0.5 ,lowFrequency
= 330 ,lowAmplitude
= 0.75 }
noRumble :: RumbleConfig Source #
A convenient rumble configuration indicating no rumble.
Exceptions
data ConnectionException Source #
A ConnectionException
is thrown if something goes wrong when reading the
internal data of a Nintendo Switch controller when connecting to it. This
should not occur if you have an unmodified controller (i.e., you have not
tampered with its internal SPI flash memory).
NoFactoryStickException | Indicates that a controller has no factory stick calibration. |
NoFactoryAxisException | Indicates that a controller has no factory sensor calibration. |
Instances
Eq ConnectionException Source # | |
Defined in Device.Nintendo.Switch.Connection (==) :: ConnectionException -> ConnectionException -> Bool # (/=) :: ConnectionException -> ConnectionException -> Bool # | |
Show ConnectionException Source # | |
Defined in Device.Nintendo.Switch.Connection showsPrec :: Int -> ConnectionException -> ShowS # show :: ConnectionException -> String # showList :: [ConnectionException] -> ShowS # | |
Exception ConnectionException Source # | |
data InputException Source #
An InputException
is thrown if something goes wrong with getInput
.
NoReplyException | Indicates that an expected reply wasn't received in a specific time interval. |
UnknownFormatException ByteString | Indicates that the controller input has an unexpected format. It essentially means that a specific part of the protocol has not been implemented yet. This should not occur as long as you stick to the public API of this library. |
Instances
Eq InputException Source # | |
Defined in Device.Nintendo.Switch.Input (==) :: InputException -> InputException -> Bool # (/=) :: InputException -> InputException -> Bool # | |
Show InputException Source # | |
Defined in Device.Nintendo.Switch.Input showsPrec :: Int -> InputException -> ShowS # show :: InputException -> String # showList :: [InputException] -> ShowS # | |
Exception InputException Source # | |
Defined in Device.Nintendo.Switch.Input |
data OutputException Source #
An OutputException
is thrown if something goes wrong when sending commands to
a Nintendo Switch controller.
Instances
Show OutputException Source # | |
Defined in Device.Nintendo.Switch.Output showsPrec :: Int -> OutputException -> ShowS # show :: OutputException -> String # showList :: [OutputException] -> ShowS # | |
Exception OutputException Source # | |
Defined in Device.Nintendo.Switch.Output |
Type Classes
class IsController (t :: ControllerType) Source #
A constraint which indicates that a controller is a valid Nintendo Switch controller that can be detected and connected to.
productID
Instances
IsController 'LeftJoyCon Source # | |
Defined in Device.Nintendo.Switch.Connection | |
IsController 'RightJoyCon Source # | |
Defined in Device.Nintendo.Switch.Connection | |
IsController 'ProController Source # | |
Defined in Device.Nintendo.Switch.Connection |
class HasCalibration (t :: ControllerType) Source #
A constraint which indicates that a Nintendo Switch controller is able to turn portions of its internal flash memory into valid calibration information.
calibrate
Instances
HasCalibration 'LeftJoyCon Source # | |
Defined in Device.Nintendo.Switch.Controller calibrate :: RawCalibration -> Calibration | |
HasCalibration 'RightJoyCon Source # | |
Defined in Device.Nintendo.Switch.Controller calibrate :: RawCalibration -> Calibration | |
HasCalibration 'ProController Source # | |
Defined in Device.Nintendo.Switch.Controller calibrate :: RawCalibration -> Calibration |
class HasInputMode t Source #
A constraint which indicates that a Nintendo Switch controller supports multiple
input modes (see setInputMode
).
Instances
HasInputMode 'LeftJoyCon Source # | |
Defined in Device.Nintendo.Switch.Output | |
HasInputMode 'RightJoyCon Source # | |
Defined in Device.Nintendo.Switch.Output |
convert
Instances
HasInput 'LeftJoyCon Source # | |
Defined in Device.Nintendo.Switch.Input convert :: Controller 'LeftJoyCon -> RawInput -> Input | |
HasInput 'RightJoyCon Source # | |
Defined in Device.Nintendo.Switch.Input convert :: Controller 'RightJoyCon -> RawInput -> Input | |
HasInput 'ProController Source # | |
Defined in Device.Nintendo.Switch.Input convert :: Controller 'ProController -> RawInput -> Input |
class HasHomeLight t Source #
A constraint which indicates that a Nintendo Switch controller has a home
light (see setHomeLight
).
Instances
HasHomeLight 'RightJoyCon Source # | |
Defined in Device.Nintendo.Switch.Output | |
HasHomeLight 'ProController Source # | |
Defined in Device.Nintendo.Switch.Output |
class HasPlayerLights t Source #
A constraint which indicates that a Nintendo Switch controller has player lights
(i.e., the four LEDs which represent the player number; see setPlayerLights
).
Instances
HasPlayerLights 'LeftJoyCon Source # | |
Defined in Device.Nintendo.Switch.Output | |
HasPlayerLights 'RightJoyCon Source # | |
Defined in Device.Nintendo.Switch.Output | |
HasPlayerLights 'ProController Source # | |
Defined in Device.Nintendo.Switch.Output |
class HasLeftRumble t Source #
A constraint which indicates that a Nintendo Switch controller has a left-side
rumble unit (see setLeftRumble
).
Instances
HasLeftRumble 'LeftJoyCon Source # | |
Defined in Device.Nintendo.Switch.Output | |
HasLeftRumble 'ProController Source # | |
Defined in Device.Nintendo.Switch.Output |
class HasRightRumble t Source #
A constraint which indicates that a Nintendo Switch controller has a right-side
rumble unit (see setRightRumble
).
Instances
HasRightRumble 'RightJoyCon Source # | |
Defined in Device.Nintendo.Switch.Output | |
HasRightRumble 'ProController Source # | |
Defined in Device.Nintendo.Switch.Output |