switch-0.1.0.0: Nintendo Switch Controller Library
Copyright(c) Michael Szvetits 2021
LicenseBSD3 (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Device.Nintendo.Switch

Description

Types and functions for connecting to Nintendo Switch controllers, reading input (e.g., buttons, sensors) and sending commands (e.g., rumble).

Synopsis

Connection

Switch Console

data Console Source #

A handle which represents a virtual Nintendo Switch console. The handle is used to detect controllers and manage their connections.

init :: IO Console Source #

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.

withConsole :: (Console -> IO a) -> IO a Source #

A convenient wrapper around init and exit.

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

Instances details
Eq ControllerType Source # 
Instance details

Defined in Device.Nintendo.Switch.Controller

Read ControllerType Source # 
Instance details

Defined in Device.Nintendo.Switch.Controller

Show ControllerType Source # 
Instance details

Defined in Device.Nintendo.Switch.Controller

HasInputMode 'LeftJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasInputMode 'RightJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasPlayerLights 'LeftJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasPlayerLights 'RightJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasPlayerLights 'ProController Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasRightRumble 'RightJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasRightRumble 'ProController Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasLeftRumble 'LeftJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasLeftRumble 'ProController Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasHomeLight 'RightJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasHomeLight 'ProController Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

data ControllerInfo (t :: ControllerType) Source #

A handle which represents an unconnected Nintendo Switch controller.

Instances

Instances details
Show (ControllerInfo t) Source # 
Instance details

Defined in Device.Nintendo.Switch.Connection

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

connect Source #

Arguments

:: 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

data InputMode Source #

The input mode of a Nintendo Switch controller determines the frequency and amount of information received by getInput.

Constructors

Standard

The default input mode. In this mode, controllers push Input packages in a 60Hz (Joy-Con) or 120Hz (Pro Controller) frequency, including battery information, Analog stick directions (stickLeft, stickRight) and Inertial sensor data (extras) if activated via setInertialMeasurement.

Simple

A simple input mode where a controller only pushes its Input whenever a button is pressed or a CommandReply (extras) is sent. In this mode, controllers only send Discrete stick directions (stickLeft, stickRight) and no inertial sensor data. Furthermore, battery information is only sent in combination with command replies.

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.

getTimeoutInput Source #

Arguments

:: HasInput t 
=> Int

The time interval in milliseconds.

-> Controller t

The controller to read the input from.

-> IO (Maybe Input)

Returns Nothing if the controller does not provide an input within the specified time interval.

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).

Instances

Instances details
(Eq s, Eq e) => Eq (ControllerInput s e) Source # 
Instance details

Defined in Device.Nintendo.Switch.Input

(Read s, Read e) => Read (ControllerInput s e) Source # 
Instance details

Defined in Device.Nintendo.Switch.Input

(Show s, Show e) => Show (ControllerInput s e) Source # 
Instance details

Defined in Device.Nintendo.Switch.Input

data StickDirection a Source #

The direction of the left (stickLeft) and right (stickRight) analog sticks.

Constructors

Discrete Direction

In Simple input mode, controllers send discrete stick directions.

Analog a a

In Standard input mode, controllers send analog stick directions. The first value is left/right (interval [-1,1]), the second value is down/up (interval [-1,1]).

data Direction Source #

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.

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).

Constructors

CommandReply ReplyData

After sending commands to the controller (e.g., setting the InputMode), a command reply is returned as extra data in the next input.

Inertial (Accelerometer a) (Gyroscope a)

A controller provides inertial sensor data (i.e., accelerometer and gyroscope) only if it is in Standard input mode and inertial measurement is activated via setInertialMeasurement.

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

Instances details
Functor ExtraInput Source # 
Instance details

Defined in Device.Nintendo.Switch.Input

Methods

fmap :: (a -> b) -> ExtraInput a -> ExtraInput b #

(<$) :: a -> ExtraInput b -> ExtraInput a #

Eq a => Eq (ExtraInput a) Source # 
Instance details

Defined in Device.Nintendo.Switch.Input

Methods

(==) :: ExtraInput a -> ExtraInput a -> Bool #

(/=) :: ExtraInput a -> ExtraInput a -> Bool #

Read a => Read (ExtraInput a) Source # 
Instance details

Defined in Device.Nintendo.Switch.Input

Show a => Show (ExtraInput a) Source # 
Instance details

Defined in Device.Nintendo.Switch.Input

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 ReplyData Source #

Data type that combines the command type and its corresponding acknowledgement.

data Acknowledgement a Source #

Whenever a command is sent to a controller (e.g., setting the InputMode), the controller replies with an Acknowledgement.

Constructors

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.

Convenience

noInput :: ControllerInput s e Source #

A convenient constant that represents no input. This can be used to set specific buttons and stick directions in order to test functions without having a Nintendo Switch controller at hand, like:

    noInput { btnX = True, stickLeft = Discrete Up }

coordinates :: StickDirection Float -> (Float, Float) Source #

Converts stick directions into x/y coordinates in the interval [-1,1]. Analog values are taken as is, while Discrete directions are converted to their analog counterpart.

mergeInputs Source #

Arguments

:: Input

The left-side input to be merged.

-> Input

The right-side input to be merged.

-> Input

The merged input, without extras and battery.

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).

withCommandReply Source #

Arguments

:: Int

The maximum count of inputs that should be consumed.

-> Int

The timeout per input read (see getTimeoutInput).

-> Controller t

The controller to read the input from.

-> (ReplyData -> Maybe a)

The function which checks the command reply. It must return Nothing if a ReplyData is encountered which we are not looking for, or Just a if everything went well.

-> 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.

Constructors

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 BaseDuration with the FadeFactor of the CycleConfig. The light upkeep duration in milliseconds is calculated by multiplying the BaseDuration with the LightFactor of the CycleConfig.

Example - fade from a switched off LED (0) to a fully bright LED (100) in 500ms (50ms * 10), stay there for one second (50ms * 20), then turn it off:

    Once 50 0 (100, 10, 20)
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 Once. See endlessPulse for a cyclic configuration example.

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.

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).

data LightMode Source #

Each player light LED can be individually turned on, turned off or used in a pulsating manner (i.e., flashing).

Constructors

LightOn 
LightOff 
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.

setRumble Source #

Arguments

:: (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.

Constructors

RumbleConfig 

Fields

  • highFrequency :: Double

    The high frequency. It will always be limited to an interval between 81.75177 Hz and 1252.572266 Hz.

  • highAmplitude :: Double

    The high amplitude. It will always be limited to an interval between 0.0 and 1.0.

  • lowFrequency :: Double

    The low frequency. It will always be limited to an interval between 40.875885 Hz and 626.286133 Hz.

  • lowAmplitude :: Double

    The low amplitude. It will always be limited to an interval between 0.0 and 1.0.

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).

Constructors

NoFactoryStickException

Indicates that a controller has no factory stick calibration.

NoFactoryAxisException

Indicates that a controller has no factory sensor calibration.

data InputException Source #

An InputException is thrown if something goes wrong with getInput.

Constructors

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.

data OutputException Source #

An OutputException is thrown if something goes wrong when sending commands to a Nintendo Switch controller.

Constructors

WriteException 

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.

Minimal complete definition

productID

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.

Minimal complete definition

calibrate

Instances

Instances details
HasCalibration 'LeftJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Controller

Methods

calibrate :: RawCalibration -> Calibration

HasCalibration 'RightJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Controller

Methods

calibrate :: RawCalibration -> Calibration

HasCalibration 'ProController Source # 
Instance details

Defined in Device.Nintendo.Switch.Controller

Methods

calibrate :: RawCalibration -> Calibration

class HasInputMode t Source #

A constraint which indicates that a Nintendo Switch controller supports multiple input modes (see setInputMode).

Instances

Instances details
HasInputMode 'LeftJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasInputMode 'RightJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

class HasInput t Source #

A constraint which indicates that a Nintendo Switch controller can provide Input (see getInput).

Minimal complete definition

convert

Instances

Instances details
HasInput 'LeftJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Input

Methods

convert :: Controller 'LeftJoyCon -> RawInput -> Input

HasInput 'RightJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Input

Methods

convert :: Controller 'RightJoyCon -> RawInput -> Input

HasInput 'ProController Source # 
Instance details

Defined in Device.Nintendo.Switch.Input

Methods

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

Instances details
HasHomeLight 'RightJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasHomeLight 'ProController Source # 
Instance details

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

Instances details
HasPlayerLights 'LeftJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasPlayerLights 'RightJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasPlayerLights 'ProController Source # 
Instance details

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

Instances details
HasLeftRumble 'LeftJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasLeftRumble 'ProController Source # 
Instance details

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

Instances details
HasRightRumble 'RightJoyCon Source # 
Instance details

Defined in Device.Nintendo.Switch.Output

HasRightRumble 'ProController Source # 
Instance details

Defined in Device.Nintendo.Switch.Output