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

Description

 

Synopsis

Documentation

data USBException Source #

Type of USB exceptions.

Constructors

IOException String

Input/output exception.

InvalidParamException

Invalid parameter.

AccessException

Access denied (insufficient permissions). It may help to run your program with elevated privileges or change the permissions of your device using something like udev.

NoDeviceException

No such device (it may have been disconnected).

NotFoundException

Entity not found.

BusyException

Resource busy.

TimeoutException

Operation timed out.

OverflowException

If the device offered to much data. See Packets and overflows in the libusb documentation.

PipeException

Pipe exception.

InterruptedException

System call interrupted (perhaps due to signal).

NoMemException

Insufficient memory.

NotSupportedException

Operation not supported or unimplemented on this platform. If possible, it's recommended the check if a certain operation is supported by using the hasCapability API.

OtherException

Other exception.

Instances

Eq USBException Source # 
Data USBException Source # 

Methods

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

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

toConstr :: USBException -> Constr #

dataTypeOf :: USBException -> DataType #

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

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

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

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

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

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

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

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

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

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

Read USBException Source # 
Show USBException Source # 
Generic USBException Source # 

Associated Types

type Rep USBException :: * -> * #

Exception USBException Source # 
type Rep USBException Source # 
type Rep USBException = D1 (MetaData "USBException" "System.USB.Base" "usb-1.3.0.5-4foKTDx9gBO9zEUKWldWNQ" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "IOException" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:+:) (C1 (MetaCons "InvalidParamException" PrefixI False) U1) (C1 (MetaCons "AccessException" PrefixI False) U1))) ((:+:) (C1 (MetaCons "NoDeviceException" PrefixI False) U1) ((:+:) (C1 (MetaCons "NotFoundException" PrefixI False) U1) (C1 (MetaCons "BusyException" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "TimeoutException" PrefixI False) U1) ((:+:) (C1 (MetaCons "OverflowException" PrefixI False) U1) (C1 (MetaCons "PipeException" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "InterruptedException" PrefixI False) U1) (C1 (MetaCons "NoMemException" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NotSupportedException" PrefixI False) U1) (C1 (MetaCons "OtherException" PrefixI False) U1)))))

incompleteReadException :: USBException Source #

IOException that is thrown when the number of bytes read doesn't equal the requested number.

incompleteWriteException :: USBException Source #

IOException that is thrown when the number of bytes written doesn't equal the requested number.