System.USB.writeInterrupt -- confused by error message from type system

Hello, I am building a USB gadget with a HexWax ExpandIO-USB chip, here: http://hexwax.com/Products/expandIO-USB/ The device is working fine (lsusb shows it) and so I thought that in the name of continued training and doing things the hard way, that I would use Haskell to talk to it! I have only ever done USB with 'C' in the past and I am now stuck fighting the type checker. Here is my full code so far, it works in so far as it finds the device, opens and closes a connection and prints out some stuff. I then wanted to send four NUL bytes which elicits the same as a response according to the documentation but I cannot get it to compile. Apologies for it in advance, it's the journey you know, not the arrival, anyway, here it is... module Main where import Data.ByteString.Char8 as BS hiding (putStrLn) import Data.Word (Word16) import Data.Vector as V (filterM, null, (!)) --as V hiding ((++)) import System.USB import System.Environment -- hexwax expandIO-USB default code: "0b40:0132" main :: IO () main = do findHexWax (0xb40,0x132) >>= \hw -> case hw of Just dev -> hexwaxGo dev Nothing -> putStrLn "HexWax device not found" findHexWax :: (Word16,Word16) -> IO (Maybe Device) findHexWax (cVendor, cProd) = do usbCtx <- newCtx usbDevs <- getDevices usbCtx setDebug usbCtx PrintWarnings boards <- V.filterM (isTarget (cVendor, cProd)) usbDevs case V.null boards of True -> return Nothing False -> return $ Just $ boards!0 where isTarget :: (Word16, Word16) -> Device -> IO Bool isTarget (cVendor, cProd) dev = do info <- getDeviceDesc dev let vid = deviceVendorId info let vpr = deviceProductId info return $ ((vid, vpr) == (cVendor, cProd)) hexwaxGo :: Device -> IO () hexwaxGo dev = withDeviceHandle dev (testBoard dev) testBoard :: Device -> DeviceHandle -> IO () testBoard dev handle = do putStrLn $ "Inspecting device: \"" ++ (show dev) ++ "\"\n" -- write 0x00 0x00 0x00 0x00, get back same... let payload = pack "\x00\x00\x00\x00" let endPoint = EndpointAddress 0 Out action <- writeInterrupt handle endPoint (size, status) <- action payload 1000 return () And the error message: Prelude> :r [1 of 1] Compiling Main ( usb1.hs, interpreted ) usb1.hs:60:13: Couldn't match expected type `IO t0' with actual type `WriteAction' In the return type of a call of `writeInterrupt' Probable cause: `writeInterrupt' is applied to too few arguments In a stmt of a 'do' block: action <- writeInterrupt handle endPoint In the expression: do { putStrLn $ "Inspecting device: \"" ++ (show dev) ++ "\""; let payload = pack "\NUL\NUL\NUL\NUL"; let endPoint = EndpointAddress 0 Out; action <- writeInterrupt handle endPoint; .... } Failed, modules loaded: none. I have spent a few hours trying this and that, my Haskell is improving but not much good if I can't compile my program now is it! So, can anybody point out the error of my ways here please as I just can't see it! Thanks, Sean Charles. PS: Code style comments, alternative ways of making it more concise (but still readable and understandable mind you) are also welcome.

Hi Sean, I think that your function for testing board should look like this: testBoard :: Device -> DeviceHandle -> IO () testBoard dev handle = do putStrLn $ "Inspecting device: \"" ++ (show dev) ++ "\"\n" -- write 0x00 0x00 0x00 0x00, get back same... let payload = pack "\x00\x00\x00\x00" let endPoint = EndpointAddress 0 Out let action = writeInterrupt handle endPoint (size, status) <- action payload 1000 return () You need to use let because writeInterrupt returns (Timeout -> ByteString -> IO (Size, Bool)) instead of IO (Timeout -> ByteString -> IO (Size, Bool)) Karol

* emacstheviking
let payload = pack "\x00\x00\x00\x00" let endPoint = EndpointAddress 0 Out action <- writeInterrupt handle endPoint ^^^^^^^^^^^^^^ ^^^^^^ ^^^^^^^^ ^^^^^^^ writeInterrupt :: DeviceHandle -> EndpointAddress -> WriteAction
WriteAction parameter is missing. GHC tells you about that right here:
usb1.hs:60:13: Couldn't match expected type `IO t0' with actual type `WriteAction' In the return type of a call of `writeInterrupt' Probable cause: `writeInterrupt' is applied to too few arguments ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
In a stmt of a 'do' block: action <- writeInterrupt handle endPoint In the expression: do { putStrLn $ "Inspecting device: \"" ++ (show dev) ++ "\""; let payload = pack "\NUL\NUL\NUL\NUL"; let endPoint = EndpointAddress 0 Out; action <- writeInterrupt handle endPoint; .... } Failed, modules loaded: none.
-- Alexander Polakov | plhk.ru

* Alexander Polakov
* emacstheviking
[130227 16:00]: let payload = pack "\x00\x00\x00\x00" let endPoint = EndpointAddress 0 Out action <- writeInterrupt handle endPoint ^^^^^^^^^^^^^^ ^^^^^^ ^^^^^^^^ ^^^^^^^ writeInterrupt :: DeviceHandle -> EndpointAddress -> WriteAction
Uhhmm, sorry, I'm being stupid and confusing here (sleep deprived a bit). I was looking at WriteAction definition while writing this, which is: type WriteAction = ByteString -> Timeout -> IO (Size, Status) So, you have to supply ByteString and Timeout to use it as IO action (with <-):
(size, status) <- writeInterrupt handle endPoint payload 1000
or use let like Karol Samborski suggested. -- Alexander Polakov | plhk.ru
participants (3)
-
Alexander Polakov
-
emacstheviking
-
Karol Samborski