Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-27 Thread Ketil Malde
Udo Stenzel wrote: That raises the question: Should combining functions on containers be provided in a strict variant? Should strict application be the default? With the exception of lists, I generally tend to want strict behavior for collections. Combined with the principle of least

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-27 Thread Ketil Malde
Scherrer, Chad wrote: Sorry to drag this thread out, but here's one more thing you might try... (This is the café, isn't it? :-) Another option is perhaps to pack both char and count in one Int and use some kind of Set. This should save some space, and possibly time as well (presuming

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-27 Thread Benjamin Franksen
On Thursday 27 October 2005 10:29, Ketil Malde wrote: Scherrer, Chad wrote: Sorry to drag this thread out, but here's one more thing you might try... (This is the café, isn't it? :-) Another option is perhaps to pack both char and count in one Int and use some kind of Set. This should

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-26 Thread Pedro Baltazar Vasconcelos
Two solutions using immutable and mutable arrays and no unsafe operations: module Main where import Control.Monad.ST import Data.Ix import Data.Array import Data.Array.MArray import Data.Array.ST -- using immutable arrays hist1 :: String - Array Char Int hist1 str = accumArray (+) 0

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-26 Thread Udo Stenzel
Pedro Baltazar Vasconcelos wrote: Two solutions using immutable and mutable arrays and no unsafe operations: Both solutions certainly count as nice, but both exhibit an ugly memory leak. As usual, this is due to too much laziness: no intermediate result is ever evaluated until it is too late.

[Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-26 Thread Scherrer, Chad
Sorry to drag this thread out, but here's one more thing you might try... I was thinking, if we just wanted something like intTable :: [Int] - [(Int, Int)] we could just replace Map with IntMap in the previous solution: intTable xs = IntMap.assocs $! foldl' f IntMap.empty xs where f m x =

[Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-25 Thread Charles SDudu
Hello, I need to calculate the frequency of each character in a String. And if I can do this really well in C, I dont find a nice (and fast) answer in haskell. I tried several functions, listed below, and even the fastest do a lot of unnecessary things : calc :: String - [ (Char, Int) ] --

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-25 Thread Lemmih
On 10/25/05, Charles SDudu [EMAIL PROTECTED] wrote: Hello, I need to calculate the frequency of each character in a String. And if I can do this really well in C, I dont find a nice (and fast) answer in haskell. I tried several functions, listed below, and even the fastest do a lot of

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-25 Thread Jon Fairbairn
On 2005-10-25 at 12:20+0200 Lemmih wrote: On 10/25/05, Charles SDudu [EMAIL PROTECTED] wrote: Hello, I need to calculate the frequency of each character in a String. And if I can do this really well in C, I dont find a nice (and fast) answer in haskell. I tried several functions, listed

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-25 Thread Adrian Hey
On Tuesday 25 Oct 2005 10:40 am, Charles SDudu wrote: Hello, I need to calculate the frequency of each character in a String. Something like this maybe (untested code ahead).. import Data.COrdering import Data.Tree.AVL calc :: String - [(Char,Int)] calc cs = asListL (genAsTree cc [(c,1) | c -

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-25 Thread Charles SDudu
It seems like the fastest way to build a list of frequency from a string is this : import Data.Array (assocs, accumArray, Array) frequency :: String - [(Char,Int)] frequency = filter (\f - snd f0) . assocs . accumArray (+) 0 ('\0', '\255') . map (\x-(x,1)) -- (~1.3 sec on a string of 700ko)

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-25 Thread Sebastian Sylvan
On 10/25/05, Charles SDudu [EMAIL PROTECTED] wrote: It seems like the fastest way to build a list of frequency from a string is this : import Data.Array (assocs, accumArray, Array) frequency :: String - [(Char,Int)] frequency = filter (\f - snd f0) . assocs . accumArray (+) 0 ('\0', '\255')

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-25 Thread Lennart Augustsson
Sebastian Sylvan wrote: Also, you may use STArrays (I think they come in unboxed as well) for stateful code, which may be even faster (unless accumArray does some neat trick to make it O(m) where m is the number of index/value pairs). The whole idea with having accumArray as part of the Array