usb-1.3.0.6: Communicate with USB devices

Copyright(c) 2009–2017 Bas van Dijk
LicenseBSD3 (see the file LICENSE)
MaintainerBas van Dijk <v.dijk.bas@gmail.com>
Safe HaskellTrustworthy
LanguageHaskell98

System.USB.IO

Contents

Description

This module provides functions for performing control, bulk and interrupt transfers.

When your system supports the GHC EventManager this module additionally exports functions for performing isochronous transfers. These are currently not available on Windows.

WARNING: You need to enable the threaded runtime (-threaded) when using the isochronous functions. They throw a runtime error otherwise!

Synopsis

One-off transfers

type ReadAction = Size -> Timeout -> IO (ByteString, Status) Source #

Handy type synonym for read transfers.

A ReadAction is a function which takes a Size which defines how many bytes to read and a Timeout. The function returns an IO action which, when executed, performs the actual read and returns the ByteString that was read paired with a Status flag which indicates whether the transfer Completed or TimedOut.

type ReadExactAction = Size -> Timeout -> IO ByteString Source #

Handy type synonym for read transfers that must exactly read the specified number of bytes. An incompleteReadException is thrown otherwise.

type WriteAction = ByteString -> Timeout -> IO (Size, Status) Source #

Handy type synonym for write transfers.

A WriteAction is a function which takes a ByteString to write and a Timeout. The function returns an IO action which, when exectued, returns the number of bytes that were actually written paired with a Status flag which indicates whether the transfer Completed or TimedOut.

type WriteExactAction = ByteString -> Timeout -> IO () Source #

Handy type synonym for write transfers that must exactly write all the given bytes. An incompleteWriteException is thrown otherwise.

type Size = Int Source #

Number of bytes transferred.

type Timeout = Int Source #

A timeout in milliseconds. A timeout defines how long a transfer should wait before giving up due to no response being received. Use noTimeout for no timeout.

noTimeout :: Timeout Source #

A timeout of 0 denotes no timeout so: noTimeout = 0.

data Status Source #

Status of a terminated transfer.

Constructors

Completed

All bytes were transferred within the maximum allowed Timeout period.

TimedOut

Not all bytes were transferred within the maximum allowed Timeout period.

Instances

Eq Status Source # 

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Data Status Source # 

Methods

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

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

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Status Source # 
Show Status Source # 
Generic Status Source # 

Associated Types

type Rep Status :: * -> * #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

type Rep Status Source # 
type Rep Status = D1 * (MetaData "Status" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) ((:+:) * (C1 * (MetaCons "Completed" PrefixI False) (U1 *)) (C1 * (MetaCons "TimedOut" PrefixI False) (U1 *)))

Control transfers

data ControlSetup Source #

Setup for control transfers.

Constructors

ControlSetup 

Fields

Instances

Eq ControlSetup Source # 
Data ControlSetup Source # 

Methods

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

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

toConstr :: ControlSetup -> Constr #

dataTypeOf :: ControlSetup -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ControlSetup Source # 
Show ControlSetup Source # 
Generic ControlSetup Source # 

Associated Types

type Rep ControlSetup :: * -> * #

type Rep ControlSetup Source # 
type Rep ControlSetup = D1 * (MetaData "ControlSetup" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) (C1 * (MetaCons "ControlSetup" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "controlSetupRequestType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * RequestType)) (S1 * (MetaSel (Just Symbol "controlSetupRecipient") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Recipient))) ((:*:) * (S1 * (MetaSel (Just Symbol "controlSetupRequest") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Request)) ((:*:) * (S1 * (MetaSel (Just Symbol "controlSetupValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Value)) (S1 * (MetaSel (Just Symbol "controlSetupIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Index))))))

data RequestType Source #

The type of control requests.

Constructors

Standard

Standard requests are common to all USB device's.

Class

Class requests are common to classes of drivers. For example, all device's conforming to the HID class will have a common set of class specific requests. These will differ to a device conforming to the communications class and differ again to that of a device conforming to the mass storage class.

Vendor

These are requests which the USB device designer (you?) can assign. These are normally different from device to device, but this is all up to your implementation and imagination.

Instances

Enum RequestType Source # 
Eq RequestType Source # 
Data RequestType Source # 

Methods

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

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

toConstr :: RequestType -> Constr #

dataTypeOf :: RequestType -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RequestType Source # 
Show RequestType Source # 
Generic RequestType Source # 

Associated Types

type Rep RequestType :: * -> * #

type Rep RequestType Source # 
type Rep RequestType = D1 * (MetaData "RequestType" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) ((:+:) * (C1 * (MetaCons "Standard" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Class" PrefixI False) (U1 *)) (C1 * (MetaCons "Vendor" PrefixI False) (U1 *))))

data Recipient Source #

A common request can be directed to different recipients and based on the recipient perform different functions. A GetStatus Standard request for example, can be directed at the device, interface or endpoint. When directed to a device it returns flags indicating the status of remote wakeup and if the device is self powered. However if the same request is directed at the interface it always returns zero, or should it be directed at an endpoint will return the halt flag for the endpoint.

Constructors

ToDevice

Directed to the device.

ToInterface

Directed to the interface.

ToEndpoint

Directed to the endpoint.

ToOther

Directed to something other than the device, interface or endpoint.

Instances

Enum Recipient Source # 
Eq Recipient Source # 
Data Recipient Source # 

Methods

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

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

toConstr :: Recipient -> Constr #

dataTypeOf :: Recipient -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Recipient Source # 
Show Recipient Source # 
Generic Recipient Source # 

Associated Types

type Rep Recipient :: * -> * #

type Rep Recipient Source # 
type Rep Recipient = D1 * (MetaData "Recipient" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ToDevice" PrefixI False) (U1 *)) (C1 * (MetaCons "ToInterface" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ToEndpoint" PrefixI False) (U1 *)) (C1 * (MetaCons "ToOther" PrefixI False) (U1 *))))

type Request = Word8 Source #

The actual request code.

type Value = Word16 Source #

A potential additional parameter for the request.

(Host-endian)

type Index = Word16 Source #

A potential additional parameter for the request. Usually used as an index or offset.

(Host-endian)

control :: DeviceHandle -> ControlSetup -> Timeout -> IO () Source #

Perform a USB control request that does not transfer data.

Exceptions:

readControl :: DeviceHandle -> ControlSetup -> ReadAction Source #

Perform a USB control read.

Exceptions:

readControlExact :: DeviceHandle -> ControlSetup -> ReadExactAction Source #

A convenience function similar to readControl which checks if the specified number of bytes to read were actually read. Throws an incompleteReadException if this is not the case.

writeControl :: DeviceHandle -> ControlSetup -> WriteAction Source #

Perform a USB control write.

Exceptions:

writeControlExact :: DeviceHandle -> ControlSetup -> WriteExactAction Source #

A convenience function similar to writeControl which checks if the given bytes were actually fully written. Throws an incompleteWriteException if this is not the case.

Bulk transfers

readBulk Source #

Arguments

:: DeviceHandle 
-> EndpointAddress

Make sure transferDirection is set to In.

-> ReadAction 

Perform a USB bulk read.

Exceptions:

writeBulk Source #

Arguments

:: DeviceHandle 
-> EndpointAddress

Make sure transferDirection is set to Out.

-> WriteAction 

Perform a USB bulk write.

Exceptions:

Interrupt transfers

readInterrupt Source #

Arguments

:: DeviceHandle 
-> EndpointAddress

Make sure transferDirection is set to In.

-> ReadAction 

Perform a USB interrupt read.

Exceptions:

writeInterrupt Source #

Arguments

:: DeviceHandle 
-> EndpointAddress

Make sure transferDirection is set to Out.

-> WriteAction 

Perform a USB interrupt write.

Exceptions:

Isochronous transfers

WARNING: You need to enable the threaded runtime (-threaded) when using the isochronous functions. They throw a runtime error otherwise!

readIsochronous Source #

Arguments

:: DeviceHandle 
-> EndpointAddress

Make sure transferDirection is set to In.

-> Vector Size

Sizes of isochronous packets to read.

-> Timeout 
-> IO (Vector ByteString) 

Perform a USB isochronous read.

WARNING: You need to enable the threaded runtime (-threaded) for this function to work correctly. It throws a runtime error otherwise!

Exceptions:

writeIsochronous Source #

Arguments

:: DeviceHandle 
-> EndpointAddress

Make sure transferDirection is set to Out.

-> Vector ByteString

Isochronous packets to write.

-> Timeout 
-> IO (Vector Size) 

Perform a USB isochronous write.

WARNING: You need to enable the threaded runtime (-threaded) for this function to work correctly. It throws a runtime error otherwise!

Exceptions: