Re: [Haskell-cafe] Grouping - Map / Reduce

Well, this approach has the problem that the running sum of key k blocks
until a new value for that k arrives in the input stream.
If you wanted to know the sum of the values of each key after you got
nelements in the input stream, we could change the valuesWithKey
inner function into:
runningSumsOfValuesPerKey :: (Eq k, Num v) => [k] -> [(k, v)] -> [[v]]
runningSumsOfValuesPerKey allPossibleKeys = runningSums . allValuesPerKey
where
runningSums = map (scanl (+) 0)
allValuesPerKey pairs = [ valuesWithKey key pairs | key <-
allPossibleKeys ]
valuesWithKey key = map (\(k,v) -> if k==key then v else 0)
then map (!!n) on the result of runningSumsOfValuesPerKey gives you the sum
after n elements arrived.
I think if you now generalize this so you don't use 0 but mempty, mconcat
and other Monoid methods, that you might get something like Luke's trie
solution, not sure, Luke is a fair bit smarter than I am :-)
But this code is very inefficient I'm afraid, I guess the blueprint stuff
that was posted really builds a map incrementally, but I don't understand
that yet.
Ik spreek Nederlands ja ('t is te zeggen, "Antwerps").
Yes I'm still learning Haskell, but I think with Haskell this is a never
ending process, since there's soo much stuff to discover and the language
evolves (which makes it both exciting and frustrating, but that's the
dilemma of knowledge anyway, the more you know the better you realize the
vast amount of knowledge that you don't know yet :-)
On Fri, Mar 27, 2009 at 12:53 AM, Guenther Schmidt
Dear Peter,
wow, thanks, this is a very ... interesting ... approach, I hadn't thought about that yet ;)
Ben je nederlands?
In case you'd be interested to share the "road to Haskell" experience with another newbie just ask.
Günther
Peter Verswyvelen schrieb:
I'm also learning Haskell so the solution below might be (1) inefficient
and (2) incorrect, but hey, let's give it a try :-)
For simplicity, in the testing code, I assume an infinite list of key/value pairs where they keys are of type Char between 'a' and 'z' and the values are Integers (the code also seems to work for keys with just a lower bound but no upper bound) I think the code speaks for itself
import System.Random runningSumsOfValuesPerKey :: (Eq k, Num v) => [k] -> [(k, v)] -> [[v]] runningSumsOfValuesPerKey allPossibleKeys = runningSums . allValuesPerKey where runningSums = map (scanl (+) 0) allValuesPerKey pairs = [ valuesWithKey key pairs | key <- allPossibleKeys ] valuesWithKey key = map snd . filter ((==key) . fst) -- Testing randomPairs :: [(Char, Integer)] randomPairs = zip keys values where keys = randomRs ('a','z') rnd1 values = randomRs (0,9) rnd2 (rnd1,rnd2) = split (mkStdGen 0) test = map (take 10) [rs `atKey` 'c', rs `atKey` 'z'] where rs = runningSumsOfValuesPerKey ['a'..] randomPairs xs `atKey` k = xs !! (fromEnum k - fromEnum 'a')

Hello What do you think of this? There is perhaps a recursive call that should be made tail recursive but it seems to work. The 'group' function takes the list of pairs as input and outputs a list of maps from key to sums. The nth element of the list of maps corresponds to the grouping applied for the elements 0....n of the input list of pairs. Thus, that also works on infinite list. Unless I am missing sth... import Data.Map (Map) import qualified Data.Map as Map group :: [(Int,Int)] -> Map Int Int -> [Map Int Int] group [] amap = [] group ((k, v):t) amap = newmap : group t newmap where newmap = (Map.insertWith (+) k v amap) l = [(1,1), (2,10), (1,2), (2,11), (1,3), (2,12)] r = group l Map.empty rr = take 2 r li = concat [ [(1,i), (2, 10*i)] | i <- [0..] ] ri = group li Map.empty rri = take 20 ri Regards J-C
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (2)
-
jean-christophe mincke
-
Peter Verswyvelen