hashmap withdrawal and poor haskell style

Michal Wallace sabren@manifestation.com
Wed, 3 Apr 2002 07:13:03 -0500 (EST)


Hello everyone,

I just wrote my first haskell program. I started with a
simple python program and tried to see if I could port it to
haskell.  The program reads text from stdin and prints out a
histogram of all the letters:

"""
alphabet = 'abcdefghjiklmnopqrstuvwxyz'

def letter_count(lines):
    res = {}
    for line in lines:
        for char in line.lower():
            if char not in alphabet:
                continue
            if res.has_key(char):
                res[char] += 1
            else:
                res[char] = 1
    return res

if __name__=="__main__":
    import sys
    hist = letter_count(sys.stdin)
    for letter in alphabet:
        print letter, "*" * hist.get(letter, 0)
"""

Kid stuff, but it took me about 10 hours to port it... :)

Here's what I came up with:


"""
module Main where
    alphabet = "abcdefghijklmnopqrstuvwxyz"
    count ch str = length [c | c <- str , c == ch]
    hist str = [count letter str | letter <- alphabet]
    oneline ch str = [ch] ++ " " ++ stars (count ch str)
    stars x = if x == 0
              then ""
              else "*" ++ stars ( x - 1 )
    report str ch = do putStrLn ( oneline ch str )
    loop f (h:t) = if t == []
                   then f h
                   else do f h
                           loop f t
    main = do content <- getContents
              let rpt letter = report content letter
              loop rpt alphabet
"""

Other than ignoring upper case letters, and being really
really slow, it seems to work fine in hugs....

One thing I really missed was a hash / dictionary. I
tried for about an hour to use Assoc following the
examples from PLEAC:

http://pleac.sourceforge.net/pleac_haskell/hashes.html


... But I never got it working:


:> module Main where
:>     import Assoc (empty)
:>     main :: IO()
:>     main = do line <- getContents
:>               let w = length line
:>                   count:: AssocDefault String Int
:>                        count = w.foldl (\a s -> a.update s (+1)) empty
:>               print x

-> ERROR "alphahist.hs":6 - Undefined type constructor "AssocDefault"

(I couldn't get Assoc to work either, even with "Import
Assoc (Assoc)" though I looked in the Assoc.hs file and
could see it in there.. This was the most frustrating part
of the experiment)

Can anyone point me in the right direction here?

Also, I'd really like to here anyone's thoughts on the code
I have above, especially concercing what I could have done
better. :)

Thanks!

Cheers,

- Michal   http://www.sabren.net/   sabren@manifestation.com 
------------------------------------------------------------
Give your ideas the perfect home: http://www.cornerhost.com/
 cvs - weblogs - php - linux shell - perl/python/cgi - java
------------------------------------------------------------