{-# LINE 1 "System/HIDAPI.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface, DeriveDataTypeable, DeriveGeneric #-}
module System.HIDAPI
( System.HIDAPI.init, exit, withHIDAPI
, enumerate, enumerateAll
, open, openPath, openDeviceInfo
, close
, System.HIDAPI.read
, System.HIDAPI.write
, System.HIDAPI.getFeatureReport
, System.HIDAPI.sendFeatureReport
, getSerialNumberString
, System.HIDAPI.error
, HIDAPIException(HIDAPIException)
, Device()
, DeviceInfo (..)
, DevicePath
, VendorID
, ProductID
, ReleaseNumber
, SerialNumber
, InterfaceNumber
) where
import Control.DeepSeq
import Control.DeepSeq.Generics
import Control.Exception
import Control.Monad
import Data.ByteString
import Data.ByteString.Internal (createAndTrim)
import Data.Maybe
import Data.Typeable
import Data.Data
import Foreign
import Foreign.C.Types
import Foreign.C.String
import GHC.Generics (Generic)
type Hid_Device_Ptr = Ptr ()
newtype Device = Device Hid_Device_Ptr
data DeviceInfoInternal = DeviceInfoInternal
{ _path :: CString
, _vendorId :: CUShort
, _productId :: CUShort
, _serialNumber :: CWString
, _releaseNumber :: CUShort
, _manufacturerString :: CWString
, _productString :: CWString
, _usagePage :: CUShort
, _usage :: CUShort
, _interfaceNumber :: CInt
, _next :: Ptr DeviceInfoInternal
} deriving (Show)
peekDeviceInfoInternal :: Ptr DeviceInfoInternal -> IO DeviceInfoInternal
peekDeviceInfoInternal p =
DeviceInfoInternal <$>
(\hsc_ptr -> peekByteOff hsc_ptr 0) p <*>
{-# LINE 63 "System/HIDAPI.hsc" #-}
(\hsc_ptr -> peekByteOff hsc_ptr 8) p <*>
{-# LINE 64 "System/HIDAPI.hsc" #-}
(\hsc_ptr -> peekByteOff hsc_ptr 10) p <*>
{-# LINE 65 "System/HIDAPI.hsc" #-}
(\hsc_ptr -> peekByteOff hsc_ptr 16) p <*>
{-# LINE 66 "System/HIDAPI.hsc" #-}
(\hsc_ptr -> peekByteOff hsc_ptr 24) p <*>
{-# LINE 67 "System/HIDAPI.hsc" #-}
(\hsc_ptr -> peekByteOff hsc_ptr 32) p <*>
{-# LINE 68 "System/HIDAPI.hsc" #-}
(\hsc_ptr -> peekByteOff hsc_ptr 40) p <*>
{-# LINE 69 "System/HIDAPI.hsc" #-}
(\hsc_ptr -> peekByteOff hsc_ptr 48) p <*>
{-# LINE 70 "System/HIDAPI.hsc" #-}
(\hsc_ptr -> peekByteOff hsc_ptr 50) p <*>
{-# LINE 71 "System/HIDAPI.hsc" #-}
(\hsc_ptr -> peekByteOff hsc_ptr 52) p <*>
{-# LINE 72 "System/HIDAPI.hsc" #-}
(\hsc_ptr -> peekByteOff hsc_ptr 56) p
{-# LINE 73 "System/HIDAPI.hsc" #-}
type DevicePath = String
type VendorID = Word16
type ProductID = Word16
type ReleaseNumber = Word16
type SerialNumber = String
type InterfaceNumber = Int
type ReportID = Word8
type ReportLength = Word16
type FeatureReport = (ReportID, ByteString)
data DeviceInfo = DeviceInfo
{ path :: DevicePath
, vendorId :: VendorID
, productId :: ProductID
, serialNumber :: Maybe SerialNumber
, releaseNumber :: ReleaseNumber
, manufacturerString :: Maybe String
, productString :: Maybe String
, usagePage :: Word16
, usage :: Word16
, interfaceNumber :: InterfaceNumber
} deriving (Show, Generic)
instance NFData DeviceInfo where rnf = genericRnf
peekOptString :: Ptr CWchar -> IO (Maybe String)
peekOptString p
| p == nullPtr = return Nothing
| otherwise = Just <$> peekCWString p
fromInternalDeviceInfo :: DeviceInfoInternal -> IO DeviceInfo
fromInternalDeviceInfo di = DeviceInfo <$>
peekCString (_path di) <*>
pure (fromIntegral $ _vendorId di) <*>
pure (fromIntegral $ _productId di) <*>
peekOptString (_serialNumber di) <*>
pure (fromIntegral $ _releaseNumber di) <*>
peekOptString (_manufacturerString di) <*>
peekOptString (_productString di) <*>
pure (fromIntegral $ _usagePage di) <*>
pure (fromIntegral $ _usage di) <*>
pure (fromIntegral $ _interfaceNumber di)
foreign import ccall unsafe "hidapi/hidapi.h hid_error"
hid_error :: Hid_Device_Ptr -> IO CWString
data HIDAPIException = HIDAPIException String String
deriving (Data, Typeable, Generic)
instance Show HIDAPIException where
showsPrec _ (HIDAPIException a c) = showString a . showString ": " . showString c
instance Exception HIDAPIException
instance NFData HIDAPIException where rnf = genericRnf
error :: Device -> IO (Maybe String)
error (Device devicePtr) = do
e <- hid_error devicePtr
if e == nullPtr
then return Nothing
else do
es <- peekCWString e
free e
return (Just es)
check :: Bool -> String -> String -> IO ()
check c msg reason = unless c $ throwIO $ HIDAPIException msg reason
checkWithHidError :: Bool -> Device -> String -> String -> IO ()
checkWithHidError c dev@(Device devPtr) msg defaultReason = unless c $ do
reason <- if devPtr /= nullPtr
then fromMaybe defaultReason <$> System.HIDAPI.error dev
else return defaultReason
throwIO $ HIDAPIException msg reason
foreign import ccall unsafe "hidapi/hidapi.h hid_init"
hid_init :: IO CInt
init :: IO ()
init = do
r <- hid_init
check (r == 0) "HIDAPI initialization failed" "hid_init /= 0"
foreign import ccall unsafe "hidapi/hidapi.h hid_exit"
hid_exit :: IO CInt
exit :: IO ()
exit = do
r <- hid_exit
check (r == 0) "HIDAPI shutdown failed" "hid_exit /= 0"
withHIDAPI :: IO a -> IO a
withHIDAPI = bracket_ System.HIDAPI.init exit
foreign import ccall unsafe "hidapi/hidapi.h hid_enumerate"
hid_enumerate :: CUShort -> CUShort -> IO (Ptr DeviceInfoInternal)
foreign import ccall unsafe "hidapi/hidapi.h hid_free_enumeration"
hid_free_enumeration :: Ptr DeviceInfoInternal -> IO ()
parseEnumeration :: Ptr DeviceInfoInternal -> IO [ DeviceInfo ]
parseEnumeration dip
| dip == nullPtr = return []
| otherwise = do
idi <- peekDeviceInfoInternal dip
di <- fromInternalDeviceInfo idi
dis <- parseEnumeration (_next idi)
return (di : dis)
enumerate :: Maybe VendorID -> Maybe ProductID -> IO [ DeviceInfo ]
enumerate m'vendorId m'productId = do
dip <- hid_enumerate (maybe 0 fromIntegral m'vendorId) (maybe 0 fromIntegral m'productId)
if dip == nullPtr
then return []
else do
dis <- parseEnumeration dip
hid_free_enumeration dip
return dis
enumerateAll :: IO [ DeviceInfo ]
enumerateAll = enumerate Nothing Nothing
foreign import ccall unsafe "hidapi/hidapi.h hid_open"
hid_open :: CUShort -> CUShort -> CWString -> IO Hid_Device_Ptr
open :: VendorID -> ProductID -> Maybe SerialNumber -> IO Device
open vendor_id product_id serial = do
let vid = fromIntegral vendor_id
let pid = fromIntegral product_id
dev@(Device dp) <- Device <$> case serial of
Nothing -> hid_open vid pid nullPtr
Just sn -> withCWString sn (hid_open vid pid)
checkWithHidError (dp /= nullPtr) dev "Device open (by vendor/product id) failed" "hid_open returned NULL"
return dev
foreign import ccall unsafe "hidapi/hidapi.h hid_open_path"
hid_open_path :: CString -> IO Hid_Device_Ptr
openPath :: DevicePath -> IO Device
openPath p = do
dev@(Device dp) <- Device <$> withCString p hid_open_path
checkWithHidError (dp /= nullPtr) dev "Device open (by path) failed" "hid_open returned NULL"
return dev
openDeviceInfo :: DeviceInfo -> IO Device
openDeviceInfo
= openPath . path
foreign import ccall unsafe "hidapi/hidapi.h hid_close"
close :: Device -> IO ()
foreign import ccall unsafe "hidapi/hidapi.h hid_read"
hid_read :: Device -> Ptr CChar -> CSize -> IO CInt
foreign import ccall unsafe "hidapi/hidapi.h hid_write"
hid_write :: Device -> Ptr CChar -> CSize -> IO CInt
foreign import ccall unsafe "hidapi/hidapi.h hid_get_feature_report"
hid_get_feature_report :: Device -> Ptr Word8 -> CSize -> IO CInt
foreign import ccall unsafe "hidapi/hidapi.h hid_send_feature_report"
hid_send_feature_report :: Device -> Ptr CChar -> CSize -> IO CInt
read :: Device -> Int -> IO ByteString
read dev n = allocaBytes n $ \b -> do
n' <- hid_read dev b (fromIntegral n)
checkWithHidError (n' /= -1) dev "Read failed" "hid_read returned -1"
packCStringLen ( b, fromIntegral n' )
write :: Device -> ByteString -> IO Int
write dev b = do
n' <- useAsCStringLen b $ \(cs, csLen) -> hid_write dev cs (fromIntegral csLen)
checkWithHidError (n' /= -1) dev "Write failed" "hid_write returned -1"
return $ fromIntegral n'
getFeatureReport :: Device -> ReportID -> ReportLength -> IO FeatureReport
getFeatureReport dev r l = do
b <- createAndTrim (toSize l) $ \cs -> do
_ <- pokeElemOff cs 0 (fromIntegral r)
n <- hid_get_feature_report dev cs (toSize l)
let n' = fromIntegral n
checkWithHidError (n' /= -1) dev "Write failed" "hid_get_feature_report returned -1"
return n'
return (Data.ByteString.head b, Data.ByteString.tail b)
where
toSize x = fromIntegral x + 1
sendFeatureReport :: Device -> ReportID -> ByteString -> IO Int
sendFeatureReport dev r d = do
let b = cons r d
n' <- useAsCStringLen b $ \(cs, csLen) -> hid_send_feature_report dev cs (fromIntegral csLen)
checkWithHidError (n' /= -1) dev "Write failed" "hid_send_feature_report returned -1"
return $ fromIntegral n'
foreign import ccall unsafe "hidapi/hidapi.h hid_get_serial_number_string"
hid_get_serial_number_string :: Device -> CWString -> CSize -> IO CInt
_SERIAL_NUMBER_MAX_LENGTH :: Int
_SERIAL_NUMBER_MAX_LENGTH = 32768
getSerialNumberString :: Device -> IO SerialNumber
getSerialNumberString dev = do
let bs = _SERIAL_NUMBER_MAX_LENGTH * sizeOf (undefined :: CWchar)
allocaBytes bs $ \b -> do
n' <- hid_get_serial_number_string dev b (fromIntegral _SERIAL_NUMBER_MAX_LENGTH)
checkWithHidError (n' /= -1) dev "Getting serial number failed" "hid_get_serial_number_string returned -1"
peekCWString b