usb-1.3.0.4: Communicate with USB devices

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

System.USB.Initialization

Contents

Description

This module provides functionality for initializing the usb library.

Synopsis

Documentation

data Ctx Source #

Abstract type representing a USB session.

The concept of individual sessions allows your program to use multiple threads that can independently use this library without interfering with eachother.

Sessions are created and initialized by newCtx and are automatically closed when they are garbage collected.

The only functions that receive a Ctx are hasCapability, setDebug and getDevices.

Instances

Eq Ctx Source # 

Methods

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

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

newCtx :: IO Ctx Source #

Create and initialize a new USB context.

This function may throw USBExceptions.

Note that the internal libusb event handling can return errors. These errors occur in the thread that is executing the event handling loop. newCtx will print these errors to stderr. If you need to handle the errors yourself (for example log them in an application specific way) please use newCtx'.

newCtx' :: (USBException -> IO ()) -> IO Ctx Source #

Like newCtx but enables you to specify the way errors should be handled that occur while handling libusb events.

Logging

setDebug :: Ctx -> Verbosity -> IO () Source #

Set message verbosity.

The default level is PrintNothing. This means no messages are ever printed. If you choose to increase the message verbosity level you must ensure that your application does not close the stdout/stderr file descriptors.

You are advised to set the debug level to PrintWarnings. Libusb is conservative with its message logging. Most of the time it will only log messages that explain error conditions and other oddities. This will help you debug your software.

The LIBUSB_DEBUG environment variable overrules the debug level set by this function. The message verbosity is fixed to the value in the environment variable if it is defined.

If libusb was compiled without any message logging, this function does nothing: you'll never get any messages.

If libusb was compiled with verbose debug message logging, this function does nothing: you'll always get messages from all levels.

data Verbosity Source #

Message verbosity

Constructors

PrintNothing

No messages are ever printed by the library.

PrintErrors

Error messages are printed to stderr.

PrintWarnings

Warning and error messages are printed to stderr.

PrintInfo

Informational messages are printed to stdout, warning and error messages are printed to stderr.

PrintDebug

Debug and informational messages are printed to stdout, warnings and errors to stderr.

Instances

Enum Verbosity Source # 
Eq Verbosity Source # 
Data Verbosity Source # 

Methods

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

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

toConstr :: Verbosity -> Constr #

dataTypeOf :: Verbosity -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Verbosity Source # 
Read Verbosity Source # 
Show Verbosity Source # 
Generic Verbosity Source # 

Associated Types

type Rep Verbosity :: * -> * #

type Rep Verbosity Source # 
type Rep Verbosity = D1 (MetaData "Verbosity" "System.USB.Base" "usb-1.3.0.4-ARqMLjBxKOGEgdhUYGAmNq" False) ((:+:) ((:+:) (C1 (MetaCons "PrintNothing" PrefixI False) U1) (C1 (MetaCons "PrintErrors" PrefixI False) U1)) ((:+:) (C1 (MetaCons "PrintWarnings" PrefixI False) U1) ((:+:) (C1 (MetaCons "PrintInfo" PrefixI False) U1) (C1 (MetaCons "PrintDebug" PrefixI False) U1))))