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

Contents

Description

USB devices report their attributes using descriptors. A descriptor is a data structure with a defined format. Using descriptors allows concise storage of the attributes of individual configurations because each configuration may reuse descriptors or portions of descriptors from other configurations that have the same characteristics. In this manner, the descriptors resemble individual data records in a relational database.

Where appropriate, descriptors contain references to string descriptors (StrIx) that provide textual information describing a descriptor in human-readable form. Note that the inclusion of string descriptors is optional.

Synopsis

Device descriptor

getDeviceDesc :: Device -> IO DeviceDesc Source #

Get the USB device descriptor for a given device.

This is a non-blocking function; the device descriptor is cached in memory.

This function may throw USBExceptions.

data DeviceDesc Source #

A structure representing the standard USB device descriptor.

This descriptor is documented in section 9.6.1 of the USB 2.0 specification.

This structure can be retrieved by getDeviceDesc.

Constructors

DeviceDesc 

Fields

Instances

Eq DeviceDesc Source # 
Data DeviceDesc Source # 

Methods

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

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

toConstr :: DeviceDesc -> Constr #

dataTypeOf :: DeviceDesc -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DeviceDesc Source # 
Show DeviceDesc Source # 
Generic DeviceDesc Source # 

Associated Types

type Rep DeviceDesc :: * -> * #

type Rep DeviceDesc Source # 
type Rep DeviceDesc = D1 * (MetaData "DeviceDesc" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) (C1 * (MetaCons "DeviceDesc" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "deviceUSBSpecReleaseNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ReleaseNumber)) ((:*:) * (S1 * (MetaSel (Just Symbol "deviceClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "deviceSubClass") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word8)))) ((:*:) * (S1 * (MetaSel (Just Symbol "deviceProtocol") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word8)) ((:*:) * (S1 * (MetaSel (Just Symbol "deviceMaxPacketSize0") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "deviceVendorId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * VendorId))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "deviceProductId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProductId)) ((:*:) * (S1 * (MetaSel (Just Symbol "deviceReleaseNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ReleaseNumber)) (S1 * (MetaSel (Just Symbol "deviceManufacturerStrIx") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StrIx))))) ((:*:) * (S1 * (MetaSel (Just Symbol "deviceProductStrIx") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StrIx))) ((:*:) * (S1 * (MetaSel (Just Symbol "deviceSerialNumberStrIx") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe StrIx))) (S1 * (MetaSel (Just Symbol "deviceNumConfigs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word8)))))))

type ReleaseNumber = (Int, Int, Int, Int) Source #

Release / version number of the USB specification / device.

For a database of USB vendors and products see the usb-id-database package at: http://hackage.haskell.org/package/usb-id-database

type VendorId = Word16 Source #

A 16-bit number used to identify a USB device. Each vendor ID is assigned by the USB Implementers Forum to a specific company.

type ProductId = Word16 Source #

A 16-bit number used to identify a USB device. Each company which is assigned a VendorId can assign a product ID to its USB-based products.

Configuration descriptor

getConfigDesc :: Device -> Word8 -> IO ConfigDesc Source #

Get a USB configuration descriptor based on its index.

This is a non-blocking function which does not involve any requests being sent to the device.

Exceptions:

data ConfigDesc Source #

A structure representing the standard USB configuration descriptor.

This descriptor is documented in section 9.6.3 of the USB 2.0 specification.

This structure can be retrieved by getConfigDesc.

Constructors

ConfigDesc 

Fields

Instances

Eq ConfigDesc Source # 
Data ConfigDesc Source # 

Methods

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

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

toConstr :: ConfigDesc -> Constr #

dataTypeOf :: ConfigDesc -> DataType #

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

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

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

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

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

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

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

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

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

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

Read ConfigDesc Source # 
Show ConfigDesc Source # 
Generic ConfigDesc Source # 

Associated Types

type Rep ConfigDesc :: * -> * #

type Rep ConfigDesc Source # 

Configuration attributes

type ConfigAttribs = DeviceStatus Source #

The USB 2.0 specification specifies that the configuration attributes only describe the device status.

data DeviceStatus Source #

The status of a USB device.

Constructors

DeviceStatus 

Fields

  • remoteWakeup :: !Bool

    The Remote Wakeup field indicates whether the device is currently enabled to request remote wakeup. The default mode for devices that support remote wakeup is disabled.

  • selfPowered :: !Bool

    The Self Powered field indicates whether the device is currently self-powered

Instances

Eq DeviceStatus Source # 
Data DeviceStatus Source # 

Methods

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

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

toConstr :: DeviceStatus -> Constr #

dataTypeOf :: DeviceStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Read DeviceStatus Source # 
Show DeviceStatus Source # 
Generic DeviceStatus Source # 

Associated Types

type Rep DeviceStatus :: * -> * #

type Rep DeviceStatus Source # 
type Rep DeviceStatus = D1 * (MetaData "DeviceStatus" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) (C1 * (MetaCons "DeviceStatus" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "remoteWakeup") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "selfPowered") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool))))

Interface descriptor

type Interface = Vector InterfaceDesc Source #

An interface is represented as a vector of alternate interface settings.

data InterfaceDesc Source #

A structure representing the standard USB interface descriptor.

This descriptor is documented in section 9.6.5 of the USB 2.0 specification.

This structure can be retrieved using configInterfaces.

Constructors

InterfaceDesc 

Fields

Instances

Eq InterfaceDesc Source # 
Data InterfaceDesc Source # 

Methods

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

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

toConstr :: InterfaceDesc -> Constr #

dataTypeOf :: InterfaceDesc -> DataType #

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

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

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

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

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

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

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

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

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

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

Read InterfaceDesc Source # 
Show InterfaceDesc Source # 
Generic InterfaceDesc Source # 

Associated Types

type Rep InterfaceDesc :: * -> * #

type Rep InterfaceDesc Source # 

Endpoint descriptor

data EndpointDesc Source #

A structure representing the standard USB endpoint descriptor.

This descriptor is documented in section 9.6.3 of the USB 2.0 specification.

This structure can be retrieved by using interfaceEndpoints.

Constructors

EndpointDesc 

Fields

Instances

Eq EndpointDesc Source # 
Data EndpointDesc Source # 

Methods

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

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

toConstr :: EndpointDesc -> Constr #

dataTypeOf :: EndpointDesc -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EndpointDesc Source # 
Show EndpointDesc Source # 
Generic EndpointDesc Source # 

Associated Types

type Rep EndpointDesc :: * -> * #

type Rep EndpointDesc Source # 

Endpoint address

data EndpointAddress Source #

The address of an endpoint.

Constructors

EndpointAddress 

Fields

Instances

Eq EndpointAddress Source # 
Data EndpointAddress Source # 

Methods

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

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

toConstr :: EndpointAddress -> Constr #

dataTypeOf :: EndpointAddress -> DataType #

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

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

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

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

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

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

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

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

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

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

Read EndpointAddress Source # 
Show EndpointAddress Source # 
Generic EndpointAddress Source # 
type Rep EndpointAddress Source # 
type Rep EndpointAddress = D1 * (MetaData "EndpointAddress" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) (C1 * (MetaCons "EndpointAddress" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "endpointNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "transferDirection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * TransferDirection))))

data TransferDirection Source #

The direction of data transfer relative to the host.

Constructors

Out

Out transfer direction (host -> device) used for writing.

In

In transfer direction (device -> host) used for reading.

Instances

Enum TransferDirection Source # 
Eq TransferDirection Source # 
Data TransferDirection Source # 

Methods

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

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

toConstr :: TransferDirection -> Constr #

dataTypeOf :: TransferDirection -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TransferDirection Source # 
Show TransferDirection Source # 
Generic TransferDirection Source # 
type Rep TransferDirection Source # 
type Rep TransferDirection = D1 * (MetaData "TransferDirection" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) ((:+:) * (C1 * (MetaCons "Out" PrefixI False) (U1 *)) (C1 * (MetaCons "In" PrefixI False) (U1 *)))

Endpoint attributes

type EndpointAttribs = TransferType Source #

The USB 2.0 specification specifies that the endpoint attributes only describe the endpoint transfer type.

data TransferType Source #

Describes what types of transfers are allowed on the endpoint.

Constructors

Control

Control transfers are typically used for command and status operations.

Isochronous !Synchronization !Usage

Isochronous transfers occur continuously and periodically.

Bulk

Bulk transfers can be used for large bursty data.

Interrupt

Interrupt transfers are typically non-periodic, small device "initiated" communication requiring bounded latency.

Instances

Eq TransferType Source # 
Data TransferType Source # 

Methods

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

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

toConstr :: TransferType -> Constr #

dataTypeOf :: TransferType -> DataType #

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

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

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

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

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

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

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

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

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

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

Read TransferType Source # 
Show TransferType Source # 
Generic TransferType Source # 

Associated Types

type Rep TransferType :: * -> * #

type Rep TransferType Source # 
type Rep TransferType = D1 * (MetaData "TransferType" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Control" PrefixI False) (U1 *)) (C1 * (MetaCons "Isochronous" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Synchronization)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Usage))))) ((:+:) * (C1 * (MetaCons "Bulk" PrefixI False) (U1 *)) (C1 * (MetaCons "Interrupt" PrefixI False) (U1 *))))

Isochronous transfer attributes

data Synchronization Source #

See section 5.12.4.1 of the USB 2.0 specification.

Constructors

NoSynchronization

No Synchonisation.

Asynchronous

Unsynchronized, although sinks provide data rate feedback.

Adaptive

Synchronized using feedback or feedforward data rate information

Synchronous

Synchronized to the USB’s SOF (Start Of Frame)

Instances

Enum Synchronization Source # 
Eq Synchronization Source # 
Data Synchronization Source # 

Methods

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

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

toConstr :: Synchronization -> Constr #

dataTypeOf :: Synchronization -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Synchronization Source # 
Show Synchronization Source # 
Generic Synchronization Source # 
type Rep Synchronization Source # 
type Rep Synchronization = D1 * (MetaData "Synchronization" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) ((:+:) * ((:+:) * (C1 * (MetaCons "NoSynchronization" PrefixI False) (U1 *)) (C1 * (MetaCons "Asynchronous" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Adaptive" PrefixI False) (U1 *)) (C1 * (MetaCons "Synchronous" PrefixI False) (U1 *))))

data Usage Source #

See section 5.12.4.2 of the USB 2.0 specification.

Constructors

Data 
Feedback 
Implicit 

Instances

Enum Usage Source # 
Eq Usage Source # 

Methods

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

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

Data Usage Source # 

Methods

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

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

toConstr :: Usage -> Constr #

dataTypeOf :: Usage -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Usage Source # 
Show Usage Source # 

Methods

showsPrec :: Int -> Usage -> ShowS #

show :: Usage -> String #

showList :: [Usage] -> ShowS #

Generic Usage Source # 

Associated Types

type Rep Usage :: * -> * #

Methods

from :: Usage -> Rep Usage x #

to :: Rep Usage x -> Usage #

type Rep Usage Source # 
type Rep Usage = D1 * (MetaData "Usage" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) ((:+:) * (C1 * (MetaCons "Data" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Feedback" PrefixI False) (U1 *)) (C1 * (MetaCons "Implicit" PrefixI False) (U1 *))))

Endpoint max packet size

data MaxPacketSize Source #

Maximum packet size.

Instances

Eq MaxPacketSize Source # 
Data MaxPacketSize Source # 

Methods

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

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

toConstr :: MaxPacketSize -> Constr #

dataTypeOf :: MaxPacketSize -> DataType #

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

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

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

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

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

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

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

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

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

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

Read MaxPacketSize Source # 
Show MaxPacketSize Source # 
Generic MaxPacketSize Source # 

Associated Types

type Rep MaxPacketSize :: * -> * #

type Rep MaxPacketSize Source # 
type Rep MaxPacketSize = D1 * (MetaData "MaxPacketSize" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) (C1 * (MetaCons "MaxPacketSize" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "maxPacketSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Size)) (S1 * (MetaSel (Just Symbol "transactionOpportunities") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * TransactionOpportunities))))

data TransactionOpportunities Source #

Number of additional transaction oppurtunities per microframe.

See table 9-13 of the USB 2.0 specification.

Constructors

Zero

None (1 transaction per microframe)

One

1 additional (2 per microframe)

Two

2 additional (3 per microframe)

Instances

Enum TransactionOpportunities Source # 
Eq TransactionOpportunities Source # 
Data TransactionOpportunities Source # 

Methods

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

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

toConstr :: TransactionOpportunities -> Constr #

dataTypeOf :: TransactionOpportunities -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TransactionOpportunities Source # 
Read TransactionOpportunities Source # 
Show TransactionOpportunities Source # 
Generic TransactionOpportunities Source # 
type Rep TransactionOpportunities Source # 
type Rep TransactionOpportunities = D1 * (MetaData "TransactionOpportunities" "System.USB.Base" "usb-1.3.0.6-BxALn33Tmsa87zdhZNpf2H" False) ((:+:) * (C1 * (MetaCons "Zero" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "One" PrefixI False) (U1 *)) (C1 * (MetaCons "Two" PrefixI False) (U1 *))))

maxIsoPacketSize :: EndpointDesc -> Size Source #

Calculate the maximum packet size which a specific endpoint is capable of sending or receiving in the duration of 1 microframe.

If acting on an Isochronous or Interrupt endpoint, this function will multiply the maxPacketSize by the additional transactionOpportunities. If acting on another type of endpoint only the maxPacketSize is returned.

This function is mainly useful for setting up isochronous transfers.

String descriptors

getLanguages :: DeviceHandle -> IO (Vector LangId) Source #

Retrieve a vector of supported languages.

This function may throw USBExceptions.

type LangId = (PrimaryLangId, SubLangId) Source #

The language ID consists of the primary language identifier and the sublanguage identififier as described in:

http://www.usb.org/developers/docs/USB_LANGIDs.pdf

For a mapping between IDs and languages see the usb-id-database package.

To see which LangIds are supported by a device see getLanguages.

type PrimaryLangId = Word16 Source #

The primary language identifier.

type SubLangId = Word16 Source #

The sublanguage identifier.

type StrIx = Word8 Source #

Type of indici of string descriptors.

Can be retrieved by all the *StrIx functions.

getStrDesc Source #

Arguments

:: DeviceHandle 
-> StrIx 
-> LangId 
-> Int

Maximum number of characters in the requested string. An IOException will be thrown when the requested string is larger than this number.

-> IO Text 

Retrieve a string descriptor from a device.

This function may throw USBExceptions.

getStrDescFirstLang Source #

Arguments

:: DeviceHandle 
-> StrIx 
-> Int

Maximum number of characters in the requested string. An IOException will be thrown when the requested string is larger than this number.

-> IO Text 

Retrieve a string descriptor from a device using the first supported language.

This function may throw USBExceptions.