Improve my FFI code please...

Hi list, I am *still* cursing the fact that I like where Haskell is taking me but that I am too dumb to get it into my head as quickly as I'd like! I will not give up and in that vein I have been beating myself up trying to run before I can walk as usual by attempting to write an FFI wrapper around the Ubuntu libcwiimote library! Having been inspired by johnnylee.net and having found his code is for Windows and C# I have taken it on myself to reproduce what he's done but using Haskell and OpenGL. Laugh, I nearly cried because it's taken hours of frustration just to get this far! I've built the hardware and now I need the software as usual. So, here we go... what I post here is the beginnings of a Wiimote wrapper. I *think* I understand Monads properly now, Brian Beck video on C9 (MSDN) really really helped a lot, I'd recommend that to anybody still struggling with the concept. What I want to know is can my code be improved by using monadic chaining and if so, with what and how (LMAO) and also have I overlooked or otherwise not used the correct forms, idioms etc. to achieve what I have so far ? I am really keen to know how the real gurus out there could reduce this code down or make it 'more haskell like'. Basically, I want you to correct it, improve it, show me and others how to do it right! I want it de-constructed, ripped to pieces, laughed at, openly mocked and I will learn from it and enjoy it because I am a developer! ;) LOL It compiles with ... ghc --make -lcwiimote -o wmscan WiiMote.hs and runs like so ... sean@sean-desktop:~/Documents/bluetooth$ ./wmscan 00:21:BD:A3:97:C7 Connecting to 00:21:BD:A3:97:C7 00:21:BD:A3:97:C7connected OK, disconnecting ...OK sean@sean-desktop:~/Documents/bluetooth$ ...and I was proud as hell, almost as proud as watching my son born but without the goo. Many thanks. Sean ---- {-# LANGUAGE ForeignFunctionInterface #-} import Foreign import Foreign.C.Types import Foreign.Ptr import Foreign.C.String import System #include "wiimote_api.h" foreign import ccall unsafe "wiimote_api.h wiimote_open" c_wiimote_open :: CString -> IO (Ptr Word8) foreign import ccall unsafe "wiimote_api.h wiimote_close" c_wiimote_close :: (Ptr Word8) -> IO CInt wiiOpen :: String -> IO (Maybe (Ptr Word8)) wiiOpen wid = do handle <- withCString wid c_wiimote_open case handle of nullPtr -> return Nothing handle -> return (Just handle) wiiClose :: Ptr Word8 -> IO Bool wiiClose wptr = do response <- c_wiimote_close wptr case response of 0 -> return True _ -> return False -- Open the wiiremote, print the handle and close it test :: String -> IO () test wiiHID = do wiimote <- wiiOpen wiiHID case wiimote of Just handle -> do putStr (wiiHID ++ " connected OK, disconnecting ... ") status <- wiiClose handle case status of True -> putStrLn "OK" False -> putStrLn "FAIL" Nothing -> putStrLn "FAIL" return () -- expects a single HID string on the command line ... main :: IO () main = do args <- getArgs case args of [hid] -> do putStrLn ("Connecting to " ++ hid) test hid _ -> putStrLn "Supply ONE Wiimote HID address!"

The code looks basically fine. Good job getting to this point. * It is probably a good idea to give Ptr Word8 a newtype; something like Wiimote, to semantically represent what it is. * Everyone loves bracketing functions! Write the function withWii :: String -> (Ptr Word8 -> IO ()) -> IO () Don't call the inner lambda if getting the Wiimote fails. * You can probably simplify 'test' a little bit by using exceptions and guards. For example, instead of 'case status' you can write 'when (not status) $ error "FAIL"'. But this is a matter of taste and what you have isn't nested too deep. Cheers, Edward

On Friday 21 January 2011 00:35:02, Sean Charles wrote:
wiiOpen :: String -> IO (Maybe (Ptr Word8)) wiiOpen wid = do handle <- withCString wid c_wiimote_open case handle of nullPtr -> return Nothing handle -> return (Just handle)
Unless nullPtr is a macro that gets replaced with a literal by the preprocessor, that won't do what you want. "nullPtr" is a generic name and matches everything, so you'll always take the first branch (with -Wall, ghc should warn about overlapping patterns in that case).

Am 21.01.2011 00:35, schrieb Sean Charles:
wiiClose :: Ptr Word8 -> IO Bool wiiClose wptr = do response <- c_wiimote_close wptr case response of 0 -> return True _ -> return False
This can be rewritten to: wiiClose = fmap (== 0) . c_wiimote_close
case status of True -> putStrLn "OK" False -> putStrLn "FAIL"
Matching Bool values use "case" is no good style: putStrLn (if status then "OK" else "FAIL") Christian

Quoting Christian Maeder
Am 21.01.2011 00:35, schrieb Sean Charles:
wiiClose :: Ptr Word8 -> IO Bool wiiClose wptr = do response <- c_wiimote_close wptr case response of 0 -> return True _ -> return False
This can be rewritten to:
wiiClose = fmap (== 0) . c_wiimote_close
case status of True -> putStrLn "OK" False -> putStrLn "FAIL"
Matching Bool values use "case" is no good style:
putStrLn (if status then "OK" else "FAIL")
Christian
That's clever but you'd have to *know* haskell to *know* you could do that! Point-free (pointless!) is something I have yet to fully tackle, it looks like a great thing. Function composition is something else for my brain to remember exists in the language! IIUC: given a Ptr8 Word, call c_wiimote close then 'functor map' the 'section' (== 0) over the single entry in the list... what list? I am confused again because I cannot see a list, c_wiimote_close answers a pointer. I understand (== 0) rather than (0 ==) though, that's something! Thanks for your time. :)

On Friday 21 January 2011 16:43:10, sean@objitsu.com wrote:
Quoting Christian Maeder
: Am 21.01.2011 00:35, schrieb Sean Charles:
wiiClose :: Ptr Word8 -> IO Bool wiiClose wptr = do response <- c_wiimote_close wptr case response of 0 -> return True _ -> return False
This can be rewritten to:
wiiClose = fmap (== 0) . c_wiimote_close
case status of True -> putStrLn "OK" False -> putStrLn "FAIL"
Matching Bool values use "case" is no good style:
putStrLn (if status then "OK" else "FAIL")
Christian
That's clever but you'd have to *know* haskell to *know* you could do that! Point-free (pointless!) is something I have yet to fully tackle, it looks like a great thing. Function composition is something else for my brain to remember exists in the language!
IIUC: given a Ptr8 Word, call c_wiimote close then 'functor map' the 'section' (== 0) over the single entry in the list... what list? I am confused again because I cannot see a list, c_wiimote_close answers a pointer.
No list here, fmap 'lifts' a function to any Functor. Here the Functor is IO. Generally, for any Monad which is also an instance of Functor (any Monad should be), fmap function monadicThingy ought to be the same as do value <- monadicThingy return (function value) which is the sugared version of monadicThingy >>= return . function
I understand (== 0) rather than (0 ==) though, that's something!
Both should be the same function.
Thanks for your time.
:)
participants (5)
-
Christian Maeder
-
Daniel Fischer
-
Edward Z. Yang
-
Sean Charles
-
sean@objitsu.com