
Hello, For my own exercise I'm writing a function 'weave' that "weaves" a list of lists together. For example: weave [[1,1,1], [2,2,2], [3,3]] ==> [1,2,3,1,2,3,1,2] weave [[1,1,1], [2,2], [3,3,3]] ==> [1,2,3,1,2,3,1] Note that 'weave' stops when a list is empty. Right now I have: weave :: [[a]] -> [a] weave ll = work ll [] [] where work ll = foldr f (\rst acc -> work (reverse rst) [] acc) ll f [] g = \_ acc -> reverse acc f (x:xs) g = \rst acc -> g (xs:rst) (x:acc) However I find this definition hard to read and I'm questioning its efficiency especially due to the 'reverse' parts (how do they impact performance and can they be removed?) So I'm wondering if 'weave' can be defined more "elegantly" (better readable, shorter, more efficient, etc.)? happy hacking, Bas van Dijk

On Wed, Apr 11, 2007 at 12:13:10AM +0200, Bas van Dijk wrote:
Hello,
For my own exercise I'm writing a function 'weave' that "weaves" a list of lists together. For example:
weave [[1,1,1], [2,2,2], [3,3]] ==> [1,2,3,1,2,3,1,2] weave [[1,1,1], [2,2], [3,3,3]] ==> [1,2,3,1,2,3,1]
Note that 'weave' stops when a list is empty. Right now I have:
If it wasn't for that, you could use import Data.List(transpose) weave :: [[a]] -> [a] weave = concat . transpose e.g.
weave [[1,1,1], [2,2], [3,3,3]] ==> [1,2,3,1,2,3,1,3]
Brandon

Bas van Dijk:
For my own exercise I'm writing a function 'weave' that "weaves" a list of lists together. For example:
weave [[1,1,1], [2,2,2], [3,3]] ==> [1,2,3,1,2,3,1,2] weave [[1,1,1], [2,2], [3,3,3]] ==> [1,2,3,1,2,3,1]
Note that 'weave' stops when a list is empty.
This *almost* does what you want:
weave' = concat . transpose
Perhaps you could look at implementations of transpose for inspiration. The following two sources show implementations which behave differently when given ragged matrices. You seem to be looking for something between these two extremes. http://darcs.haskell.org/libraries/base/Data/List.hs http://www.soi.city.ac.uk/~ross/papers/Applicative.html Here's a modification of the latter to give the termination behaviour you show above:
weave = concat . foldr zipWeave [] where zipWeave (x:xs) (ys:yss) = (x:ys) : zipWeave xs yss zipWeave xs [] = map (:[]) xs zipWeave [] ys = []

Here's a very different approach. I make no claim to increased
elegance or efficiency, though I find it fairly readable and its made
of reusable parts. (Of course that's how you always finds your own
code!)
import Prelude hiding (head,tail)
-- Some would say this is how head and tail should have been defined.
head (a:_) = Just a
head _ = Nothing
tail (_:a) = Just a
tail _ = Nothing
-- A bit like map but stops when f returns Nothing.
mapWhile f (a:b) = case f a of
Just x -> x : mapWhile f b
Nothing -> []
mapWhile f [] = []
weave [] = []
weave a = mapWhile head a ++ weave (mapWhile tail a)
On 4/10/07, Bas van Dijk
Hello,
For my own exercise I'm writing a function 'weave' that "weaves" a list of lists together. For example:
weave [[1,1,1], [2,2,2], [3,3]] ==> [1,2,3,1,2,3,1,2] weave [[1,1,1], [2,2], [3,3,3]] ==> [1,2,3,1,2,3,1]
Note that 'weave' stops when a list is empty. Right now I have:
weave :: [[a]] -> [a] weave ll = work ll [] [] where work ll = foldr f (\rst acc -> work (reverse rst) [] acc) ll f [] g = \_ acc -> reverse acc f (x:xs) g = \rst acc -> g (xs:rst) (x:acc)
However I find this definition hard to read and I'm questioning its efficiency especially due to the 'reverse' parts (how do they impact performance and can they be removed?)
So I'm wondering if 'weave' can be defined more "elegantly" (better readable, shorter, more efficient, etc.)?
happy hacking,
Bas van Dijk _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

"Bas van Dijk"
Hello,
For my own exercise I'm writing a function 'weave' that "weaves" a list of lists together. For example:
weave [[1,1,1], [2,2,2], [3,3]] ==> [1,2,3,1,2,3,1,2] weave [[1,1,1], [2,2], [3,3,3]] ==> [1,2,3,1,2,3,1]
[...]
So I'm wondering if 'weave' can be defined more "elegantly" (better readable, shorter, more efficient, etc.)?
I don't know about your other criteria, but this is shorter: weave [] = [] weave ([]:_) = [] weave ((x:xs):others) = x : weave (others ++ [xs]) It's also lazy:
take 12 $ weave [[1..], [100..], [200..]] [1,100,200,2,101,201,3,102,202,4,103,203]

"Bas van Dijk"
weave [[1,1,1], [2,2,2], [3,3]] ==> [1,2,3,1,2,3,1,2] weave [[1,1,1], [2,2], [3,3,3]] ==> [1,2,3,1,2,3,1]
Note that 'weave' stops when a list is empty.
My naive implementation is, weave [] = [] weave ([]:_) = [] weave (x:xs) = head x : weave (xs ++ [tail x]) It's at least brief! -- Mark

Thanks for all the wonderful solutions. I put them into one module so other people can try it out: http://hpaste.org/1338 Thanks, Bas van Dijk

I have a simply recursive solution that operates efficiently... Bas van Dijk wrote:
Hello,
For my own exercise I'm writing a function 'weave' that "weaves" a list of lists together. For example:
weave [[1,1,1], [2,2,2], [3,3]] ==> [1,2,3,1,2,3,1,2] weave [[1,1,1], [2,2], [3,3,3]] ==> [1,2,3,1,2,3,1]
Note that 'weave' stops when a list is empty.
This version of weave works without Data.Sequence or using reverse, (++), or concat:
weave :: [[a]] -> [a] weave [] = [] weave xss = weave' id xss where weave' _rest ([]:_) = [] -- end when any list is empty weave' rest [] = weave (rest []) -- goto next, check for (weave []) weave' rest ((x:xs):xss) = x : weave' (rest . (xs:)) xss
The first parameter of weave' is the usual "difference list" trick to allow efficient append with simple lists. It works lazily and handles infinite lists. Though if you weave an infinite number of lists together you will get unbounded memory usage. Here it terminates when there is no element after the 15 in the second list: *Main> weave [[1..],[11..15],[300..]] [1,11,300,2,12,301,3,13,302,4,14,303,5,15,304,6] -- Chris

On Apr 11, 2007, at 6:00 AM, Chris Kuklewicz wrote:
I have a simply recursive solution that operates efficiently...
Bas van Dijk wrote:
Hello,
For my own exercise I'm writing a function 'weave' that "weaves" a list of lists together. For example:
weave [[1,1,1], [2,2,2], [3,3]] ==> [1,2,3,1,2,3,1,2] weave [[1,1,1], [2,2], [3,3,3]] ==> [1,2,3,1,2,3,1]
Note that 'weave' stops when a list is empty.
This version of weave works without Data.Sequence or using reverse, (++), or concat:
weave :: [[a]] -> [a] weave [] = [] weave xss = weave' id xss where weave' _rest ([]:_) = [] -- end when any list is empty weave' rest [] = weave (rest []) -- goto next, check for (weave []) weave' rest ((x:xs):xss) = x : weave' (rest . (xs:)) xss
The first parameter of weave' is the usual "difference list" trick to allow efficient append with simple lists.
Interestingly, in this particular case what we obtain is isomorphic to constructing and reversing a list. Let's represent the function rest by the following data type: data Rest a = Id | RestOfCons (Rest a) [a] apply :: Rest a -> [[a]] -> [[a]] apply Id = id apply (RestOfCons rest xs) = apply rest . (xs:) Let's add the missing argument to apply: apply :: Rest a -> [[a]] -> [[a]] apply Id xss = id xss apply (RestOfCons rest xs) xss = (apply rest . (xs:)) xss And simplify: apply :: Rest a -> [[a]] -> [[a]] apply Id xss = xss apply (RestOfCons rest xs) xss = apply rest (xs:xss) Compare this to the oh-so-useful reverseAppend function on lists (keeping variable names the same to make the connection obvious): reverseAppend :: [a] -> [a] -> [a] -- reverseAppend a b == reverse a ++ b reverseAppend [] xss = xss reverseAppend (xs:rest) xss = reverseAppend rest (xs:xss) So we've simply created the solution using "reverse" in new clothing. This shouldn't be surprising, actually. Both the "reverse" solution and the one using Data.Sequence are maintaining a queue of visited lists. In the case of the reverse solution, we represent the queue as a pair of lists: enqueue t (hs,ts) = (hs,t:ts) dequeue (h:hs,ts) = (h, (hs,ts)) dequeue ([],ts) = dequeue (reverse ts, []) The use of the function trick doesn't change this fact, it just hides it in the closures which are constructed. -Jan-Willem Maessen
-- Chris

You are correct, my weave did hide the list in the explicit composition of closure(s). I can be even more declarative and let the closure construction be implicit in weave' below... (and this message should be literate Haskell) weave' uses a fixed point and pairs to tie the knot declaratively:
import Data.List
weave' :: [[a]] -> [a] weave' [] = [] weave' xss = let (ans,rest) = helper rest xss in ans where helper :: [[a]] -> [[a]] -> ([a],[[a]]) helper _rest ([]:_xss) = ([],[]) helper rest [] = (weave' rest,[]) helper rest ((x:xs):xss) = let (ans,rest') = helper rest xss in (x:ans,xs:rest')
The next case might be an optimization, since we know that nothing after the [] will be used in the next pass:
-- helper rest ((x:[]):xss) = let (ans,_) = helper rest xss -- in (x:ans,[]:[])
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
One might imagine an 'optimized' case like in weave':
-- helper rest ((x:[]):xss) = let yss = rest ([]:[]) -- in x : helper (const yss) xss
Some simple tests such that check should be True
check = (ans == test 20 weave) && (ans == test 20 weave')
test n w = map (take n . w) $ [] : [[]] : [[],[]] : [[1..10]] : [[1,3..10],[2,4..10]] : [[1..],[11..15],[301..],[11..15]] : [[1..],[11..15],[301..]] : [[1..],[11..15],[301..],[]] : [[1..],[11..15],[],[301..]] : [[1..],[],[11..15],[],[301..]] : [[],[1..],[11..15],[],[301..]] : testInf : [] testInf = map enumFrom [1..] ans = [[],[],[],[1,2,3,4,5,6,7,8,9,10],[1,2,3,4,5,6,7,8,9,10] ,[1,11,301,11,2,12,302,12,3,13,303,13,4,14,304,14,5,15,305,15] ,[1,11,301,2,12,302,3,13,303,4,14,304,5,15,305,6] ,[1,11,301],[1,11],[1],[] ,[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20]]

Jan-Willem Maessen:
Interestingly, in this particular case what we obtain is isomorphic to constructing and reversing a list.
Jan-Willem's observation also hints at some interesting performance characteristics of difference lists. It's well known that difference lists give O(1) concatenation, but I haven't seen much discussion of the cost of conversion to ordinary lists. The conversion cost seems to be O(n), where n is the number of concatenations performed to build the difference list. Since the cost of building such a difference list is already O(n), the conversion cost only becomes significant if a difference list is converted more than once. Of course, the cost of consuming any one of those conversions is also likely to be at least O(n), so we see why this doesn't get much attention. Slightly more interesting is the observation that the grouping of difference list concatenations has a significant impact on the conversion cost, and in particular, on when the cost is incurred. When concatenations are grouped to the right, we get lazy conversion. Grouped to the left, we get strict(er) conversion. To see this, consider what happens if we take the heads of two difference lists, with concatenations grouped to the right and left respectively:
head_r n = head ((foldr1 (.) (map (:) [1..n])) []) head_l n = head ((foldl1 (.) (map (:) [1..n])) [])
We find that head_r is O(1), and head_l is O(n). Writing out the conversion for a left-grouped difference list, we also see Jan-Willem's reverse isomorphism quite clearly: head ((((1:).(2:)).(3:)) []) ==> head (((1:).(2:)) (3:[])) ==> head ((1:) (2:3:[])) ==> head (1:2:3:[]) ==> 1

Matthew Brecknell wrote:
Jan-Willem Maessen:
Interestingly, in this particular case what we obtain is isomorphic to constructing and reversing a list.
Jan-Willem's observation also hints at some interesting performance characteristics of difference lists. It's well known that difference lists give O(1) concatenation, but I haven't seen much discussion of the cost of conversion to ordinary lists.
The conversion cost seems to be O(n), where n is the number of concatenations performed to build the difference list.
The O(n) conversion cost is amortized over deconstructing the list thanks to laziness. So the head element is O(1). If head were O(n) then it would never be a win over using reverse.
[snip]
Slightly more interesting is the observation that the grouping of difference list concatenations has a significant impact on the conversion cost, and in particular, on when the cost is incurred. When concatenations are grouped to the right, we get lazy conversion. Grouped to the left, we get strict(er) conversion.
AFAIK, constructing a difference list using (.) is exactly like constructing a tree. The cost of converting to a normal list and getting the head element requires traversing the tree from the "root" to the first element. So if you construct it with just appends then the first element is the left node of the root, which is very fast. And if you construct it with prepends then the first element requires traversing the whole list. Since the list can only be deconstructed in order the sensible way to build a difference list is with appends. Note that pre-pending a huge list will blow the stack (for at least GHC). -- Chris

On Apr 12, 2007, at 9:39 PM, Matthew Brecknell wrote:
Jan-Willem Maessen:
Interestingly, in this particular case what we obtain is isomorphic to constructing and reversing a list.
Jan-Willem's observation also hints at some interesting performance characteristics of difference lists. It's well known that difference lists give O(1) concatenation, but I haven't seen much discussion of the cost of conversion to ordinary lists.
Nice analysis, thanks to both of you. I think a lot of this folklore isn't widely understood, particularly the fact that the closures constructed by difference lists are isomorphic to trees, with nodes corresponding to append/compose and leaves corresponding to empty/ singleton. So you pay the cost for append each time you flatten---the difference list trick is only a win if you flatten to an ordinary list once and/ or consume the entire list each time you flatten it. I'd had an intuitive notion of how this worked, but this spells it out nicely. Of course, once you represent things like so: data DiffList a = Segment [a] | DiffList a :++ DiffList a toList :: DiffList a -> [a] toList dl = toListApp dl [] toListApp :: DiffList a -> [a] -> [a] toListApp (Segment s) = (s++) toListApp (a:++b) = toListApp a . toListApp b You can start thinking about all sorts of other interesting questions, beyond just transforming to a list and eta-abstracting toListApp. The next thing you know, you're writing a better pretty printer or otherwise mucking about with the DiffList type itself to tailor it for your own nefarious purposes. -Jan

Jan-Willem Maessen wrote:
On Apr 12, 2007, at 9:39 PM, Matthew Brecknell wrote:
Jan-Willem Maessen:
Interestingly, in this particular case what we obtain is isomorphic to constructing and reversing a list.
Jan-Willem's observation also hints at some interesting performance characteristics of difference lists. It's well known that difference lists give O(1) concatenation, but I haven't seen much discussion of the cost of conversion to ordinary lists.
Nice analysis, thanks to both of you. I think a lot of this folklore isn't widely understood, particularly the fact that the closures constructed by difference lists are isomorphic to trees, with nodes corresponding to append/compose and leaves corresponding to empty/singleton. So you pay the cost for append each time you flatten---the difference list trick is only a win if you flatten to an ordinary list once and/or consume the entire list each time you flatten it. I'd had an intuitive notion of how this worked, but this spells it out nicely.
Of course, once you represent things like so:
data DiffList a = Segment [a] | DiffList a :++ DiffList a
toList :: DiffList a -> [a] toList dl = toListApp dl []
toListApp :: DiffList a -> [a] -> [a] toListApp (Segment s) = (s++) toListApp (a:++b) = toListApp a . toListApp b
You can start thinking about all sorts of other interesting questions, beyond just transforming to a list and eta-abstracting toListApp. The next thing you know, you're writing a better pretty printer or otherwise mucking about with the DiffList type itself to tailor it for your own nefarious purposes.
-Jan
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
And the relationship between them is de-/re-functionalization, "Defunctionalization at Work" (http://www.brics.dk/RS/01/23/) has some interesting applications of ideas along the line of Jan's.

On 4/11/07, Chris Kuklewicz
... 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
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:))
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 )
The funny thing is that this definition looks very similar to my first weave. However the reverse parts are now removed because of the difference list trick:
weave :: [[a]] -> [a] weave ll = work ll [] [] where work ll = foldr f (\rst acc -> work (reverse rst) [] acc) ll f [] g = \_ acc -> reverse acc f (x:xs) g = \rst acc -> g (xs:rst) (x:acc)
Thanks, Bas van Dijk

The fun never ends... Bas van Dijk wrote:
On 4/11/07, Chris Kuklewicz
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 )

Back to the original problem for a moment. \begin{code} import qualified Data.Sequence as Seq import Data.Sequence ((|>), ViewL((:<))) weave :: [[a]] -> [a] weave = weaveSeqL . Seq.viewl . Seq.fromList where weaveSeqL ((x:xs) :< s) = x : weaveSeqL (Seq.viewl $ s |> xs) weaveSeqL _ = [] \end{code} Yes, it also weaves infinite lists. Regards, Yitz
participants (10)
-
Bas van Dijk
-
Brandon Michael Moore
-
Chris Kuklewicz
-
Chris Mears
-
Dan Piponi
-
Derek Elkins
-
Jan-Willem Maessen
-
mark@ixod.org
-
Matthew Brecknell
-
Yitzchak Gale