[Haskell-cafe] Weaving fun
Chris Kuklewicz
haskell at list.mightyreason.com
Fri Apr 13 08:03:28 EDT 2007
The fun never ends...
Bas van Dijk wrote:
> On 4/11/07, Chris Kuklewicz <haskell at list.mightyreason.com> wrote:
>> ...
>> My previous weave, uses composition of (xs:) thunks instead of pairs:
>>
>> > weave :: [[a]] -> [a]
>> > weave [] = []
>> > weave xss = helper id xss
>> > where helper :: ([[a]] -> [[a]]) -> [[a]] -> [a]
>> > helper _rest ([]:_xss) = [] -- done
>> > helper rest [] = weave (rest [])
>> > helper rest ((x:xs):xss) = x : helper (rest . (xs:)) xss
The difference list is built with id and (rest . (xs:)) and (rest [])
>>
>> One might imagine an 'optimized' case like in weave':
>>
>> > -- helper rest ((x:[]):xss) = let yss = rest ([]:[])
>> > -- in x : helper (const yss) xss
>> ...
>
> Nice! The iteration over the list can be abstracted using foldr:
>
>> weave :: [[a]] -> [a]
>> weave [] = []
>> weave xss = foldr f (\rest -> weave $ rest []) xss id
>> where
>> f [] _ = \_ -> []
>> f (x:xs) g = \rest -> x : g (rest . (xs:))
That abstraction kills my ability to quickly see what is going on.
Renaming this to weavefgh and adding type signatures:
> weavefgh :: [[a]] -> [a]
> weavefgh [] = []
> weavefgh xss = h xss id
>
> h :: [[a]]
> -> ([[a]] -> [[a]]) -> [a]
> h = foldr f g
>
> g :: ([[a]] -> [[a]]) -> [a]
> g rest = weavefgh (rest [])
>
> f :: [a]
> -> (([[a]] -> [[a]]) -> [a])
> -> ([[a]] -> [[a]]) -> [a]
> f [] _ = \_ -> []
> f (x:xs) g = \rest -> x : g (rest . (xs:))
Here we can see that the foldr builds a function h which is supplied id.
let xss = [x1:x1s,x2:x2s] in
h xss = foldr f g [(x1:x1s),(x2:x2s)]
= (x1:x1s) `f` (foldr f g [(x2:x2s)])
= f (x1:x1s) (foldr f g [(x2:x2s)])
= \rest -> x1 : (foldr f g [(x2:x2s)]) (rest . (x1s:))
h xss id = x1 : (foldr f g [(x2:x2s)]) (id . (x1s:))
demanding the next element will compute...
= x1 : (f (x2:x2s) (foldr f g []) (id . (x1s:))
= x1 : (\rest -> x2 : (foldr f g []) (rest . (x2s:))) (id . (x1s:))
= x1 : x2 : (foldr f g []) (id . (x1s:) . (x2s:))
demanding the next element will compute...
= x1 : x2 : g (id . (x1s:) . (x2s:))
= x1 : x2 : weavefgs ((id . (x1s:) . (x2s:)) [])
= x1 : x2 : weavefgh [x1s,x2s]
which now can been see to work as desired. The end of the foldr is g which
calls weavefgh which, if there is still work, call h/foldr again.
>
> This is beginning to look scary :-) To enable your last optimization
> you can replace the last alternative of 'f' by:
>
>> f (x:xs) g = \rest -> x : g (\l -> rest $ case xs of
>> [] -> [[]]
>> xs -> xs:l
>> )
>
More information about the Haskell-Cafe
mailing list