usb-1.3.0.5: 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.Misc

Contents

Description

This module provides miscellaneous functionality.

Synopsis

Capabilties of libusb

data Capability Source #

Capabilities supported by an instance of libusb on the current running platform.

Test if the loaded libusb library supports a given capability by calling hasCapability.

Constructors

HasCapability

The hasCapability API is available.

HasHotplug

Hotplug support is available on this platform.

HasHidAccess

The library can access HID devices without requiring user intervention.

Note that before being able to actually access an HID device, you may still have to call additional libusb functions such as detachKernelDriver.

SupportsDetachKernelDriver

The library supports detaching of the default USB driver, using detachKernelDriver, if one is set by the OS kernel.

Instances

Enum Capability Source # 
Eq Capability Source # 
Data Capability Source # 

Methods

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

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

toConstr :: Capability -> Constr #

dataTypeOf :: Capability -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Capability Source # 
Read Capability Source # 
Show Capability Source # 
Generic Capability Source # 

Associated Types

type Rep Capability :: * -> * #

type Rep Capability Source # 
type Rep Capability = D1 (MetaData "Capability" "System.USB.Base" "usb-1.3.0.5-4foKTDx9gBO9zEUKWldWNQ" False) ((:+:) ((:+:) (C1 (MetaCons "HasCapability" PrefixI False) U1) (C1 (MetaCons "HasHotplug" PrefixI False) U1)) ((:+:) (C1 (MetaCons "HasHidAccess" PrefixI False) U1) (C1 (MetaCons "SupportsDetachKernelDriver" PrefixI False) U1)))

hasCapability :: Ctx -> Capability -> Bool Source #

Check at runtime if the loaded libusb library has a given capability.

This call should be performed after newCtx, to ensure the backend has updated its capability set. For this reason you need to apply it to a Ctx.

Version of libusb

data LibusbVersion Source #

Structure providing the version of the libusb runtime.

Constructors

LibusbVersion 

Fields

Instances

Eq LibusbVersion Source # 
Data LibusbVersion Source # 

Methods

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

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

toConstr :: LibusbVersion -> Constr #

dataTypeOf :: LibusbVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Read LibusbVersion Source # 
Show LibusbVersion Source # 
Generic LibusbVersion Source # 

Associated Types

type Rep LibusbVersion :: * -> * #

type Rep LibusbVersion Source # 

libusbVersion :: LibusbVersion Source #

Returns the version (major, minor, micro, nano and rc) of the loaded libusb library.

toVersion :: LibusbVersion -> Version Source #

Convert a LibusbVersion to a Version for easy comparison.