#if __GLASGOW_HASKELL__ >= 704
#endif
module System.USB.IO.StandardDeviceRequests
( setHalt
, setConfig, getConfig
, clearRemoteWakeup
, setRemoteWakeup
, setStandardTestMode, TestMode(..)
, getInterfaceAltSetting
, getDeviceStatus
, getEndpointStatus
, setDeviceAddress
, synchFrame, FrameNumber
) where
import Data.Bits ( testBit, shiftL )
import Data.Bool ( Bool )
import Data.Data ( Data )
import Data.Eq ( Eq, (==) )
import Data.Function ( ($), (.) )
import Data.Functor ( fmap )
import Data.Maybe ( Maybe(Nothing, Just), maybe )
import Data.Typeable ( Typeable )
import Data.Word ( Word8, Word16 )
import Prelude ( (+), (*), fromIntegral, Enum )
import System.IO ( IO )
import Text.Read ( Read )
import Text.Show ( Show )
#if __GLASGOW_HASKELL__ < 700
import Prelude ( fromInteger )
import Data.Eq ( (==) )
#endif
import qualified Data.ByteString as B ( ByteString, head, unpack )
import Bindings.Libusb ( c'LIBUSB_REQUEST_SET_FEATURE
, c'LIBUSB_REQUEST_SET_CONFIGURATION
, c'LIBUSB_REQUEST_GET_CONFIGURATION
, c'LIBUSB_REQUEST_CLEAR_FEATURE
, c'LIBUSB_REQUEST_GET_INTERFACE
, c'LIBUSB_REQUEST_GET_STATUS
, c'LIBUSB_REQUEST_SET_ADDRESS
, c'LIBUSB_REQUEST_SYNCH_FRAME
)
import System.USB.DeviceHandling ( DeviceHandle
, ConfigValue
, InterfaceNumber
, InterfaceAltSetting
)
#if __HADDOCK__
import qualified System.USB.DeviceHandling as USB ( setConfig, getConfig )
#endif
import System.USB.Descriptors ( EndpointAddress
, DeviceStatus(..)
)
import System.USB.IO ( Timeout
, RequestType(Standard)
, Recipient( ToDevice
, ToInterface
, ToEndpoint
)
, Value
, control, readControlExact
)
import System.USB.Internal ( marshalEndpointAddress )
import Utils ( genFromEnum )
haltFeature, remoteWakeupFeature, testModeFeature :: Value
haltFeature = 0
remoteWakeupFeature = 1
testModeFeature = 2
setHalt :: DeviceHandle -> EndpointAddress -> (Timeout -> IO ())
setHalt devHndl endpointAddr = control devHndl
Standard
ToEndpoint
c'LIBUSB_REQUEST_SET_FEATURE
haltFeature
(marshalEndpointAddress endpointAddr)
setConfig :: DeviceHandle -> Maybe ConfigValue -> (Timeout -> IO ())
setConfig devHndl mbConfigValue = control devHndl
Standard
ToDevice
c'LIBUSB_REQUEST_SET_CONFIGURATION
(marshal mbConfigValue)
0
where
marshal :: Maybe ConfigValue -> Value
marshal = maybe 0 fromIntegral
getConfig :: DeviceHandle -> (Timeout -> IO (Maybe ConfigValue))
getConfig devHndl = fmap (unmarshal . B.head)
. readControlExact devHndl
Standard
ToDevice
c'LIBUSB_REQUEST_GET_CONFIGURATION
0
0
1
where
unmarshal :: Word8 -> Maybe ConfigValue
unmarshal 0 = Nothing
unmarshal n = Just $ fromIntegral n
clearRemoteWakeup :: DeviceHandle -> (Timeout -> IO ())
clearRemoteWakeup devHndl =
control devHndl
Standard
ToDevice
c'LIBUSB_REQUEST_CLEAR_FEATURE
remoteWakeupFeature
0
setRemoteWakeup :: DeviceHandle -> (Timeout -> IO ())
setRemoteWakeup devHndl =
control devHndl
Standard
ToDevice
c'LIBUSB_REQUEST_SET_FEATURE
remoteWakeupFeature
0
setStandardTestMode :: DeviceHandle -> TestMode -> (Timeout -> IO ())
setStandardTestMode devHndl testMode =
control devHndl
Standard
ToDevice
c'LIBUSB_REQUEST_SET_FEATURE
testModeFeature
((genFromEnum testMode + 1) `shiftL` 8)
data TestMode = Test_J
| Test_K
| Test_SE0_NAK
| Test_Packet
| Test_Force_Enable
deriving (Eq, Show, Read, Enum, Data, Typeable)
getInterfaceAltSetting :: DeviceHandle -> InterfaceNumber -> (Timeout -> IO InterfaceAltSetting)
getInterfaceAltSetting devHndl ifNum =
fmap B.head . readControlExact devHndl
Standard
ToInterface
c'LIBUSB_REQUEST_GET_INTERFACE
0
(fromIntegral ifNum)
1
getDeviceStatus :: DeviceHandle -> (Timeout -> IO DeviceStatus)
getDeviceStatus devHndl =
fmap (unmarshal . B.head) . readControlExact devHndl
Standard
ToDevice
c'LIBUSB_REQUEST_GET_STATUS
0
0
2
where
unmarshal :: Word8 -> DeviceStatus
unmarshal a = DeviceStatus { remoteWakeup = testBit a 1
, selfPowered = testBit a 0
}
getEndpointStatus :: DeviceHandle -> EndpointAddress -> (Timeout -> IO Bool)
getEndpointStatus devHndl endpointAddr =
fmap ((1 ==) . B.head) . readControlExact devHndl
Standard
ToEndpoint
c'LIBUSB_REQUEST_GET_STATUS
0
(marshalEndpointAddress endpointAddr)
2
setDeviceAddress :: DeviceHandle -> Word16 -> (Timeout -> IO ())
setDeviceAddress devHndl deviceAddr = control devHndl
Standard
ToDevice
c'LIBUSB_REQUEST_SET_ADDRESS
deviceAddr
0
synchFrame :: DeviceHandle -> EndpointAddress -> (Timeout -> IO FrameNumber)
synchFrame devHndl endpointAddr =
fmap unmarshal . readControlExact devHndl
Standard
ToEndpoint
c'LIBUSB_REQUEST_SYNCH_FRAME
0
(marshalEndpointAddress endpointAddr)
2
where
unmarshal :: B.ByteString -> FrameNumber
unmarshal bs = let [h, l] = B.unpack bs
in fromIntegral h * 256 + fromIntegral l
type FrameNumber = Word16