Send Beginners mailing list submissions to
        [email protected]

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
        [email protected]

You can reach the person managing the list at
        [email protected]

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


Today's Topics:

   1. Re:  A tree code (Lyndon Maydwell)
   2.  Converting bytes to numbers (Emacs The Viking)
   3. Re:  Converting bytes to numbers (David McBride)
   4. Re:  Converting bytes to numbers (Chadda? Fouch?)
   5.  More on trying to install Haskell platform on    Lion...
      (Stuart Hungerford)
   6. Re:  More on trying to install Haskell platform   on Lion...
      (Jakub Oboza)
   7. Re:  More on trying to install Haskell platform   on Lion...
      (Brandon Allbery)
   8.  Ambiguous MonadIO and Monad (Ken KAWAMOTO)


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

Message: 1
Date: Tue, 6 Mar 2012 22:46:49 +0800
From: Lyndon Maydwell <[email protected]>
Subject: Re: [Haskell-beginners] A tree code
To: AbdulSattar Mohammed <[email protected]>
Cc: bahad?r altan <[email protected]>, [email protected]
Message-ID:
        <cam5qztyczyyqqk3ycipn30zrqys7_78lhxq78omtx0dqa4d...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

A quick correction:

data Node a = Empty
            | ValueNode a (Node a) (Node a)

or

data Node a = Empty
            | ValueNode (a, (Node a), (Node a))


On Fri, Feb 24, 2012 at 1:16 PM, AbdulSattar Mohammed
<[email protected]> wrote:
> {snip}
> data Node = Empty
> ? ? ? ? ? | ValueNode Int, Node, Node -- An integer, a left node and a right
> node
> {snip}



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

Message: 2
Date: Tue, 06 Mar 2012 16:20:06 +0000
From: Emacs The Viking <[email protected]>
Subject: [Haskell-beginners] Converting bytes to numbers
To: <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset="utf-8"

  

OK, I have a situation....I have a little PIC microchip sending out
24 bit ADC values over TCP/IP... I want to know what is the nicest /
cleanest / best / efficient / geekiest etc way tyo convert the three
bytes it sends into an unsigned 24-bit number... 

main :: IO () 

main
= do 

 h 
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120306/7d41412a/attachment-0001.htm>

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

Message: 3
Date: Tue, 6 Mar 2012 13:47:25 -0500
From: David McBride <[email protected]>
Subject: Re: [Haskell-beginners] Converting bytes to numbers
To: Emacs The Viking <[email protected]>
Cc: [email protected]
Message-ID:
        <can+tr40s6mm8bfkyjtc3df9m-2gknhiauml_5lac8wdyded...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

While I like your pre-zipping solution, I see why it didn't work out
well for you.  The way that I've done such things is with folds.  The
thing is that you need to store both the final answer as well as the
index of the bytestring where you are so that the supplied function
can know what power to take 256 to at each step.  Here's how I would
do it.

totalBS :: ByteString -> Integer
totalBS bs = ans
  where
    (_,ans) = foldr' func (0,0) (BS.reverse bs)
    func byte (acc,ans) = (acc+1, ans + fromIntegral byte * (256^acc))

This should work on any size bytestring.


On Tue, Mar 6, 2012 at 11:20 AM, Emacs The Viking <[email protected]> wrote:
> OK, I have a situation....I have a little PIC microchip sending out 24 bit
> ADC values over TCP/IP... I want to know what is the nicest / cleanest /
> best / efficient / geekiest etc way tyo convert the three bytes it sends
> into an unsigned 24-bit number...
>
>
>
> main :: IO ()
>
> main = do
>
> ? ? h <- connectTo "picbox" (PortNumber 20000)
>
> ? ? len <- liftM unpack $ BS.hGet h 3
>
> ? ? hClose h
>
> ? ? print len
>
>
>
> that currently gives me [17,0,0] on the console, which is 0x000011 in hex.
>
> I have played with ByteString foldl' and all sorts of other ways to do what
> I want, which is essentially the sum of b0 + (b1*256) + (b2 * 256 * 256)
> where b0 is 17 and b2 and b3 are the zeros.
>
> I've tried toying with zipping it with an array containing [1, 256,
> 256*256], I've tried using left and right folds and pre-multiplying the
> accumulator by 256 each time but the ByteString seems limited to 0-255 and
> so it doesn't work. I've tried brute force arithmetic by extracting each
> part and doing the maths etc.
>
> The challenge then is to show me how to deal with ByteStrings and
> "fromIntegral" type conversions; I am still learning Haskell and loving it
> but things like this really stump me sometimes! LOL
>
> The generalisation I guess is how to convert an array of bytes into a number
> where each byte must be multiplied by its respective power... I am still
> working on it myself... I am still happy that I used "liftM" for the first
> time and actually understood why, how and what I was doing it for LMAO
>
> Thanks... I have a feeling the answers will really help me.
>
> Sean Charles.
>
>
>
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>



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

Message: 4
Date: Tue, 6 Mar 2012 20:33:16 +0100
From: Chadda? Fouch? <[email protected]>
Subject: Re: [Haskell-beginners] Converting bytes to numbers
To: David McBride <[email protected]>
Cc: Emacs The Viking <[email protected]>, [email protected]
Message-ID:
        <CANfjZRZT7qy+6Zn8TQd=w64eyuyjdkyy+hau3ayzwod6hgd...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Tue, Mar 6, 2012 at 7:47 PM, David McBride <[email protected]> wrote:
> While I like your pre-zipping solution, I see why it didn't work out
> well for you. ?The way that I've done such things is with folds. ?The
> thing is that you need to store both the final answer as well as the
> index of the bytestring where you are so that the supplied function
> can know what power to take 256 to at each step. ?Here's how I would
> do it.
>
> totalBS :: ByteString -> Integer
> totalBS bs = ans
> ?where
> ? ?(_,ans) = foldr' func (0,0) (BS.reverse bs)
> ? ?func byte (acc,ans) = (acc+1, ans + fromIntegral byte * (256^acc))
>
> This should work on any size bytestring.

Rather than doing this you can simply multiply by 256 because a + 256
b + 256? c == a + 256 ( b + 256 c )

So :
> totalBS :: ByteString -> Integer
> totalBS = BS.foldr' (\byte total -> fromIntegral byte + 256 * total) 0

This is an idiom often used :)

Note that for normal sized words and if your parser become more
complicated, you should look at the binary package to parse streams of
bytes.

-- 
Jeda?



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

Message: 5
Date: Wed, 7 Mar 2012 08:04:42 +1100
From: Stuart Hungerford <[email protected]>
Subject: [Haskell-beginners] More on trying to install Haskell
        platform on     Lion...
To: [email protected]
Message-ID:
        <CAG+kMrHCV8R7uqqh0+fjvbqr5UQz1GiZ3Pu9vzPB0=ez6ev...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi,

An update on my continuing attempts to install Haskell platform on
OS/X Lion.  Just in case there was some problem with my Homebrew
settings I completely removed Homebrew and reinstalled a fresh
version, but still get the same errors.

Could someone confirm for me whether OS/X Lion is supported for
Haskell platform (or more likely) there's a different way of going
about installation?

Thanks,

Stu



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

Message: 6
Date: Tue, 6 Mar 2012 21:08:30 +0000
From: Jakub Oboza <[email protected]>
Subject: Re: [Haskell-beginners] More on trying to install Haskell
        platform        on Lion...
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii

I managed to install 64bit haskell platform and use it without problems on 10.7 
Lion


On 6 Mar 2012, at 21:04, Stuart Hungerford wrote:

> Hi,
> 
> An update on my continuing attempts to install Haskell platform on
> OS/X Lion.  Just in case there was some problem with my Homebrew
> settings I completely removed Homebrew and reinstalled a fresh
> version, but still get the same errors.
> 
> Could someone confirm for me whether OS/X Lion is supported for
> Haskell platform (or more likely) there's a different way of going
> about installation?
> 
> Thanks,
> 
> Stu
> 
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners




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

Message: 7
Date: Tue, 6 Mar 2012 17:20:50 -0500
From: Brandon Allbery <[email protected]>
Subject: Re: [Haskell-beginners] More on trying to install Haskell
        platform        on Lion...
To: Stuart Hungerford <[email protected]>
Cc: [email protected]
Message-ID:
        <cakfcl4u9lkui1n13r52ito7kkn-rtk8sqf-d2a3g2hia6sp...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Tue, Mar 6, 2012 at 16:04, Stuart Hungerford <[email protected]
> wrote:

> Could someone confirm for me whether OS/X Lion is supported for
> Haskell platform (or more likely) there's a different way of going
> about installation?
>

The problem is not Lion, it is that

(a) Xcode 4.3 was only just released
(b) Apple does not allow details of unreleased software to be discussed
etc. before release
which means
(c) everyone who relies on Xcode got pretty much blindsided by all the
changes.

ghc hasn't quite caught up with the changes yet.  MacPorts is still
struggling with some issues involved with the release; I don't know where
Homebrew is with respect to it.  Some of the other projects I'm involved
with aren't Mac focused, and are just starting to realize that there are
problems with Xcode 4.3 support.

If you need Haskell Platform working ASAP on OS X, remove Xcode 4.3, then
download Xcode 4.2.1 from http://connect.apple.com/.

-- 
brandon s allbery                                      [email protected]
wandering unix systems administrator (available)     (412) 475-9364 vm/sms
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120306/6d92a388/attachment-0001.htm>

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

Message: 8
Date: Wed, 7 Mar 2012 08:42:05 +0900
From: Ken KAWAMOTO <[email protected]>
Subject: [Haskell-beginners] Ambiguous MonadIO and Monad
To: [email protected]
Message-ID:
        <cagbyekpf2efcab2fh6_xbdseaq_jzokgbq9zbd039cv8w2x...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi,

I'm trying to understand how Network.OAuth.Consumer works, and
run sample code found here with Twitter API. (the full code is
attached at the bottom)
http://hackage.haskell.org/packages/archive/hoauth/0.3.3/doc/html/Network-OAuth-Consumer.html

When I load the test code with GHCi 7.0.2, it raises error:

--- Error message begin
TestOAuth.hs:21:103:
    Ambiguous type variable `m0' in the constraints:
      (MonadIO m0) arising from a use of `serviceRequest'
                   at TestOAuth.hs:21:103-116
      (Monad m0) arising from a use of `>>=' at TestOAuth.hs:21:99-101
    Possible cause: the monomorphism restriction applied to the following:
      response :: m0 Response (bound at TestOAuth.hs:17:1)
    Probable fix: give these definition(s) an explicit type signature
                  or use -XNoMonomorphismRestriction
    In the second argument of `(>>=)', namely
      `serviceRequest CurlClient'
    In the expression:
        signRq2 HMACSHA1 (Just $ Realm "realm") srvUrl
      >>=
        serviceRequest CurlClient
    In the second argument of `($)', namely
      `do { signRq2 PLAINTEXT Nothing reqUrl >>= oauthRequest CurlClient;
          cliAskAuthorization authUrl;
            signRq2 PLAINTEXT Nothing accUrl >>= oauthRequest CurlClient;
            signRq2 HMACSHA1 (Just $ Realm "realm") srvUrl
          >>=
            serviceRequest CurlClient }'
--- Error message end

I seem using NoMonomorphismRestriction is workaround, so I want to add
a proper type signature, but I cannot figure out what it is.

What confuses me is why GHC didn't just take MonadIO as MonadIO is a
Monad according to the definition.
http://hackage.haskell.org/packages/archive/transformers/0.2.2.0/doc/html/Control-Monad-IO-Class.html#t:MonadIO

I tried to add a type signature by replacing the second line from the
bottom with this, in vain.
  ((signRq2 HMACSHA1 (Just $ Realm "realm") srvUrl) :: (MonadIO m) =>
OAuthMonadT m OAuthRequest) >>= serviceRequest CurlClient


Can you help me find what's wrong with this?


Thanks in advance,
Ken


--- Test code (TestOAuth.hs)
import Control.Monad.IO.Class (MonadIO)
import Data.Maybe (fromJust)

import Network.OAuth.Consumer
import Network.OAuth.Http.CurlHttpClient
import Network.OAuth.Http.Request
import Network.OAuth.Http.Response

consumerKey = "MY CONSUMER KEY"
consumerSec = "MY CONSUMER SEC"

reqUrl    = fromJust . parseURL $ "https://api.twitter.com/oauth/request_token";
accUrl    = fromJust . parseURL $ "https://api.twitter.com/oauth/access_token";
srvUrl    = fromJust . parseURL $ "http://service/path/to/resource/";
authUrl   = ("https://api.twitter.com/oauth/authorize?oauth_token="++)
. findWithDefault ("oauth_token","ERROR") . oauthParams
app       = Application consumerKey consumerSec OOB
response  = runOAuthM (fromApplication app) $ do { signRq2 PLAINTEXT
Nothing reqUrl >>= oauthRequest CurlClient
                                                 ; cliAskAuthorization authUrl
                                                 ; signRq2 PLAINTEXT
Nothing accUrl >>= oauthRequest CurlClient
                                                 ; signRq2 HMACSHA1
(Just $ Realm "realm") srvUrl >>= serviceRequest CurlClient
                                                 }



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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 45, Issue 5
****************************************

Reply via email to