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.  record problem when updating fields with an IO   a type
      (Manfred Lotz)
   2. Re:  record problem when updating fields with an  IO a type
      (Christian Maeder)
   3. Re:  Another request for code critique... (Brent Yorgey)
   4. Re:  Critique my Code! (black...@pro-ns.net)
   5.  Haskell Platform and GHC 7.0.3 (Alba Marchisio)
   6. Re:  Haskell Platform and GHC 7.0.3 (Luca Ciciriello)
   7. Re:  Haskell Platform and GHC 7.0.3 (Forrest Cahoon)
   8.  Network.HTTP basics (Barbara Shirtcliff)
   9. Re:  Network.HTTP basics (Antoine Latter)
  10. Re:  Network.HTTP basics (Daniel Fischer)


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

Message: 1
Date: Fri, 1 Apr 2011 16:28:05 +0200
From: Manfred Lotz <manfred.l...@arcor.de>
Subject: [Haskell-beginners] record problem when updating fields with
        an IO   a type
To: beginners@haskell.org
Message-ID: <20110401162805.3a188...@arcor.com>
Content-Type: text/plain; charset=US-ASCII

Hi there,
I have a problem where I like to update a record with an IO a. Not
quite sure how to describe it.

Here is a minimal example: I get a list of numbers from the command
line and I like to add those numbers n and randome numbers from a
range from [0..n] in two fields of a record. 

<---------------------------snip---------------------------->
module Main where

import System.Environment.UTF8
import System.Random

data NumRec = NumRec {
  mxV :: Int,
  mxR :: Int
  } deriving (Show,Read)


initNumRec = NumRec { mxV = 0, mxR = 0 }

toInt s = read s :: Int


addRandom m n = do
  let mxv = mxV m
  let mxr = mxR m
  let r = rand n
  m { mxV = mxv + n,
          mxR = mxr + r }

rand :: Int -> IO Int
rand max = getStdRandom (randomR (0, max))         
                   

main = do  
    args <- getArgs  
    print args
    let ilist = map toInt args
    let mixed = foldl addRandom initNumRec ilist
    print mixed
<---------------------------snap---------------------------->

I get the following error when compiling:

[1 of 1] Compiling Main             ( minimal.hs, minimal.o )

minimal.hs:22:23:
    Couldn't match expected type `Int' with actual type `IO Int'
    In the second argument of `(+)', namely `r'
    In the `mxR' field of a record
    In the expression: m {mxV = mxv + n, mxR = mxr + r}


How can I correct the compile error? 



-- 
Manfred





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

Message: 2
Date: Fri, 01 Apr 2011 16:56:37 +0200
From: Christian Maeder <christian.mae...@dfki.de>
Subject: Re: [Haskell-beginners] record problem when updating fields
        with an IO a type
To: Manfred Lotz <manfred.l...@arcor.de>
Cc: beginners@haskell.org
Message-ID: <4d95e7a5.6020...@dfki.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Am 01.04.2011 16:28, schrieb Manfred Lotz:
> Hi there,
> I have a problem where I like to update a record with an IO a. Not
> quite sure how to describe it.
>
> Here is a minimal example: I get a list of numbers from the command
> line and I like to add those numbers n and randome numbers from a
> range from [0..n] in two fields of a record.
>
> <---------------------------snip---------------------------->
> module Main where
>
> import System.Environment.UTF8
> import System.Random
>
> data NumRec = NumRec {
>    mxV :: Int,
>    mxR :: Int
>    } deriving (Show,Read)
>
>
> initNumRec = NumRec { mxV = 0, mxR = 0 }
>
> toInt s = read s :: Int
>
>

think about the type of addRandom!

> addRandom m n = do
>    let mxv = mxV m
>    let mxr = mxR m


change:
>    let r = rand n
>    m { mxV = mxv + n,
>            mxR = mxr + r }

to:
     r <- rand n
     return m {....}

>
> rand :: Int ->  IO Int
> rand max = getStdRandom (randomR (0, max))
>
>
> main = do
>      args<- getArgs
>      print args
>      let ilist = map toInt args
>      let mixed = foldl addRandom initNumRec ilist

use Control.Monad.foldM. I'm not sure if the following will work:

      mixed <- foldM addRandom initNumRec ilist

Cheers Christian

>      print mixed
> <---------------------------snap---------------------------->
>
> I get the following error when compiling:
>
> [1 of 1] Compiling Main             ( minimal.hs, minimal.o )
>
> minimal.hs:22:23:
>      Couldn't match expected type `Int' with actual type `IO Int'
>      In the second argument of `(+)', namely `r'
>      In the `mxR' field of a record
>      In the expression: m {mxV = mxv + n, mxR = mxr + r}
>
>
> How can I correct the compile error?
>
>
>



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

Message: 3
Date: Fri, 1 Apr 2011 11:07:12 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Another request for code critique...
To: beginners@haskell.org
Message-ID: <20110401150712.ga5...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Thu, Mar 31, 2011 at 02:18:32PM -0400, Mike Meyer wrote:
> Shorter, but thing I've done that wasn't just an exercise from a
> haskell book.
> 
> The problem statement can be found at
> http://kernelbob.wordpress.com/2011/03/20/same-five-digits/.
> 
> My solution can be seen at http://pastebin.com/iW95q2ex.

Looks nice.  A few places things could be made a bit more points-free
(which isn't always a good thing -- but I think in these cases it makes
things more readable, although I suppose that's mostly an issue of
what you're used to)

  (\ s -> length s < 6)   --->   ((<6) . length)  (etc.)

  (\ (_, m) -> (== 5) $ M.size m)  --->  (==5) . M.size . snd   (etc.)

  If you have a recent enough version of base, (\ (t,m) -> (m,t)) is
  available as 'swap' in Data.Tuple.

This one is slightly more advanced:

  map (\ (t,m) -> (t, head . M.keys $ M.filter (== '1') m))

can be replaced by

  (map . second) (head . M.keys . M.filter (== '1'))

which applies the function (head . M.keys . M.filter (== '1')) to the
second component of every element of a list.  The 'second' function is
from Control.Arrow, and can be given the type

  second :: (b -> c) -> (a,b) -> (a,c)

(actually its type is a bit more general than that).

-Brent



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

Message: 4
Date: Fri, 01 Apr 2011 08:16:44 -0700
From: black...@pro-ns.net
Subject: Re: [Haskell-beginners] Critique my Code!
To: Christian Maeder <christian.mae...@dfki.de>
Cc: beginners@haskell.org
Message-ID: <e36f7ce71ca72c96d724b7d171946...@pro-ns.net>
Content-Type: text/plain; charset=UTF-8; format=flowed

 Thanks for the comments, Christian.

 Looking at the structure of the code overall, I should just be using a 
 set for the set of factors, not a list.  That's the fundamental problem 
 there.  I'm just so focused on list processing in Haskell that I didn't 
 take the time to examine if it was appropriate here.

> b) "sort $ nub" (even twice)
>
> first sort and then removing duplicates can be more efficient, I
> would suggest: "Data.Set.toList . Data.Set.fromList"
>





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

Message: 5
Date: Fri, 1 Apr 2011 17:33:55 +0200
From: Alba Marchisio <alba.marchi...@gmail.com>
Subject: [Haskell-beginners] Haskell Platform and GHC 7.0.3
To: beginners@haskell.org
Message-ID:
        <aanlktimb4mqoccmyhmx1lqb6c0ct24pfu+e4khaxz...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Sorry I'm new and probably this post is out of topic, but my question is:
when a Haskell Platform integrated with GHC 7.0.3?

Thanks

Alba.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20110401/9d329cd6/attachment-0001.htm>

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

Message: 6
Date: Fri, 1 Apr 2011 17:39:28 +0200
From: Luca Ciciriello <luca_cicirie...@hotmail.com>
Subject: Re: [Haskell-beginners] Haskell Platform and GHC 7.0.3
To: Alba Marchisio <alba.marchi...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <blu0-smtp156c0391862b3f2d1ef6feb9a...@phx.gbl>
Content-Type: text/plain; charset="us-ascii"

Hi Alba.
I've formulated the same question on the GHC mailing list, but I haven't 
received any answer.
Good Luck.

Luca.

On Apr 1, 2011, at 5:33 PM, Alba Marchisio wrote:

> Sorry I'm new and probably this post is out of topic, but my question is: 
> when a Haskell Platform integrated with GHC 7.0.3? 
> 
> Thanks
> 
> Alba.
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners




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

Message: 7
Date: Fri, 1 Apr 2011 13:35:45 -0500
From: Forrest Cahoon <forrest.cah...@gmail.com>
Subject: Re: [Haskell-beginners] Haskell Platform and GHC 7.0.3
To: Alba Marchisio <alba.marchi...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <AANLkTikNfwaOLWB6TYxAfiiwzGAO81GFoY=pqnww9...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Fri, Apr 1, 2011 at 10:33 AM, Alba Marchisio
<alba.marchi...@gmail.com> wrote:
> Sorry I'm new and probably this post is out of topic, but my question is:
> when a Haskell Platform integrated with GHC 7.0.3?
> Thanks
> Alba.

The current 2011.2.0.0 version linked from
http://hackage.haskell.org/platform/ does. It took them a while to
update that link, but it's there now.



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

Message: 8
Date: Fri, 01 Apr 2011 19:42:19 +0000
From: "Barbara Shirtcliff" <ba...@gmx.com>
Subject: [Haskell-beginners] Network.HTTP basics
To: beginners@haskell.org
Message-ID: <20110401194220.201...@gmx.com>
Content-Type: text/plain; charset="utf-8"

Hi, this is small, but this is the beginners list, so here goes:

I can see how to use HTTP to request a page. ?for example, this works:


Prelude Network.HTTP> let respgoogle = simpleHTTP $ getRequest 
"http://google.com";
Prelude Network.HTTP> respgoogle
Right HTTP/1.1 301 Moved Permanently 
Location: http://www.google.com/
Content-Type: text/html; charset=UTF-8
Date: Fri, 01 Apr 2011 17:31:25 GMT
Expires: Sun, 01 May 2011 17:31:25 GMT
Cache-Control: public, max-age=2592000
Server: gws
Content-Length: 219
X-XSS-Protection: 1; mode=block
Connection: close

that looks really nice, but hey, what if I want to see what's in the content? 
?It isn't immediately clear to me from the documentation at 
http://hackage.haskell.org/packages/archive/HTTP/4000.1.1/doc/html/Network-HTTP.html
 .

In the end, I'll be working with JSON, here, but I need to know how to get to 
it, and the examples in the documentation don't work (i.e. don't appear to be 
up to date). ?I'm not very experienced with Haskell, so, it's pretty opaque.

Thanks,
Bar




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

Message: 9
Date: Fri, 1 Apr 2011 15:00:44 -0500
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] Network.HTTP basics
To: Barbara Shirtcliff <ba...@gmx.com>
Cc: beginners@haskell.org
Message-ID:
        <AANLkTikkk5Q0awEXEv13Qj=n8zm-vqfnzwm2wjxpv...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Fri, Apr 1, 2011 at 2:42 PM, Barbara Shirtcliff <ba...@gmx.com> wrote:
> Hi, this is small, but this is the beginners list, so here goes:
>
> I can see how to use HTTP to request a page. ?for example, this works:
>
>
> Prelude Network.HTTP> let respgoogle = simpleHTTP $ getRequest 
> "http://google.com";
> Prelude Network.HTTP> respgoogle
> Right HTTP/1.1 301 Moved Permanently
> Location: http://www.google.com/
> Content-Type: text/html; charset=UTF-8
> Date: Fri, 01 Apr 2011 17:31:25 GMT
> Expires: Sun, 01 May 2011 17:31:25 GMT
> Cache-Control: public, max-age=2592000
> Server: gws
> Content-Length: 219
> X-XSS-Protection: 1; mode=block
> Connection: close
>
> that looks really nice, but hey, what if I want to see what's in the content? 
> ?It isn't immediately clear to me from the documentation at 
> http://hackage.haskell.org/packages/archive/HTTP/4000.1.1/doc/html/Network-HTTP.html
>  .
>
> In the end, I'll be working with JSON, here, but I need to know how to get to 
> it, and the examples in the documentation don't work (i.e. don't appear to be 
> up to date). ?I'm not very experienced with Haskell, so, it's pretty opaque.
>

Hi,

The Response type is exported non-abstractly by the HTTP package, with
documentation here:

http://hackage.haskell.org/packages/archive/HTTP/4000.1.1/doc/html/Network-HTTP-Base.html#t:Response

You can either pattern-match on the response, or use the rspBody
function to extract the response body.

Take care,
Antoine



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

Message: 10
Date: Fri, 1 Apr 2011 22:04:06 +0200
From: Daniel Fischer <daniel.is.fisc...@googlemail.com>
Subject: Re: [Haskell-beginners] Network.HTTP basics
To: beginners@haskell.org
Message-ID: <201104012204.07096.daniel.is.fisc...@googlemail.com>
Content-Type: Text/Plain;  charset="utf-8"

On Friday 01 April 2011 21:42:19, Barbara Shirtcliff wrote:
> Hi, this is small, but this is the beginners list, so here goes:
> 
> I can see how to use HTTP to request a page.  for example, this works:
> 
> 
> Prelude Network.HTTP> let respgoogle = simpleHTTP $ getRequest
> "http://google.com"; Prelude Network.HTTP> respgoogle
> Right HTTP/1.1 301 Moved Permanently
> Location: http://www.google.com/
> Content-Type: text/html; charset=UTF-8
> Date: Fri, 01 Apr 2011 17:31:25 GMT
> Expires: Sun, 01 May 2011 17:31:25 GMT
> Cache-Control: public, max-age=2592000
> Server: gws
> Content-Length: 219
> X-XSS-Protection: 1; mode=block
> Connection: close
> 
> that looks really nice, but hey, what if I want to see what's in the
> content?  It isn't immediately clear to me from the documentation at
> http://hackage.haskell.org/packages/archive/HTTP/4000.1.1/doc/html/Netw
> ork-HTTP.html .

stuff = do
    answer <- respgoogle
    case answer of
      Left connErr -> putStrLn "Got a connection error:" >> print connErr
      Right result -> do
            let goodies = rspBody result
            putStrLn goodies    -- or do something sensible

> 
> In the end, I'll be working with JSON, here, but I need to know how to
> get to it, and the examples in the documentation don't work (i.e. don't
> appear to be up to date).  I'm not very experienced with Haskell, so,
> it's pretty opaque.
> 
> Thanks,
> Bar
> 



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

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


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

Reply via email to