Maintainer | Bas van Dijk <v.dijk.bas@gmail.com> |
---|
This modules provides the following guarantees for working with USB devices:
- You can't reference handles to devices that are closed. In other words: no I/O with closed handles is possible.
- The programmer can specify the region in which devices should remain open. On exit from the region the opened devices will be closed automatically.
- You can't reference handles to configurations that have not been set.
- You can't reference handles to interfaces that have not been claimed.
- Just like with devices, the programmer can specify the region in which interfaces should remain claimed. On exit from the region the claimed interfaces will be released automatically.
- You can't reference handles to alternates that have not been set.
- You can't reference endpoints that don't belong to a setted alternate.
- You can't read from an endpoint with an
Out
transfer direction. - You can't write to an endpoint with an
In
transfer direction.
This modules makes use of a technique called Lightweight monadic regions invented by Oleg Kiselyov and Chung-chieh Shan
See: http://okmij.org/ftp/Haskell/regions.html#light-weight
This technique is implemented in the regions
package of which the
Control.Monad.Trans.Region
module is re-exported by this module.
See the usb-safe-examples
package for examples how to use this library:
git clone https://github.com/basvandijk/usb-safe-examples
- module Control.Monad.Trans.Region
- data RegionalDeviceHandle r
- openDevice :: MonadControlIO pr => Device -> RegionT s pr (RegionalDeviceHandle (RegionT s pr))
- withDevice :: MonadControlIO pr => Device -> (forall s. RegionalDeviceHandle (RegionT s pr) -> RegionT s pr α) -> pr α
- withDeviceWhich :: forall pr α. MonadControlIO pr => Ctx -> (DeviceDesc -> Bool) -> (forall s. RegionalDeviceHandle (RegionT s pr) -> RegionT s pr α) -> pr α
- getDevice :: RegionalDeviceHandle r -> Device
- class GetDescriptor α desc | α -> desc, desc -> α where
- getDesc :: α -> desc
- resetDevice :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> cr ()
- data Config r
- getConfigs :: RegionalDeviceHandle r -> [Config r]
- data ConfigHandle sCfg
- setConfig :: forall pr cr s α. (AncestorRegion pr (RegionT s cr), MonadControlIO cr) => Config pr -> (forall sCfg. ConfigHandle sCfg -> RegionT s cr α) -> RegionT s cr α
- data SettingAlreadySet = SettingAlreadySet
- useActiveConfig :: forall pr cr s α. (AncestorRegion pr (RegionT s cr), MonadControlIO cr) => RegionalDeviceHandle pr -> (forall sCfg. ConfigHandle sCfg -> RegionT s cr α) -> RegionT s cr α
- data NoActiveConfig = NoActiveConfig
- setConfigWhich :: forall pr cr s α. (AncestorRegion pr (RegionT s cr), MonadControlIO cr) => RegionalDeviceHandle pr -> (ConfigDesc -> Bool) -> (forall sCfg. ConfigHandle sCfg -> RegionT s cr α) -> RegionT s cr α
- data Interface sCfg
- getInterfaces :: ConfigHandle sCfg -> [Interface sCfg]
- data RegionalInterfaceHandle sCfg r
- claim :: forall pr sCfg s. MonadControlIO pr => Interface sCfg -> RegionT s pr (RegionalInterfaceHandle sCfg (RegionT s pr))
- withInterface :: forall pr sCfg α. MonadControlIO pr => Interface sCfg -> (forall s. RegionalInterfaceHandle sCfg (RegionT s pr) -> RegionT s pr α) -> pr α
- withInterfaceWhich :: forall pr sCfg α. MonadControlIO pr => ConfigHandle sCfg -> (Interface -> Bool) -> (forall s. RegionalInterfaceHandle sCfg (RegionT s pr) -> RegionT s pr α) -> pr α
- data Alternate sCfg r
- getAlternates :: RegionalInterfaceHandle sCfg r -> [Alternate sCfg r]
- data AlternateHandle sAlt r
- setAlternate :: forall pr cr s sCfg α. (AncestorRegion pr (RegionT s cr), MonadControlIO cr) => Alternate sCfg pr -> (forall sAlt. AlternateHandle sAlt pr -> RegionT s cr α) -> RegionT s cr α
- useActiveAlternate :: forall pr cr s sCfg α. (AncestorRegion pr (RegionT s cr), MonadControlIO cr) => RegionalInterfaceHandle sCfg pr -> (forall sAlt. AlternateHandle sAlt pr -> RegionT s cr α) -> RegionT s cr α
- setAlternateWhich :: forall pr cr sCfg s α. (AncestorRegion pr (RegionT s cr), MonadControlIO cr) => RegionalInterfaceHandle sCfg pr -> (InterfaceDesc -> Bool) -> (forall sAlt. AlternateHandle sAlt pr -> RegionT s cr α) -> RegionT s cr α
- data Endpoint transDir transType sAlt r
- getEndpoints :: forall transDir transType sAlt r. AlternateHandle sAlt r -> TransferDirection transDir -> TransferType transType -> [Endpoint transDir transType sAlt r]
- getEndpoints' :: forall transDir transType sAlt r. MkTransferDirection transDir => MkTransferType transType => AlternateHandle sAlt r -> [Endpoint transDir transType sAlt r]
- data TransferDirection transDir where
- Out :: TransferDirection Out
- In :: TransferDirection In
- data Out
- data In
- class MkTransferDirection transDir where
- mkTransferDirection :: TransferDirection transDir
- data TransferType transType where
- data Control
- data Isochronous
- data Bulk
- data Interrupt
- class MkTransferType transType where
- mkTransferType :: TransferType transType
- clearHalt :: (AncestorRegion pr cr, MonadIO cr) => Endpoint transDir transType sAlt pr -> cr ()
- type ReadAction r = Size -> Timeout -> r (ByteString, Status)
- type WriteAction r = ByteString -> Timeout -> r (Size, Status)
- class ReadEndpoint transType where
- readEndpoint :: (AncestorRegion pr cr, MonadIO cr) => Endpoint In transType sAlt pr -> ReadAction cr
- class WriteEndpoint transType where
- writeEndpoint :: (AncestorRegion pr cr, MonadIO cr) => Endpoint Out transType sAlt pr -> WriteAction cr
- class EnumReadEndpoint transType where
- enumReadEndpoint :: (AncestorRegion pr cr, MonadControlIO cr, ReadableChunk s Word8, NullPoint s) => Endpoint In transType sAlt pr -> Size -> Timeout -> Enumerator s cr α
- readIsochronousEndpoint :: (AncestorRegion pr cr, MonadIO cr) => Endpoint In Isochronous sAlt pr -> [Size] -> Timeout -> cr [ByteString]
- writeIsochronousEndpoint :: (AncestorRegion pr cr, MonadIO cr) => Endpoint Out Isochronous sAlt pr -> [ByteString] -> Timeout -> cr [Size]
- enumReadIsochronousEndpoint :: forall s pr cr sAlt α. (ReadableChunk s Word8, AncestorRegion pr cr, MonadControlIO cr) => Endpoint In Isochronous sAlt pr -> [Size] -> Timeout -> Enumerator [s] cr α
- type ControlAction α = RequestType -> Recipient -> Request -> Value -> Index -> α
- data RequestType
- control :: forall pr cr. (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> ControlAction (Timeout -> cr ())
- readControl :: forall pr cr. (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> ControlAction (ReadAction cr)
- readControlExact :: forall pr cr. (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> ControlAction (ReadExactAction cr)
- writeControl :: forall pr cr. (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> ControlAction (WriteAction cr)
- writeControlExact :: forall pr cr. (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> ControlAction (WriteExactAction cr)
- getLanguages :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> cr [LangId]
- getStrDesc :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> StrIx -> LangId -> Int -> cr Text
- getStrDescFirstLang :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> StrIx -> Int -> cr Text
- kernelDriverActive :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> InterfaceNumber -> cr Bool
- detachKernelDriver :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> InterfaceNumber -> cr ()
- attachKernelDriver :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> InterfaceNumber -> cr ()
- withDetachedKernelDriver :: (AncestorRegion pr (RegionT s cr), MonadControlIO cr) => RegionalDeviceHandle pr -> InterfaceNumber -> RegionT s cr α -> RegionT s cr α
USB devices as scarce resources
Note that this module re-exports the Control.Monad.Trans.Region
module
from the regions
package which allows you to run regions using runRegionT
and duplicate a RegionalDeviceHandle
to a parent region using dup
.
module Control.Monad.Trans.Region
Regional device handles
data RegionalDeviceHandle r Source
A regional handle to an opened USB device.
A regional handle to an opened USB device can be created by applying
openDevice
or withDevice
to the USB device you wish to open.
Note that you can also duplicate a regional device handle by applying dup
to it.
openDevice :: MonadControlIO pr => Device -> RegionT s pr (RegionalDeviceHandle (RegionT s pr))Source
Open a device and obtain a regional device handle. The device is automatically closed when the region terminates.
This is a non-blocking function; no requests are sent over the bus.
Exceptions:
-
NoMemException
if there is a memory allocation failure. -
AccessException
if the user has insufficient permissions. -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
withDevice :: MonadControlIO pr => Device -> (forall s. RegionalDeviceHandle (RegionT s pr) -> RegionT s pr α) -> pr αSource
Convenience function which opens the device, applies the given continuation function to the resulting regional device handle and runs the resulting region.
:: forall pr α . MonadControlIO pr | |
=> Ctx | |
-> (DeviceDesc -> Bool) | Predicate on the device descriptor. |
-> (forall s. RegionalDeviceHandle (RegionT s pr) -> RegionT s pr α) | Continuation function |
-> pr α |
Convenience function which finds the first device attached to the system which satisfies the given predicate on its descriptor, then opens that device and applies the given continuation function to the resulting device handle.
Exceptions:
-
NotFoundException
if no device is found which satisfies the given predicate. -
NoMemException
if there is a memory allocation failure. -
AccessException
if the user has insufficient permissions. -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
getDevice :: RegionalDeviceHandle r -> DeviceSource
Convenience function for retrieving the device from the given regional handle.
Getting descriptors
class GetDescriptor α desc | α -> desc, desc -> α whereSource
GetDescriptor Device DeviceDesc | |
GetDescriptor (Interface sCfg) Interface | |
GetDescriptor (Config r) ConfigDesc | |
GetDescriptor (Alternate sIntrf r) InterfaceDesc | |
GetDescriptor (Endpoint transDir transType sAlt r) EndpointDesc |
Resetting devices
resetDevice :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> cr ()Source
Perform a USB port reset to reinitialize a device. The system will attempt to restore the previous configuration and alternate settings after the reset has completed.
Note the constraint: pr `AncestorRegion` cr
. This allows this function to be
executed in any child region cr
of the parent region pr
in which the given
regional handle was created.
You can only reset a device when all computations passed to setConfig
,
useActiveConfig
and setConfigWhich
have been terminated. If you call
resetDevice
and such a computation is still running a SettingAlreadySet
exception is thrown.
If the reset fails, the descriptors change, or the previous state cannot be
restored, the device will appear to be disconnected and reconnected. This means
that the device handle is no longer valid (you should close it) and rediscover
the device. A NotFoundException
is raised to indicate that this is the case.
TODO: Think about how to handle the implications of the the previous paragraph!
This is a blocking function which usually incurs a noticeable delay.
Exceptions:
-
SettingAlreadySet
if a configuration has been set usingsetConfig
,useActiveConfig
andsetConfigWhich
. -
NotFoundException
if re-enumeration is required, or if the device has been disconnected. - Another
USBException
.
Configurations
getConfigs :: RegionalDeviceHandle r -> [Config r]Source
Retrieve the supported configurations from the given regional handle.
Note that the configuration is parameterized by the same region r
in which the
regional handle was created. This ensures you can never use a configuration
outside that region.
Setting configurations
data ConfigHandle sCfg Source
A handle to an active Config
which you can get using: setConfig
, useActiveConfig
or setConfigWhich
.
The type variable sCfg
is used to ensure that
you can't return this handle from these functions.
:: forall pr cr s α . (AncestorRegion pr (RegionT s cr), MonadControlIO cr) | |
=> Config pr | The configuration you wish to set. |
-> (forall sCfg. ConfigHandle sCfg -> RegionT s cr α) | Continuation function. |
-> RegionT s cr α |
Set the active configuration for a device and then apply the given continuation function to the resulting configuration handle.
USB devices support multiple configurations of which only one can be active at
any given time. When a configuration is set using setConfig
, useActiveConfig
or setConfigWhich
no threads may set a new configuration until the computation
passed to these functions terminates. If you do try to set one, a
SettingAlreadySet
exception will be thrown.
The operating system may or may not have already set an active configuration on
the device. It is up to your application to ensure the correct configuration is
selected before you attempt to claim interfaces and perform other operations. If
you want to use the current active configuration: useActiveConfig
.
If you call this function on a device already configured with the selected
configuration, then this function will act as a lightweight device reset: it
will issue a SET_CONFIGURATION
request using the current configuration, causing
most USB-related device state to be reset (altsetting reset to zero, endpoint
halts cleared, toggles reset).
You cannot change/reset configuration if other applications or drivers have claimed interfaces.
This is a blocking function.
Exceptions:
-
SettingAlreadySet
if a configuration has already been set usingsetConfig
,useActiveConfig
orsetConfigWhich
. -
BusyException
if interfaces are currently claimed. -
NoDeviceException
if the device has been disconnected - Another
USBException
.
data SettingAlreadySet Source
This exception can be thrown in:
to indicate that the device was already configured with a setting.
:: forall pr cr s α . (AncestorRegion pr (RegionT s cr), MonadControlIO cr) | |
=> RegionalDeviceHandle pr | Regional handle to the device from which you want to use the active configuration. |
-> (forall sCfg. ConfigHandle sCfg -> RegionT s cr α) | Continuation function |
-> RegionT s cr α |
Apply the given continuation function to the configuration handle of the current active configuration of the given device handle.
This function needs to determine the current active configuration. This information may be cached by the operating system. If it isn't cached this function will block while a control transfer is submitted to retrieve the information.
Exceptions:
-
NoActiveConfig
if the device is not configured. -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
data NoActiveConfig Source
This exception can be thrown in useActiveConfig
to indicate that the
device is currently not configured.
:: forall pr cr s α . (AncestorRegion pr (RegionT s cr), MonadControlIO cr) | |
=> RegionalDeviceHandle pr | Regional handle to the device for which you want to set a configuration. |
-> (ConfigDesc -> Bool) | Predicate on the configuration descriptor. |
-> (forall sCfg. ConfigHandle sCfg -> RegionT s cr α) | Continuation function. |
-> RegionT s cr α |
Convenience function which finds the first configuration of the given device handle which satisfies the given predicate on its descriptor, then sets that configuration and applies the given function to the resulting configuration handle.
This function calls setConfig
so do see its documentation.
Exceptions:
-
SettingAlreadySet
if a configuration has already been set usingsetConfig
,useActiveConfig
orsetConfigWhich
. -
NotFoundException
if no configuration is found that satisfies the given predicate. -
BusyException
if interfaces are currently claimed. -
NoDeviceException
if the device has been disconnected - Another
USBException
.
Interfaces
A supported interface of a configuration
which you can retrieve using getInterfaces
.
To retrieve the Interface
descriptors of an interface use getDesc
.
GetDescriptor (Interface sCfg) Interface |
getInterfaces :: ConfigHandle sCfg -> [Interface sCfg]Source
Retrieve the supported interfaces from the configuration handle.
Note that the interface is parameterized by the sCfg
of the configuration
handle it is derived from. This ensures that it can never be returned from the
functions that created this configuration handle: setConfig
, useActiveConfig
and setConfigWhich
.
The latter is useful because outside those functions the active configuration may change. If at that moment you still have an interface of the old configuration claiming it would be an error.
Claiming interfaces
data RegionalInterfaceHandle sCfg r Source
A regional handle to a claimed interface.
A regional handle to a claimed interface can be created
by applying claim
or withInterface
to the interface you wish to claim.
Dup (RegionalInterfaceHandle sCfg) |
:: forall pr sCfg s . MonadControlIO pr | |
=> Interface sCfg | Interface you wish to claim |
-> RegionT s pr (RegionalInterfaceHandle sCfg (RegionT s pr)) |
Claim the given interface in the region. When the region terminates the interface is released automatically.
Note that it is allowed to claim an already-claimed interface.
Claiming of interfaces is a purely logical operation; it does not cause any requests to be sent over the bus. Interface claiming is used to instruct the underlying operating system that your application wishes to take ownership of the interface.
This is a non-blocking function.
Exceptions:
-
BusyException
if another program or driver has claimed the interface. -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
:: forall pr sCfg α . MonadControlIO pr | |
=> Interface sCfg | The interface you wish to claim. |
-> (forall s. RegionalInterfaceHandle sCfg (RegionT s pr) -> RegionT s pr α) | Continuation function. |
-> pr α |
:: forall pr sCfg α . MonadControlIO pr | |
=> ConfigHandle sCfg | Handle to a configuration of which you want to claim an interface. |
-> (Interface -> Bool) | Predicate on the interface descriptors. |
-> (forall s. RegionalInterfaceHandle sCfg (RegionT s pr) -> RegionT s pr α) | Continuation function. |
-> pr α |
Convenience function which finds the first interface of the given configuration handle which satisfies the given predicate on its descriptors, then claims that interfaces and applies the given continuation function to the resulting regional handle.
Exceptions:
-
NotFoundException
if no interface was found that satisfies the fiven predicate. -
BusyException
if another program or driver has claimed the interface. -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
Alternates
A supported Interface
alternate setting
which you can retrieve using getAlternates
.
Dup (Alternate sCfg) | |
GetDescriptor (Alternate sIntrf r) InterfaceDesc |
getAlternates :: RegionalInterfaceHandle sCfg r -> [Alternate sCfg r]Source
Retrieve the supported alternate settings from the given interface handle.
Note that the alternate setting is parameterized by the same type variables as the interface handle. This ensures you can never use an alternate setting outside the region in which the interface handle was created.
Setting alternates
data AlternateHandle sAlt r Source
A handle to a setted alternate setting.
You get a handle to an alternate using
setAlternate
, useActiveAlternate
or setAlternateWhich
.
The type variable sAlt
is used to ensure that
you can't return this handle from these functions.
:: forall pr cr s sCfg α . (AncestorRegion pr (RegionT s cr), MonadControlIO cr) | |
=> Alternate sCfg pr | The alternate you wish to set. |
-> (forall sAlt. AlternateHandle sAlt pr -> RegionT s cr α) | Continuation function. |
-> RegionT s cr α |
Activate an alternate setting for an interface and then apply the given continuation function to the resulting alternate handle.
Simillary to configurations, interfaces support multiple alternate settings of
which only one can be active at any given time. When an alternate is set using
setAlternate
, useActiveAlternate
or setAlternateWhich
no threads may set a
new alternate until the computation passed to these functions terminates. If you
do try to set one a SettingAlreadySet
exception will be thrown.
The operating system has always set an interface in one of the available
alternates. If you want to use the current active alternate:
useActiveAlternate
.
This is a blocking function.
Exceptions:
-
NoDeviceException
if the device has been disconnected. -
SettingAlreadySet
if an alternate has already been set usingsetAlternate
,useActiveAlternate
orsetAlternateWhich
. - Another
USBException
.
:: forall pr cr s sCfg α . (AncestorRegion pr (RegionT s cr), MonadControlIO cr) | |
=> RegionalInterfaceHandle sCfg pr | Regional handle to the interface from which you want to use the active alternate. |
-> (forall sAlt. AlternateHandle sAlt pr -> RegionT s cr α) | Continuation function. |
-> RegionT s cr α |
Apply the given function to the alternate handle of the current active alternate of the given interface handle.
To determine the current active alternate this function will block while a control transfer is submitted to retrieve the information.
Note that unlike configurations an interface is always set in one of the
available alternates, so unlike useActiveConfig
this function will never throw
an exception like NoActiveConfig
.
Exceptions:
-
NoDeviceException
if the device has been disconnected. - Another
USBException
.
:: forall pr cr sCfg s α . (AncestorRegion pr (RegionT s cr), MonadControlIO cr) | |
=> RegionalInterfaceHandle sCfg pr | Regional handle to the interface for which you want to set an alternate. |
-> (InterfaceDesc -> Bool) | Predicate on the interface descriptor. |
-> (forall sAlt. AlternateHandle sAlt pr -> RegionT s cr α) | Continuation function |
-> RegionT s cr α |
Convenience function which finds the first alternate of the given interface handle which satisfies the given predicate on its descriptor, then sets that alternate and applies the given function to the resulting alternate handle.
This function calls setAlternate
so do see its documentation.
Exceptions:
-
NotFoundException
if no alternate is found that satisfies the given predicate. -
NoDeviceException
if the device has been disconnected. -
SettingAlreadySet
if an alternate has already been set usingsetAlternate
,useActiveAlternate
orsetAlternateWhich
. - Another
USBException
.
Endpoints
data Endpoint transDir transType sAlt r Source
I/O operations on endpoints are type-safe. You can only read from an
endpoint with an In
transfer direction and you can only write to an endpoint
with an Out
transfer direction.
Reading and writing also have different implementations for the different
endpoint transfer types like: Bulk
and Interrupt
. I/O with endpoints of
other transfer types like Control
and Isochronous
is not possible.
This type lifts the transfer direction and transfer type information to the
type-level so that I/O operations like readEndpoint
and writeEndpoint
can
specify which endpoints they support.
You can retrieve the endpoints of an alternate using getEndpoints
.
GetDescriptor (Endpoint transDir transType sAlt r) EndpointDesc |
:: forall transDir transType sAlt r . | |
=> AlternateHandle sAlt r | Handle to the alternate from which you want to retrieve its endpoints. |
-> TransferDirection transDir | Filter all endpoints which have this transfer direction. |
-> TransferType transType | Filter all endpoints which have this transfer type. |
-> [Endpoint transDir transType sAlt r] |
Retrieve all the endpoints from the given alternate handle which are of the given transfer direction and transfer type.
getEndpoints' :: forall transDir transType sAlt r. MkTransferDirection transDir => MkTransferType transType => AlternateHandle sAlt r -> [Endpoint transDir transType sAlt r]Source
Similar to getEndpoints
but will retrieve the endpoints based on the
inferred type of transfer direction and transfer type.
Note that:
getEndpoints' altHndl =
.
getEndpoints
altHndl mkTransferDirection
mkTransferType
Transfer directions
data TransferDirection transDir whereSource
Out :: TransferDirection Out | |
In :: TransferDirection In |
class MkTransferDirection transDir whereSource
mkTransferDirection :: TransferDirection transDirSource
An overloaded constructor function for transfer directions.
Transfer types
data TransferType transType whereSource
class MkTransferType transType whereSource
mkTransferType :: TransferType transTypeSource
An overloaded constructor function for transfer types.
Endpoint I/O
clearHalt :: (AncestorRegion pr cr, MonadIO cr) => Endpoint transDir transType sAlt pr -> cr ()Source
Clear the halt/stall condition for an endpoint.
Endpoints with halt status are unable to receive or transmit data until the halt condition is stalled.
You should cancel all pending transfers before attempting to clear the halt condition.
This is a blocking function.
Exceptions:
-
NoDeviceException
if the device has been disconnected. - Another
USBException
.
type ReadAction r = Size -> Timeout -> r (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 action which, when executed,
performs the actual read and returns the bytestring that was read paired with an
indication if the transfer timed out.
type WriteAction r = ByteString -> Timeout -> r (Size, Status)Source
Handy type synonym for write transfers.
A WriteAction
is a function which takes the bytestring to write and a
timeout. The function returns an action which, when exectued, returns the number
of bytes that were actually written paired with an indication if the transfer
timed out.
Bulk and interrupt transfers
class ReadEndpoint transType whereSource
Class of transfer types that support reading.
readEndpoint :: (AncestorRegion pr cr, MonadIO cr) => Endpoint In transType sAlt pr -> ReadAction crSource
Read bytes from an In
endpoint
with either a Bulk
or Interrupt
transfer type.
Exceptions:
-
PipeException
if the endpoint halted. -
OverflowException
if the device offered more data, see Packets and overflows in the libusb documentation: http://libusb.sourceforge.net/api-1.0/packetoverflow.html. -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
class WriteEndpoint transType whereSource
Class of transfer types that support writing
writeEndpoint :: (AncestorRegion pr cr, MonadIO cr) => Endpoint Out transType sAlt pr -> WriteAction crSource
Write bytes to an Out
endpoint
with either a Bulk
or Interrupt
transfer type.
Exceptions:
-
PipeException
if the endpoint halted. -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
class EnumReadEndpoint transType whereSource
Class of transfer types that support enumeration.
:: (AncestorRegion pr cr, MonadControlIO cr, ReadableChunk s Word8, NullPoint s) | |
=> Endpoint In transType sAlt pr | |
-> Size | Chunk size. A good value for this would be
the |
-> Timeout | Timeout (in milliseconds) that this function should wait for each chunk before giving up due to no response being received. For no timeout, use value 0. |
-> Enumerator s cr α |
Isochronous transfers
WARNING: You need to enable the threaded runtime (-threaded
) when using
the isochronous functions. They throw a runtime error otherwise!
:: (AncestorRegion pr cr, MonadIO cr) | |
=> Endpoint In Isochronous sAlt pr | |
-> [Size] | Sizes of isochronous packets |
-> Timeout | |
-> cr [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:
-
PipeException
if the endpoint halted. -
OverflowException
if the device offered more data, see Packets and overflows in thelibusb
documentation: http://libusb.sourceforge.net/api-1.0/packetoverflow.html. -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
writeIsochronousEndpointSource
:: (AncestorRegion pr cr, MonadIO cr) | |
=> Endpoint Out Isochronous sAlt pr | |
-> [ByteString] | Sizes of isochronous packets |
-> Timeout | |
-> cr [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:
-
PipeException
if the endpoint halted. -
OverflowException
if the device offered more data, see Packets and overflows in thelibusb
documentation: http://libusb.sourceforge.net/api-1.0/packetoverflow.html. -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
enumReadIsochronousEndpoint :: forall s pr cr sAlt α. (ReadableChunk s Word8, AncestorRegion pr cr, MonadControlIO cr) => Endpoint In Isochronous sAlt pr -> [Size] -> Timeout -> Enumerator [s] cr αSource
Iteratee enumerator for reading isochronous endpoints.
WARNING: You need to enable the threaded runtime (-threaded
) for this
function to work correctly. It throws a runtime error otherwise!
Control transfers
type ControlAction α = RequestType -> Recipient -> Request -> Value -> Index -> αSource
Handy type synonym that names the parameters of a control transfer.
data RequestType Source
Control transfers can have three request types: Standard
, Class
and
Vendor
. We disallow Standard
requests however because with them you can
destroy the safety guarantees that this module provides.
control :: forall pr cr. (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> ControlAction (Timeout -> cr ())Source
Perform a USB control request that does not transfer data.
Exceptions:
-
TimeoutException
if the transfer timed out. -
PipeException
if the control request was not supported by the device -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
readControl :: forall pr cr. (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> ControlAction (ReadAction cr)Source
Perform a USB control read.
Exceptions:
-
PipeException
if the control request was not supported by the device -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
readControlExact :: forall pr cr. (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> ControlAction (ReadExactAction cr)Source
A convenience function similar to readControl
which checks if the
specified number of bytes to read were actually read.
Throws an IOException
if this is not the case.
writeControl :: forall pr cr. (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> ControlAction (WriteAction cr)Source
Perform a USB control write.
Exceptions:
-
PipeException
if the control request was not supported by the device -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
writeControlExact :: forall pr cr. (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> ControlAction (WriteExactAction cr)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.
String descriptors
getLanguages :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> cr [LangId]Source
Retrieve a list of supported languages.
This function may throw USBException
s.
:: (AncestorRegion pr cr, MonadIO cr) | |
=> RegionalDeviceHandle pr | |
-> StrIx | |
-> LangId | |
-> Int | Maximum number of characters in the requested string. An
|
-> cr Text |
Retrieve a string descriptor from a device.
This function may throw USBException
s.
TODO: The following can be made more type-safe!
When I call getStrDesc
I would like the type system to guarantee that the
given StrIx
and LangId
actually belong to the given Handle
. In other
words I would like to get a type error when they are some arbitrary number or
come from another device.
:: (AncestorRegion pr cr, MonadIO cr) | |
=> RegionalDeviceHandle pr | |
-> StrIx | |
-> Int | Maximum number of characters in the requested
string. An |
-> cr Text |
Retrieve a string descriptor from a device using the first supported language.
This function may throw USBException
s.
USB kernel drivers
kernelDriverActive :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> InterfaceNumber -> cr BoolSource
Determine if a kernel driver is active on an interface.
If a kernel driver is active, you cannot claim the interface, and libusb will be unable to perform I/O.
Exceptions:
-
NoDeviceException
if the device has been disconnected. - Another
USBException
.
detachKernelDriver :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> InterfaceNumber -> cr ()Source
Detach a kernel driver from an interface.
If successful, you will then be able to claim the interface and perform I/O.
Exceptions:
-
NotFoundException
if no kernel driver was active. -
InvalidParamException
if the interface does not exist. -
NoDeviceException
if the device has been disconnected. - Another
USBException
.
attachKernelDriver :: (AncestorRegion pr cr, MonadIO cr) => RegionalDeviceHandle pr -> InterfaceNumber -> cr ()Source
Re-attach an interface's kernel driver, which was previously
detached using detachKernelDriver
.
Exceptions:
-
NotFoundException
if no kernel driver was active. -
InvalidParamException
if the interface does not exist. -
NoDeviceException
if the device has been disconnected. -
BusyException
if the driver cannot be attached because the interface is claimed by a program or driver. - Another
USBException
.
withDetachedKernelDriver :: (AncestorRegion pr (RegionT s cr), MonadControlIO cr) => RegionalDeviceHandle pr -> InterfaceNumber -> RegionT s cr α -> RegionT s cr αSource
If a kernel driver is active on the specified interface the driver is detached and the given action is executed. If the action terminates, whether by normal termination or by raising an exception, the kernel driver is attached again. If a kernel driver is not active on the specified interface the action is just executed.
Exceptions:
-
NoDeviceException
if the device has been disconnected. - Another
USBException
.