[Haskell-cafe] Really need some help understanding a solution

GüŸnther Schmidt gue.schmidt at web.de
Thu Mar 26 14:21:21 EDT 2009


Hi guys,

I tried for days now to figure out a solution that Luke Palmer has 
presented me with, by myself, I'm getting nowhere.

He has kindly provided me with this code:

import Data.Monoid

newtype IntTrie a = IntTrie [a]
     deriving Show

singleton :: (Monoid a) => Int -> a -> IntTrie a
singleton ch x = IntTrie $ replicate ch mempty ++ [x] ++ repeat mempty

lookupTrie :: IntTrie a -> Int -> a
lookupTrie (IntTrie xs) n = xs !! n

instance (Monoid a) => Monoid (IntTrie a) where
     mempty                            = IntTrie (repeat mempty)
     mappend (IntTrie xs) (IntTrie ys) = IntTrie (infZipWith mappend xs ys)

infZipWith f ~(x:xs) ~(y:ys) = f x y : infZipWith f xs ys

test =  mconcat [singleton (n `mod` 42) [n] | n <- [0..]] `lookupTrie` 10

It's supposed to eventually help me group a list of key value pairs and 
then further process them in a linear (streaming like) way.

The original list being something like [('a', 23), ('b', 18), ('a', 34) 
...].

There are couple of techniques employed in this solution, but I'm just 
guessing here.

The keywords I've been looking up so far:

Memmoization, Deforestation, Single Pass, Linear Map and some others.

Can someone please fill me in?

Günther



More information about the Haskell-Cafe mailing list