Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Help with some heavy lifting... (emacstheviking)
   2. Re:  Help with some heavy lifting... (Bob Ippolito)
   3. Re:  Help with some heavy lifting... (David McBride)
   4. Re:  Help with some heavy lifting... (emacstheviking)


----------------------------------------------------------------------

Message: 1
Date: Sun, 3 Mar 2013 18:28:16 +0000
From: emacstheviking <obji...@gmail.com>
Subject: [Haskell-beginners] Help with some heavy lifting...
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID:
        <caeieuu+86qp8ekz2xpmr-5+qq5kxs18phxumyn67et6i9rz...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

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<http://hackage.haskell.org/packages/archive/base/4.6.0.0/doc/html/Data-Bool.html#t:Bool>)
-> 
Vector<http://hackage.haskell.org/packages/archive/vector/0.10.0.1/doc/html/Data-Vector.html#t:Vector>a
->
Maybe<http://hackage.haskell.org/packages/archive/base/4.6.0.0/doc/html/Data-Maybe.html#t: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.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130303/7e43cfc4/attachment-0001.htm>

------------------------------

Message: 2
Date: Sun, 3 Mar 2013 10:44:07 -0800
From: Bob Ippolito <b...@redivi.com>
Subject: Re: [Haskell-beginners] Help with some heavy lifting...
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID:
        <cacwmpm-ax_ajma0ph8wgmsh8rfgjdkgelx6j1zqz8xdrk4x...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

I don't know what the performance would look like, but you can freeze the
mutable Vector and then just use find. Here's an example:

import qualified Data.Vector.Mutable as M
import qualified Data.Vector as V
main :: IO ()
main = do
  v <- M.replicate 10 'a'
  M.write v 2 'b'
  V.freeze v >>= print . V.find (=='b')



On Sun, Mar 3, 2013 at 10:28 AM, emacstheviking <obji...@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<http://hackage.haskell.org/packages/archive/base/4.6.0.0/doc/html/Data-Bool.html#t:Bool>)
> -> 
> Vector<http://hackage.haskell.org/packages/archive/vector/0.10.0.1/doc/html/Data-Vector.html#t:Vector>a
>  ->
> Maybe<http://hackage.haskell.org/packages/archive/base/4.6.0.0/doc/html/Data-Maybe.html#t: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
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130303/6310cc75/attachment-0001.htm>

------------------------------

Message: 3
Date: Sun, 3 Mar 2013 14:46:58 -0500
From: David McBride <toa...@gmail.com>
Subject: Re: [Haskell-beginners] Help with some heavy lifting...
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID:
        <CAN+Tr43hHOUK=su+c3jmlk+wj6akbfstu4ovdxlykp_vwb1...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

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 <obji...@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<http://hackage.haskell.org/packages/archive/base/4.6.0.0/doc/html/Data-Bool.html#t:Bool>)
> -> 
> Vector<http://hackage.haskell.org/packages/archive/vector/0.10.0.1/doc/html/Data-Vector.html#t:Vector>a
>  ->
> Maybe<http://hackage.haskell.org/packages/archive/base/4.6.0.0/doc/html/Data-Maybe.html#t: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
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130303/e9152cb2/attachment-0001.htm>

------------------------------

Message: 4
Date: Sun, 3 Mar 2013 21:58:30 +0000
From: emacstheviking <obji...@gmail.com>
Subject: Re: [Haskell-beginners] Help with some heavy lifting...
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID:
        <caeieuujy6qqfcakxnc07w308ztbnkuwafkxa6avu-edhfsk...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi Bob,

I can't see how this helps my situation though because V.find expects the
predicate to be pure. My predicate requires "IO" as it calls two functions
that dip into the USB device structure.

Have I missed something here???

Thanks
Sean


On 3 March 2013 18:44, Bob Ippolito <b...@redivi.com> wrote:

> I don't know what the performance would look like, but you can freeze the
> mutable Vector and then just use find. Here's an example:
>
> import qualified Data.Vector.Mutable as M
> import qualified Data.Vector as V
> main :: IO ()
> main = do
>   v <- M.replicate 10 'a'
>   M.write v 2 'b'
>   V.freeze v >>= print . V.find (=='b')
>
>
>
> On Sun, Mar 3, 2013 at 10:28 AM, emacstheviking <obji...@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<http://hackage.haskell.org/packages/archive/base/4.6.0.0/doc/html/Data-Bool.html#t:Bool>)
>> -> 
>> Vector<http://hackage.haskell.org/packages/archive/vector/0.10.0.1/doc/html/Data-Vector.html#t:Vector>a
>>  ->
>> Maybe<http://hackage.haskell.org/packages/archive/base/4.6.0.0/doc/html/Data-Maybe.html#t: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
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130303/8ca9d73a/attachment.htm>

------------------------------

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


End of Beginners Digest, Vol 57, Issue 2
****************************************

Reply via email to