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. Re:  Sequential IO processing (Andrew Wagner)
   2. Re:  Sequential IO processing (Sergey V. Mikhanov)
   3.  Re: Sequential IO processing (Heinrich Apfelmus)
   4. Re:  Re: Sequential IO processing (Sergey V. Mikhanov)
   5. Re:  Re: Sequential IO processing (Felipe Lessa)
   6.  Counting Fruits (Adolfo Builes)
   7. Re:  Counting Fruits (Alexander Dunlap)


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

Message: 1
Date: Thu, 19 Feb 2009 10:19:35 -0500
From: Andrew Wagner <wagner.and...@gmail.com>
Subject: Re: [Haskell-beginners] Sequential IO processing
To: "Sergey V. Mikhanov" <ser...@mikhanov.com>
Cc: beginners@haskell.org
Message-ID:
        <b8a8636e0902190719xf7beb26j215f8a31746fe...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

You did really well here. There's just one small detail that you missed,
which is causing the problem:

>
> sequenceIO [] = return []
> sequenceIO (x : xs) = do result <- x
>                         return result : sequenceIO xs
>

The problem is indeed here. The type of 'sequenceIO xs' is IO [a], but the
type of result is 'a'. You can't cons an 'a' onto an 'IO [a]'. Thus, what
you need is something like this:

sequenceIO [] = return []
sequenceIO (x : xs) = do result <- x                                     xs'
<- sequenceIO xs -- to take the list out of the IO Monad
                                     return result : xs'
On Thu, Feb 19, 2009 at 9:56 AM, Sergey V. Mikhanov <ser...@mikhanov.com>wrote:

>   Hi community,
>
> I am making my first steps in Haskell, reading Haskell wikibook and
> now stuck with one of the excercises, namely this one:
>
> Implement a function sequenceIO :: [IO a] -> IO [a]. Given a list of
> actions, this function runs each of the actions in order and returns
> all their results as a list.
>
> This is what I came with:
>
> ioOne :: Num a => IO a
>
> ioOne = do print guid
>           return guid
>        where
>           guid = 2
>
> ioTwo :: Num a => IO a
>
> ioTwo = do print guid
>           return guid
>        where
>           guid = 3
>
> sequenceIO :: Num a => [IO a] -> IO [a]
>
> sequenceIO [] = return []
> sequenceIO (x : xs) = do result <- x
>                         return result : sequenceIO xs
>
> First two functions are there because of the invocation that I've
> planned: sequenceIO [getGuid, getNextGuid].
>
> However, this could not be compiled (GHC):
>
> Couldn't match expected type `[m a]' against inferred type `IO [a]'
> In the second argument of `(:)', namely `sequenceIO xs'
> In the expression: return result : sequenceIO xs
> In the expression:
>    do result <- x
>        return result : sequenceIO xs
>
> Fine, I thought, something wrong with the type of the 'sequenceIO xs'
> (becasue I am sure the type of 'result' is fine). So I wrote another
> program to check what happens to the result of IO action evaluation
> (namely, which type is assigned):
>
> bar :: Num a => IO a
>
> bar = do print guid
>         return guid
>      where
>         guid = 2
>
> foo = do result <- bar
>         result
>
> This could not be compiled either:
>
> No instance for (Num (IO b))
>    arising from a use of `bar' at auxil.hs:8:19-21
> Possible fix: add an instance declaration for (Num (IO b))
> In a stmt of a 'do' expression: result <- bar
> In the expression:
>    do result <- bar
>        result
> In the definition of `foo':
>    foo = do result <- bar
>            result
>
> I am a newbie, so I am interpreting this like "Haskell could not
> construct Num from the result of invocation of bar, which is of type
> IO a". But why do I need this at all? When doing console I/O with
> 'result <- getLine', I do not need to reconstruct String from the
> result.
>
> What am I doing wrong? Where is the failure in reasoning?
>
> Thanks,
> Sergey
> _______________________________________________
> 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/20090219/3e166623/attachment-0001.htm

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

Message: 2
Date: Thu, 19 Feb 2009 16:27:02 +0100
From: "Sergey V. Mikhanov" <ser...@mikhanov.com>
Subject: Re: [Haskell-beginners] Sequential IO processing
To: beginners <beginners@haskell.org>
Message-ID:
        <b38b3dd10902190727p5eaaf9dbn9c5e04a45c4fe...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I tried this earlier as well:

sequenceIO [] = return []
sequenceIO (x : xs) = do result <- x
                         resultTail <- sequenceIO xs
                         return result : resultTail

This results in:

Couldn't match expected type `IO [a]' against inferred type `[m a]'
In the expression: return result : resultTail
In the expression:
    do result <- x
      resultTail <- sequenceIO xs
         return result : resultTail
In the definition of `sequenceIO':
    sequenceIO (x : xs)
                 = do result <- x
                      resultTail <- sequenceIO xs
                        return result : resultTail

>> sequenceIO [] = return []
>> sequenceIO (x : xs) = do result <- x
>>                         return result : sequenceIO xs
>
> The problem is indeed here. The type of 'sequenceIO xs' is IO [a], but the
> type of result is 'a'. You can't cons an 'a' onto an 'IO [a]'. Thus, what
> you need is something like this:
> sequenceIO [] = return []
> sequenceIO (x : xs) = do result <- x
>                                      xs' <- sequenceIO xs -- to take the
> list out of the IO Monad
>                                      return result : xs'


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

Message: 3
Date: Thu, 19 Feb 2009 16:32:29 +0100
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: Sequential IO processing
To: beginners@haskell.org
Message-ID: <gnju0m$29...@ger.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1

Sergey V. Mikhanov wrote:
> I tried this earlier as well:
> 
> sequenceIO [] = return []
> sequenceIO (x : xs) = do result <- x
>                          resultTail <- sequenceIO xs
>                          return result : resultTail

The last line should be

                           return (result : resultTail)

otherwise it will be parsed as

  (return result) : resultTail

which is not what you want.


Regards,
apfelmus

--
http://apfelmus.nfshost.com



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

Message: 4
Date: Thu, 19 Feb 2009 16:35:08 +0100
From: "Sergey V. Mikhanov" <ser...@mikhanov.com>
Subject: Re: [Haskell-beginners] Re: Sequential IO processing
To: beginners@haskell.org
Message-ID:
        <b38b3dd10902190735i59d5cfe8p42c69068eb522...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Now works!

Thank you very much -- a nice lesson learned for me.

S.

>> I tried this earlier as well:
>>
>> sequenceIO [] = return []
>> sequenceIO (x : xs) = do result <- x
>>                          resultTail <- sequenceIO xs
>>                          return result : resultTail
>
> The last line should be
>
>                           return (result : resultTail)
>
> otherwise it will be parsed as
>
>  (return result) : resultTail
>
> which is not what you want.
>
>
> Regards,
> apfelmus


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

Message: 5
Date: Thu, 19 Feb 2009 13:06:00 -0300
From: Felipe Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] Re: Sequential IO processing
To: "Sergey V. Mikhanov" <ser...@mikhanov.com>
Cc: beginners@haskell.org
Message-ID:
        <c2701f5c0902190806y2bdd617du8315320529a78...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Just a small comment, it's great to see the beginners list being so
useful! Thanks, everyone, beginners and 'otherwise'.

-- 
Felipe.


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

Message: 6
Date: Thu, 19 Feb 2009 23:15:33 +0000
From: Adolfo Builes <builes.ado...@googlemail.com>
Subject: [Haskell-beginners] Counting Fruits
To: Beginners@haskell.org
Message-ID:
        <b04662900902191515m64e707afo1937a839ba6fc...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hello everyone ,
I wanted to do a small program which read a txt with fruit's name in each
line and then print how many fruits I have of each type. something like
these:
  apple
  apple

and then

[(apple,2)]

I came up whit this

import qualified Data.Map as Map
import Data.List
import System.IO

main =
    do
      file <- readFile "fruits.txt"
      let answer = proccessFile $ lines file

      putStrLn (show answer)

proccessFile :: [String] -> [(String,Int)]
proccessFile file = Map.toAscList $ parseFile Map.empty  file
    where parseFile fruits [] = fruits
          parseFile fruits_map (x:xs) = parseFile (Map.insertWith (+)
x 1 fruits_map) xs


It works, but I would like to know how would  you do it ?,  Share different
points of view, different code. Was it a good idea to use a Map  ?, Did I
separate the code  in a proper way, I mean pure - impure ? How can we
improve the performance ?

Best Regards for everyone.


Adolfo
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090219/1162574a/attachment-0001.htm

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

Message: 7
Date: Thu, 19 Feb 2009 21:01:24 -0800
From: Alexander Dunlap <alexander.dun...@gmail.com>
Subject: Re: [Haskell-beginners] Counting Fruits
To: Adolfo Builes <builes.ado...@googlemail.com>
Cc: Beginners@haskell.org
Message-ID:
        <57526e770902192101n6666ea99h317ea5cb22db7...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

 On Thu, Feb 19, 2009 at 3:15 PM, Adolfo Builes
<builes.ado...@googlemail.com> wrote:
> Hello everyone ,
> I wanted to do a small program which read a txt with fruit's name in each
> line and then print how many fruits I have of each type. something like
> these:
>   apple
>   apple
>
> and then
>
> [(apple,2)]
>
> I came up whit this
>
> import qualified Data.Map as Map
> import Data.List
> import System.IO
>
> main =
>     do
>       file <- readFile "fruits.txt"
>       let answer = proccessFile $ lines file
>
>
>       putStrLn (show answer)
>
> proccessFile :: [String] -> [(String,Int)]
> proccessFile file = Map.toAscList $ parseFile Map.empty  file
>     where parseFile fruits [] = fruits
>           parseFile fruits_map (x:xs) = parseFile (Map.insertWith (+) x 1
> fruits_map) xs
>
>
> It works, but I would like to know how would  you do it ?,  Share different
> points of view, different code. Was it a good idea to use a Map  ?, Did I
> separate the code  in a proper way, I mean pure - impure ? How can we
> improve the performance ?
>
> Best Regards for everyone.
>
>
> Adolfo

You spelled "process" incorrectly ;). Not a big deal of course, just
makes your code a bit cleaner-looking.

In terms of actual code, I think "proccessFruits" could probably be
rewritten more clearly (and perhaps more efficiently, due to rewrite
rules) using a fold. You might also check out the "group" function
from Data.List, although that approach would probably be a bit slower.

Hope that helps.

Alex


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

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


End of Beginners Digest, Vol 8, Issue 16
****************************************

Reply via email to