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: Counting Fruits (Heinrich Apfelmus)
   2.  flip lookup in ghci (Matt R)
   3. Re:  flip lookup in ghci (Rafael Gustavo da Cunha Pereira Pinto)
   4. Re:  flip lookup in ghci (Matt R)
   5. Re:  flip lookup in ghci (Felipe Lessa)
   6. Re:  flip lookup in ghci (Magnus Therning)
   7.  Help with monads (I think...) (Patrick LeBoutillier)
   8. Re:  Help with monads (I think...) (Daniel Fischer)
   9. Re:  Help with monads (I think...) (Thomas Davie)


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

Message: 1
Date: Fri, 20 Feb 2009 11:15:03 +0100
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: Counting Fruits
To: beginners@haskell.org
Message-ID: <gnlvpf$59...@ger.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1

Adolfo Builes wrote:
> 
> 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 with 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 ?

Looks good to me. :)

Here's how I would write it

    main = print . process . lines =<< readFile "fruits.txt"

    process :: [String] -> [(String,Int)]
    process = Map.toAscList . foldl f Map.empty
        where f map x = Map.insertWith (+) x 1 map


So, the  parseFile  function is best expressed as a left fold and
function composition is good style.


The above works fine for smaller files. If you have larger amounts of
data, you will need a few strictness annotations or there will be a
space leak. In this case, this means using the functions

    foldl'  and  Map.insertWith'

instead of

    foldl   and  Map.insertWith

But I wouldn't bother about that for now.


Regards,
apfelmus

--
http://apfelmus.nfshost.com



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

Message: 2
Date: Fri, 20 Feb 2009 10:27:50 +0000
From: Matt R <mattrussell...@googlemail.com>
Subject: [Haskell-beginners] flip lookup in ghci
To: beginners@haskell.org
Message-ID:
        <2f9e00bc0902200227v3a0213f6v1329969ee174c...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

So what's this all about then? How come a has become ()?

  ghci> :t lookup
  lookup :: (Eq a) => a -> [(a, b)] -> Maybe b
  ghci> :t flip lookup
  flip lookup :: (Eq a) => [(a, b)] -> a -> Maybe b
  ghci> let lookupIn = (flip lookup :: (Eq a) => [(a, b)] -> a -> Maybe b )
  ghci> :t lookupIn
  lookupIn :: [((), b)] -> () -> Maybe b


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

Message: 3
Date: Fri, 20 Feb 2009 09:11:12 -0300
From: Rafael Gustavo da Cunha Pereira Pinto
        <rafaelgcpp.li...@gmail.com>
Subject: Re: [Haskell-beginners] flip lookup in ghci
To: Matt R <mattrussell...@googlemail.com>
Cc: beginners@haskell.org
Message-ID:
        <351ff25e0902200411l6b02e8cu40cf1ce50bba9...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

you are applying the type to lookup only!

try let lookupIn = ((flip lookup ) :: (Eq a) => [(a, b)] -> a -> Maybe b )

On Fri, Feb 20, 2009 at 07:27, Matt R <mattrussell...@googlemail.com> wrote:

> So what's this all about then? How come a has become ()?
>
>  ghci> :t lookup
>  lookup :: (Eq a) => a -> [(a, b)] -> Maybe b
>  ghci> :t flip lookup
>  flip lookup :: (Eq a) => [(a, b)] -> a -> Maybe b
>  ghci> let lookupIn = (flip lookup :: (Eq a) => [(a, b)] -> a -> Maybe b )
>  ghci> :t lookupIn
>  lookupIn :: [((), b)] -> () -> Maybe b
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
Rafael Gustavo da Cunha Pereira Pinto
Electronic Engineer, MSc.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090220/06daa777/attachment-0001.htm

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

Message: 4
Date: Fri, 20 Feb 2009 12:44:30 +0000
From: Matt R <mattrussell...@googlemail.com>
Subject: Re: [Haskell-beginners] flip lookup in ghci
To: Rafael Gustavo da Cunha Pereira Pinto <rafaelgcpp.li...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <2f9e00bc0902200444r3b74e314v47851cfea0d7f...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Rafael Gustavo da Cunha Pereira Pinto <rafaelgcpp.li...@gmail.com>:
> you are applying the type to lookup only!
>
> try let lookupIn = ((flip lookup ) :: (Eq a) => [(a, b)] -> a -> Maybe b )

Oops, I didn't mean to include my attempts at type annotation in my
previous email...I meant to write

ghci> let lookupIn = flip lookup

But it doesn't seem to make any difference either way. I still get

ghci> :t lookupIn
lookupIn :: [((), b)] -> () -> Maybe b

regardless :(

-- Matt


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

Message: 5
Date: Fri, 20 Feb 2009 10:06:07 -0300
From: Felipe Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] flip lookup in ghci
To: Matt R <mattrussell...@googlemail.com>
Cc: beginners@haskell.org,      Rafael Gustavo da Cunha Pereira Pinto
        <rafaelgcpp.li...@gmail.com>
Message-ID:
        <c2701f5c0902200506o21d1f92avf1c2adff91ab2...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Let's try to see what is going on using GHCi 6.10.1:

  Prelude> :t lookup
  lookup :: (Eq a) => a -> [(a, b)] -> Maybe b
  Prelude> :t flip lookup
  flip lookup :: (Eq a) => [(a, b)] -> a -> Maybe b

Everything ok. Lets try binding:

  Prelude> let f = flip lookup
  Prelude> :t f
  f :: [((), b)] -> () -> Maybe b

Woops. Whenever you see a type of a function becoming less polymorphic
than you expected, try adding a parameter:

  Prelude> let g x = flip lookup x
  Prelude> :t g
  g :: (Eq a) => [(a, b)] -> a -> Maybe b

Nice! Let's try again without the monomorphism restriction[1]

  Prelude> :s -XNoMonomorphismRestriction
  Prelude> let h = flip lookup
  Prelude> :t h
  h :: (Eq a) => [(a, b)] -> a -> Maybe b
  Prelude> :s -XMonomorphismRestriction

So, that's where the culprit lies! As we declared 'f' without a type
signature and without explicit arguments, the monomorphism restriction
didn't let us overload our function with the 'Eq' class.

Note that if we activated all warnings, GHC would tell us that
something is wrong:

  Prelude> :s -Wall
  Prelude> let j = flip lookup
  <interactive>:1:13:
      Warning: Defaulting the following constraint(s) to type `()'
               `Eq a' arising from a use of `lookup' at <interactive>:1:13-18
      In the first argument of `flip', namely `lookup'
      In the expression: flip lookup
      In the definition of `j': j = flip lookup

We can't just remove the 'Eq' constraint, if we want to refine the
type of 'lookup' then we need to supply something that implements
'Eq'. As GHC doesn't know what you want to do, it just defaults to ().
If, for example, you used the new function in the same let-binding,
GHC would infer another type and show no warnings:

  Prelude> let k = flip lookup; l = k [] (1 :: Int)
  Prelude> :t k
  k :: [(Int, b)] -> Int -> Maybe b

But note that even if you use the function where you defined it, it
can't be polymorphic

  Prelude> let m = flip lookup; n = m [] (1 :: Int); o = m [] (1 :: Double)
  <interactive>:1:52:
      Couldn't match expected type `Int' against inferred type `Double'
      In the second argument of `m', namely `(1 :: Double)'
      In the expression: m [] (1 :: Double)
      In the definition of `o': o = m [] (1 :: Double)

In short: add an explicit parameter or use a type signature. =)

Hope that helps!

[1] http://www.haskell.org/haskellwiki/Monomorphism_restriction

-- 
Felipe.


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

Message: 6
Date: Fri, 20 Feb 2009 13:06:22 +0000
From: Magnus Therning <mag...@therning.org>
Subject: Re: [Haskell-beginners] flip lookup in ghci
To: Matt R <mattrussell...@googlemail.com>
Cc: beginners@haskell.org,      Rafael Gustavo da Cunha Pereira Pinto
        <rafaelgcpp.li...@gmail.com>
Message-ID:
        <e040b520902200506t5673e36fxb9e0d65fb1780...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Fri, Feb 20, 2009 at 12:44 PM, Matt R <mattrussell...@googlemail.com> wrote:
> Rafael Gustavo da Cunha Pereira Pinto <rafaelgcpp.li...@gmail.com>:
>> you are applying the type to lookup only!
>>
>> try let lookupIn = ((flip lookup ) :: (Eq a) => [(a, b)] -> a -> Maybe b )
>
> Oops, I didn't mean to include my attempts at type annotation in my
> previous email...I meant to write
>
> ghci> let lookupIn = flip lookup
>
> But it doesn't seem to make any difference either way. I still get
>
> ghci> :t lookupIn
> lookupIn :: [((), b)] -> () -> Maybe b
>
> regardless :(

Indeed, how funky:

  GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
  Loading package base ... linking ... done.
  Prelude> :t flip lookup
  flip lookup :: (Eq a) => [(a, b)] -> a -> Maybe b
  Prelude> let lookupIn = flip lookup
  Prelude> :t lookupIn
  lookupIn :: [((), b)] -> () -> Maybe b
  Prelude>

/M

-- 
Magnus Therning                        (OpenPGP: 0xAB4DFBA4)
magnus@therning.org          Jabber: magnus@therning.org
http://therning.org/magnus         identi.ca|twitter: magthe


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

Message: 7
Date: Fri, 20 Feb 2009 19:30:05 -0500
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: [Haskell-beginners] Help with monads (I think...)
To: beginners <beginners@haskell.org>
Message-ID:
        <b217a64f0902201630p29440fadid342841062589...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi all,

I'm trying to implement the following simple Perl program in Haskell:

  my $nb_tests = 0 ;

  sub ok {
          my $bool = shift ;
          $nb_tests++ ;
          print STDOUT ($bool ? "ok" : "nok") . " $nb_tests\n" ;
  }

  ok(0) ;
  ok(1) ;

The output is:

  nok 1
  ok 2

I'm pretty much a Haskell newbie, but I know a bit about monads (and
have been reading "Real World Haskell"), and I think I need to put the
ok function must live inside some kind of state monad. My problem is
that I also would like the ok function to perform some IO (as shown
above, print).

How is a case like this handled? Can my function live in 2 monads?


Thanks a lot,

Patrick

-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


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

Message: 8
Date: Sat, 21 Feb 2009 01:54:56 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Help with monads (I think...)
To: Patrick LeBoutillier <patrick.leboutill...@gmail.com>,      beginners
        <beginners@haskell.org>
Message-ID: <200902210154.56471.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Samstag, 21. Februar 2009 01:30 schrieb Patrick LeBoutillier:
> Hi all,
>
> I'm trying to implement the following simple Perl program in Haskell:
>
>   my $nb_tests = 0 ;
>
>   sub ok {
>           my $bool = shift ;
>           $nb_tests++ ;
>           print STDOUT ($bool ? "ok" : "nok") . " $nb_tests\n" ;
>   }
>
>   ok(0) ;
>   ok(1) ;
>
> The output is:
>
>   nok 1
>   ok 2
>
> I'm pretty much a Haskell newbie, but I know a bit about monads (and
> have been reading "Real World Haskell"), and I think I need to put the
> ok function must live inside some kind of state monad. My problem is
> that I also would like the ok function to perform some IO (as shown
> above, print).
>
> How is a case like this handled? Can my function live in 2 monads?

Yes, it can:
--------------------
module OK where
import Control.Monad.State

ok :: Bool -> StateT Int IO ()
ok b = do
    increment
    nr <- get
    lift $ putStrLn $ (if b then "ok " else "nok ") ++ show nr

increment :: StateT Int IO ()
increment = modify succ

main :: IO ()
main = evalStateT (ok False >> ok True) 0
--------------------

Loading package base ... linking ... done.
[1 of 1] Compiling OK               ( OK.hs, interpreted )
Ok, modules loaded: OK.
*OK> main
Loading package mtl-1.1.0.1 ... linking ... done.
nok 1
ok 2

What you need for this kind of stuff is a monad-transformer, there are 
transformers for most(? many, anyway) monads, recognizable by ending in T.
They wrap one monad (here IO) inside another (State), combining their 
respective abilities.

I'm sure there's lots of useful stuff on monad-transformers in the wikibook, 
too - they should also be treated in RWH, because in real-world apps you tend 
to need them:)

>
>
> Thanks a lot,
>
> Patrick

Cheers,
Daniel



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

Message: 9
Date: Sat, 21 Feb 2009 10:59:09 +0100
From: Thomas Davie <tom.da...@gmail.com>
Subject: Re: [Haskell-beginners] Help with monads (I think...)
To: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Cc: beginners <beginners@haskell.org>
Message-ID: <3f163140-acab-4202-9b98-2269cf2e8...@gmail.com>
Content-Type: text/plain; charset="windows-1252"


On 21 Feb 2009, at 01:30, Patrick LeBoutillier wrote:

> Hi all,
>
> I'm trying to implement the following simple Perl program in Haskell:
>
>  my $nb_tests = 0 ;
>
>  sub ok {
>          my $bool = shift ;
>          $nb_tests++ ;
>          print STDOUT ($bool ? "ok" : "nok") . " $nb_tests\n" ;
>  }
>
>  ok(0) ;
>  ok(1) ;
>
> The output is:
>
>  nok 1
>  ok 2
>
> I'm pretty much a Haskell newbie, but I know a bit about monads (and
> have been reading "Real World Haskell"), and I think I need to put the
> ok function must live inside some kind of state monad. My problem is
> that I also would like the ok function to perform some IO (as shown
> above, print).
>
> How is a case like this handled? Can my function live in 2 monads?

I personally wouldn't use two monads at all for this – in fact, I'd  
only use IO in one function:

main = putStr . unlines . results inputs . snd . tests $ inputs

inputs = [1,2]

tests = foldr (\_ (x,l) -> (not x, x:l)) (True,[])

results = zipWith result
result testN True  = "ok "  ++ show testN
result testN False = "nok " ++ show testN

Bob
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090221/c1482bc2/attachment.htm

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

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


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

Reply via email to