usb-1.2.0.1: Communicate with USB devices

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

System.USB.Internal

Contents

Description

This module is not intended for end users. It provides internal and unsafe functions used for extending this package.

Synopsis

Documentation

type C'TransferFunc = Ptr C'libusb_device_handle -> CUChar -> Ptr CUChar -> CInt -> Ptr CInt -> CUInt -> IO CInt Source

Handy type synonym for the libusb transfer functions.

convertUSBException :: (Num a, Eq a, Show a) => a -> USBException Source

Convert a C'libusb_error to a USBException. If the C'libusb_error is unknown an error is thrown.

unmarshalReleaseNumber :: Word16 -> ReleaseNumber Source

Unmarshal a a 16bit word as a release number. The 16bit word should be encoded as a Binary Coded Decimal using 4 bits for each of the 4 decimals.

unmarshalStrIx :: Word8 -> Maybe StrIx Source

Unmarshal an 8bit word to a string descriptor index. 0 denotes that a string descriptor is not available and unmarshals to Nothing.

Marshal and unmarshal endpoint addresses

The address should be encoded according to section 9.6.6 of the USB 2.0 specification.

marshalEndpointAddress :: (Bits a, Num a) => EndpointAddress -> a Source

Marshal an endpoint address so that it can be used by the libusb transfer functions.

unmarshalEndpointAddress :: Word8 -> EndpointAddress Source

Unmarshal an 8bit word as an endpoint address. This function is primarily used when unmarshalling USB descriptors.

Useful types and functions for asynchronous implementations

getWait :: DeviceHandle -> Maybe Wait Source

Checks if the system supports asynchronous I/O.

  • Nothing means asynchronous I/O is not supported so synchronous I/O should be used instead.
  • Just wait means that asynchronous I/O is supported. The wait function can be used to wait for submitted transfers.

type Wait = Timeout -> Lock -> Ptr C'libusb_transfer -> IO () Source

A function to wait for the termination of a submitted transfer.

allocaTransfer :: Int -> (Ptr C'libusb_transfer -> IO a) -> IO a Source

Allocate a transfer with the given number of isochronous packets and apply the function to the resulting pointer. The transfer is automatically freed when the function terminates (whether normally or by raising an exception).

A NoMemException may be thrown.

withCallback :: (Ptr C'libusb_transfer -> IO ()) -> (C'libusb_transfer_cb_fn -> IO a) -> IO a Source

Create a FunPtr to the given transfer callback function and pass it to the continuation function. The FunPtr is automatically freed when the continuation terminates (whether normally or by raising an exception).

pokeVector :: forall a. Storable a => Ptr a -> Vector a -> IO () Source

initIsoPacketDesc :: Size -> C'libusb_iso_packet_descriptor Source

An isochronous packet descriptor with all fields zero except for the length.

Locks

data Lock Source

A lock is in one of two states: "locked" or "unlocked".

Instances

newLock :: IO Lock Source

Create a lock in the "unlocked" state.

acquire :: Lock -> IO () Source

Acquires the Lock. Blocks if another thread has acquired the Lock.

acquire behaves as follows:

  • When the state is "unlocked" acquire changes the state to "locked".
  • When the state is "locked" acquire blocks until a call to release in another thread wakes the calling thread. Upon awakening it will change the state to "locked".

release :: Lock -> IO () Source

release changes the state to "unlocked" and returns immediately.

The behaviour is undefined when a lock in the "unlocked" state is released!

If there are any threads blocked on acquire the thread that first called acquire will be woken up.