Comments and/or Criticisms

Hi Any comments and/or criticisms would be most appreciated: --count the occurrences of char in string countC :: Char -> [Char] -> Int countC x xs = sum [1 | c <- xs, c == x] --count occurrences of chars in string countCS :: [Char] -> [(Char, Int)] countCS xs = [(x, (countC x xs)) | x <- [' '..'z'], (countC x xs) > 0] Can anyone come up with a better alternative? Thanks, Paul

On 9/10/07, PR Stanley
Can anyone come up with a better alternative?
*puts on his pointfree hat* import Control.Arrow ((&&&)) import Data.List (group, sort) countCS :: [Char] -> [(Char, Int)] -- Char can be generalised to any Ord countCS = map (head &&& length) . group . sort Stuart

I wanted to use the standard name for the function pair :: (a -> b) -> (a -> c) -> (a -> (b,c)) pair f g x = (f x, g x) but I can find no such function in the Report or its Libraries. Is there a recommended name for this?

On 9/9/07, ok
I wanted to use the standard name for the function
pair :: (a -> b) -> (a -> c) -> (a -> (b,c))
pair f g x = (f x, g x)
but I can find no such function in the Report or its Libraries. Is there a recommended name for this?
It is called (&&&) and is avaiable from Control.Arrow. -- Felipe.

Alternatives; use your own judgment: PR Stanley wrote:
--count the occurrences of char in string countC :: Char -> [Char] -> Int countC x xs = sum [1 | c <- xs, c == x]
-- Direct mind-mapping of my brain: countC x = length . filter (c ==) -- Avoids constructing an intermediate list? I dunno. Looks stupid: countC x = foldr (\c s -> s + if c == x then 1 else 0) 0
--count occurrences of chars in string countCS :: [Char] -> [(Char, Int)] countCS xs = [(x, (countC x xs)) | x <- [' '..'z'], (countC x xs) > 0]
-- What popped into my imperative little brain import Data.Map(assocs, empty, insertWith) countCS str = assocs (countCS' str) where countCS' [] = empty countCS' (x:xs) = insertWith (+) x 1 (countCS' xs) -- but Stuart's pointfree version is so much nicer. Devin

On 9/10/07, PR Stanley
Hi Any comments and/or criticisms would be most appreciated: --count the occurrences of char in string countC :: Char -> [Char] -> Int countC x xs = sum [1 | c <- xs, c == x]
That's a clever implementation, but I think there are clearer ways of achieving the same goal. You could replace sum with length and get the same answer, at which point the list comprehension isn't buying you much. How about this? countC ch xs = length $ filter (ch ==) xs
--count occurrences of chars in string countCS :: [Char] -> [(Char, Int)] countCS xs = [(x, (countC x xs)) | x <- [' '..'z'], (countC x xs) > 0]
A few things to note: * Those extra parens around countC are unnecessary; function application has highest precedence. * [' '..'z'] has a few issues: it misses a few ASCII characters (including all the control codes), and won't catch non-ASCII characters. * Duplicating the call to countC will probably result in redundant evaluation, so it's best to avoid that if possible -- difficult to avoid cleanly inside a comprehension though. * Scanning the string repeatedly for each potential character [' '..'z'] seems excessive, especially if you want to expand it to include non-ASCII. Better just to deal with the characters actually in the string as they appear, I think. Stuart

On Sep 10, 2007, at 1:47 , Stuart Cook wrote:
On 9/10/07, PR Stanley
wrote: --count occurrences of chars in string countCS :: [Char] -> [(Char, Int)] countCS xs = [(x, (countC x xs)) | x <- [' '..'z'], (countC x xs)
0]
A few things to note:
My naive take on it: import Data.List import Control.Monad.Reader countCS = map (liftM2 (,) head length) . group . sort -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Mon, 2007-09-10 at 15:47 +1000, Stuart Cook wrote:
On 9/10/07, PR Stanley
wrote: Hi Any comments and/or criticisms would be most appreciated: --count the occurrences of char in string countC :: Char -> [Char] -> Int countC x xs = sum [1 | c <- xs, c == x]
That's a clever implementation, but I think there are clearer ways of achieving the same goal. You could replace sum with length and get the same answer, at which point the list comprehension isn't buying you much.
How about this?
countC ch xs = length $ filter (ch ==) xs
--count occurrences of chars in string countCS :: [Char] -> [(Char, Int)] countCS xs = [(x, (countC x xs)) | x <- [' '..'z'], (countC x xs) > 0]
A few things to note:
* Those extra parens around countC are unnecessary; function application has highest precedence. * [' '..'z'] has a few issues: it misses a few ASCII characters (including all the control codes), and won't catch non-ASCII characters. * Duplicating the call to countC will probably result in redundant evaluation, so it's best to avoid that if possible -- difficult to avoid cleanly inside a comprehension though. * Scanning the string repeatedly for each potential character [' '..'z'] seems excessive, especially if you want to expand it to include non-ASCII. Better just to deal with the characters actually in the string as they appear, I think.
You can use 'let' in a list comprehension, [(x,count) | x <- [' '..'z'], let count = countC x xs, count > 0]

countCS :: [Char] -> [(Char, Int)]
I use this count :: (Ord a, Num b) => [a] -> (a -> b,[(a,b)]) count xs = ( flip (Map.findWithDefault 0) m , Map.assocs m ) where m = Map.fromListWith (+) $ zip xs $ repeat 1 which returns the frequencies list as well as a query function that I found myself quite often useful. /BR
participants (8)
-
Brandon S. Allbery KF8NH
-
Derek Elkins
-
Devin Mullins
-
Felipe Almeida Lessa
-
ok
-
PR Stanley
-
rahn@ira.uka.de
-
Stuart Cook