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

Thomas Hartman tphyahoo at gmail.com
Thu Mar 26 20:15:27 EDT 2009


Luke, does your explanation to Guenther have anything to do with
coinduction? -- the property that a producer gives a little bit of
output at each step of recursion, which a consumer can than crunch in
a lazy way?

I find that coinduction seems to figure frequently in algos that
process a stream.

So, Guenther, I'm not certain if coinduction figures in here yet but
it gives you another thing to google on. Co-induction seems to play
the same role for stream processing in haskell that tail recursiveness
plays in non-lazy languages
like lisp. That is, it's kind of the ideal to be striven for. Whereas
in haskell, tail recursive is frequently not the best thing because it
goes into a non-terminating state when there is an infinite data
structure which is crunched down to a finite one but at the wrong
point in the function pipeline.

see http://groups.google.com/group/fa.haskell/browse_thread/thread/4240bc7c7abd4d30/49f28f5a41519335?q="it+is+however+nicely+coinductive"#49f28f5a41519335


2009/3/26 Luke Palmer <lrpalnmer at gmail.com>:
> On Thu, Mar 26, 2009 at 12:21 PM, GüŸnther Schmidt <gue.schmidt at web.de>
> wrote:y
>>
>> 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.
>
> Sorry, I meant to respond earlier.
>
> They say you don't really understand something until you can explain it to a
> six year old.  So trying to explain this to a colleague made me realize how
> little I must understand it :-).  But I'll try by saying whatever come to
> mind...
>
> Lazy list processing is all about right associativity.  We need to be able
> to output some information knowing that our input looks like a:b:c:...,
> where we don't know the ...  I see IntTrie [a] as an infinite collection of
> lists (well, it is [[a]], after all :-), one for each integer.  So I want to
> take a structure like this:
>
> (1,2):(3,4):(3,5):...
>
> And turn it into a structure like this:
>
> {
> 0 -> ...
> 1 -> 2:...
> 2 -> ...
> 3 -> 4:5:...
> ...
> }
>
> (This is just a list in my implementation, but I intended it to be a trie,
> ideally, which is why I wrote the keys explicitly)
>
> So the yet-unknown information at the tail of the list turns into
> yet-unknown information about the tails of the keys.  In fact, if you
> replace ... with _|_, you get exactly the same thing (this is no
> coincidence!)
>
> The spine of this trie is maximally lazy: this is key.  If the structure of
> the spine depended on the input data (as it does for Data.Map), then we
> wouldn't be able to process infinite data, because we can never get it all.
> So even making a trie out of the list _|_ gives us:
>
> { 0 -> _|_, 1 -> _|_, 2 -> _|_, ... }
>
> I.e. the keys are still there.  Then we can combine two tries just by
> combining them pointwise (which is what infZipWith does).  It is essential
> that the pattern matches on infZipWith are lazy. We're zipping together an
> infinite sequence of lists, and normally the result would be the length of
> the shortest one, which is unknowable.  So the lazy pattern match forces the
> result ('s spine) to be infinite.
>
> Umm... yeah, that's a braindump.   Sorry I couldn't be more helpful.  I'm
> happy to answer any specific questions.
>
> Luke
>
>>
>>
>> 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
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


More information about the Haskell-Cafe mailing list