Good morning David,

I shall read that today first chance I get once the boring old day job is under steam on a fine Monday morning.

Thanks. I tried to install the command line hoogle a while back but (not always) surprisingly I had some cabal package issues... I have a fresh isntall since then so maybe I'll give it a go... if there is no emacs interface to it I might try to knock one up BUT I bet somebody has already done it!

:)




On 4 March 2013 02:04, David McBride <toad3k@gmail.com> wrote:
Hoogle only indexes some small subset of libraries, while hayoo indexes everything on hackage.  Unfortunately it seems like peoples' first inclination is to visit hoogle because hey, it's like google right?  But in fact hayoo is far better unless you know what you are looking for something in the core libraries.

I think there is some technical merit behind hoogle, like being able to search for function prototypes, and I do know you can make your own hoogle command line searcher to search libraries installed on your machine.  But usually you are searching for something you don't already have.

An actual google search comes up with http://hackage.haskell.org/packages/archive/MissingM/0.0.4/doc/html/Control-Monad-MissingM.html which actually has findM proving my point that others have felt its absense in the standard library.

On Sun, Mar 3, 2013 at 5:24 PM, emacstheviking <objitsu@gmail.com> wrote:
David,

Hoogle doesn't appear to have any matches for "findM" that I could find. Your code is pretty close to what I came up with this morning except yours is clever with monads and mine was just boring recursing through the list till I hit a match. This solution of yours looks like it is in the spirit of what I think I saw in my mind so I am going to study it very hard and understand it!

Sometimes you just have to grind it out!
Thanks.


On 3 March 2013 19:46, David McBride <toad3k@gmail.com> wrote:
I would probably go (untested):

    ...
    usbDevs <- ...
    matches <- findM (isTarget foo) $ V.toList usbDevs
    ...
    where
      findM :: Monad m => (a -> m Boolean) -> [a] -> m (Maybe a)
      findM _ [] = return Nothing
      findM f (x:xs) = do
        b <- f x
        return $ if b
          then Just x
          else findM f xs

I can almost guarantee you there is a findM already out there somewhere to use, but hayoo is down right now so I can't search for it.

On Sun, Mar 3, 2013 at 1:28 PM, emacstheviking <objitsu@gmail.com> wrote:
I now have a working USB application that can find, locate and switch LED-s on and off on my Hexwax board, for which I thank all those that helped me out last week.

I am now trying to "Haskell-ise" my code i.e. make it less amateurish with respect to some of its inner workings in a constant drive for inner cleanliness and warm fuzziness etc.

When attempting to find the device, I use the System.USB.getDevices function which returns me IO (Vector Device), a list of everything that's currently plugged in and available and I then use Data.Vector.filterM like so:

handleFor ctx (cVendor, cProd) = do
    usbDevs <- getDevices ctx
    matches <- V.filterM (isTarget (cVendor, cProd)) usbDevs
    case V.null matches of
      True  -> return Nothing
      False -> return $ Just $ matches!


isTarget :: (Word16, Word16) -> Device -> IO Bool
isTarget (vid, pid) dev = do
  getDeviceDesc dev >>= \info ->
    return $ (deviceVendorId info, deviceProductId info) == (vid, pid)


but... that is not as efficient as it could be because I could have N devices and then I just throw all but the first. Tut tut. Could do better. If I knew how... well I kind of do but I can't figure it out by myself yet!

In the Data.Vector there is "Data.Vector.find" which is *exactly* what I want with small dent in the bodywork, the predicate function is pure:

find :: (a -> Bool) -> Vector a -> Maybe a

So my question is, how do I make it work? I know (but don't yet feel comfortable with) about liftM and all that but in this case I can't see how and where it would work. I "know" (like Spiderman knows there is danger) that it's crying out for something and the return type is perfect too as it would just match.

SO...how can I do it chaps?

And as usual... .any comments, style notes, idiomatic pointers(!) etc. are always welcome.

Thanks,
Sean Charles.


_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners



_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners



_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners



_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners