Re: hashmap withdrawal and poor haskell style

2002-04-04 Thread Long Goodbye
module Main where main = do content <- getContents let starstat = oneline content alphabet = ['a'..'z'] count ch = length . filter (==ch) oneline str ch = [ch] ++ " " ++ stars (count ch str) stars x = take x ['*','*'..] s

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread Daan Leijen
lt;[EMAIL PROTECTED]> To: "Daan Leijen" <[EMAIL PROTECTED]> Cc: "Michal Wallace" <[EMAIL PROTECTED]>; <[EMAIL PROTECTED]> Sent: Wednesday, April 03, 2002 5:54 PM Subject: Re: hashmap withdrawal and poor haskell style ons 2002-04-03 klockan 15.51 skrev Daan L

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread Yoann Padioleau
Remi Turk <[EMAIL PROTECTED]> writes: > > > module Main where > > import Char > import FiniteMap > > printCount :: (Char, Integer) -> IO () > printCount (letter, count) > =3D putStrLn $ letter : replicate count '*' > > countLetters:: String -> [(Cha

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread Remi Turk
On Wed, Apr 03, 2002 at 07:13:03AM -0500, Michal Wallace wrote: > > 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 let

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread Martin Norbäck
ons 2002-04-03 klockan 15.51 skrev Daan Leijen: > > import Array > > > > type Histogram = Array Char Int > > > > histogram :: String -> Histogram > > histogram input > >= accumArray (+) 0 (minBound,maxBound) [(c,1) | c <- input] > > (The "minBound" and "maxBound" functions are overloaded fro

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread Dean Herington
Michal, As Daan Leijen has suggested, `accumArray` is probably the best solution to your simple histogramming problem. However, you might also be interested to learn about "finite maps", which are often the appropriate functional analogue to "hash maps". Finite maps are typically implemented

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread Yoann Padioleau
Michal Wallace <[EMAIL PROTECTED]> writes: > module Main where > alphabet = "abcdefghijklmnopqrstuvwxyz" in haskell you can do alphabet = ['a'..'z'] > count ch str = length [c | c <- str , c == ch] can do count c s = length (filter (c ==) s) or more cryptic: count c = length . (filte

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread Daan Leijen
an. ----- Original Message - From: "Michal Wallace" <[EMAIL PROTECTED]> To: "D. Tweed" <[EMAIL PROTECTED]> Cc: <[EMAIL PROTECTED]> Sent: Wednesday, April 03, 2002 2:40 PM Subject: Re: hashmap withdrawal and poor haskell style > On Wed, 3 Apr 2002, D. Tw

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread Jan de Wit
> On Wed, 3 Apr 2002, D. Tweed wrote: > > > > main = do content <- getContents > > > let rpt letter = report content letter > > > loop rpt alphabet > > > I'm a bit confused how this can have worked... in Haskell `let' is used in > > the context of a `let ..<1>.. in

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread D. Tweed
> It's correct Haskell. Have a look at > http://www.haskell.org/onlinereport/exps.html#sect3.14 Thanks; serves me right for being lazy and not having actually read a version of the report since the various elements of monad syntax were introduced... ___cheers,_dave___

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread Michal Wallace
On Wed, 3 Apr 2002, D. Tweed wrote: > > main = do content <- getContents > > let rpt letter = report content letter > > loop rpt alphabet > I'm a bit confused how this can have worked... in Haskell `let' is used in > the context of a `let ..<1>.. in ..<2>..' where

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread Rijk J. C. van Haaften
At 13:27 03-04-02 +0100, D. Tweed wrote: >On Wed, 3 Apr 2002, Michal Wallace wrote: > > > 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

Re: hashmap withdrawal and poor haskell style

2002-04-03 Thread D. Tweed
On Wed, 3 Apr 2002, Michal Wallace wrote: > 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

hashmap withdrawal and poor haskell style

2002-04-03 Thread Michal Wallace
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):