I believe this does what you want:
diagN :: [[a]] -> [[a]]
diagN = diagN' 0
diagN' :: Integer -> [[a]] -> [[a]]
diagN' i xss = case r of
[] -> []
_ -> r ++ diagN' (i + 1) xss
where r = diagN_i i xss
diagN_i :: Integer -> [[a]] -> [[a]]
diagN_i 0 [] = [[]]
diagN_i _ [] = []
diagN_i _ ([]:xss) = []
diagN_i 0 ((x:xs):xss) = [ x : r | r <- diagN_i 0 xss ]
diagN_i i ((x:xs):xss) = diagN_i (i - 1) (xs:xss) ++ [ x : r | r <-
diagN_i i xss ]
diagN_i produces all the diagonals where the sum of indices sum to i.
The order of the arguments to ++ in the last line determines the bias
to the earlier or later axes.
Where you say you want diagN (map (:[]) xs) == map (:[]) xs, I think
you mean diagN (map (:[]) xs) == [xs], which can never finish when xs
is infinite, because diagN has to check there isn't an empty list in
the list of lists it gets, in which case diagN must return [].
Sjoerd
On Nov 3, 2009, at 9:42 PM, Martijn van Steenbergen wrote:
Dear café,
I am looking for a function that does an N-dimensional diagonal
traversal. I want the traversal to be fair: the sum of the indices
of the produced combinations should be non-decreasing. Let me
illustrate with an example.
The type of a 2-dimensional traversal would look like this:
diag2 :: [a] -> [b] -> [(a, b)]
The first two arguments are the two half-axes of the grid and the
result is a fair diagonal traversal of all the points. For example:
diag2 [1,2,3] [4,5,6,7]
[(1,4),(2,4),(1,5),(3,4),(1,6),(2,5),(1,7),(3,5),(2,6),(2,7),(3,6),
(3,7)]
Of course the function should work on infinite lists:
diag2 [1..] [1..]
[(1,1),(2,1),(1,2),(3,1),...
Or a combination of finite and infinite lists:
diag2 [1,2] [1..]
[(1,1),(2,1),(1,2),(1,3),(2,2),(1,4),...
Notice that in each case the sum of the pairs (which can seen as
indices in these particular examples) are non-decreasing:
let sums = map (uncurry (+))
sums $ diag2 [1,2,3] [4,5,6,7]
[5,6,6,7,7,7,8,8,8,9,9,10]
sums $ diag2 [1..] [1..]
[2,3,3,4,4,4,5,5,5,5,6,...
sums $ diag2 [1,2] [1..]
[2,3,3,4,4,5,5,6,6,7,7,...
Similarly for 3 dimensions the type would be:
diag3 :: [a] -> [b] -> [c] -> [(a, b, c)]
For N dimensions we have to sacrifice some generality and ask all
axes to be of the same type and produce lists instead of tuples, but
I'm perfectly happy with that:
diagN :: [[a]] -> [[a]]
I have implemented diag2 and diag3 [1] but noticed that the function
bodies increase in size exponentially following Pascal's triangle
and have no clue how to generialize to N dimensions. Can you help me
write diagN?
Bonus points for the following:
* An infinite number of singleton axes produces [origin] (and
finishes computing), e.g. forall (infinite) xs. diagN (map (:[]) xs)
== map (:[]) xs
* For equal indices, the traversal biases to axes that are occur
early in the input (but I don't know how to formalize this).
* The implementation shows regularity and elegance.
Many thanks,
Martijn.
[1] http://hpaste.org/fastcgi/hpaste.fcgi/view?id=11515
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
--
Sjoerd Visscher
sjo...@w3future.com
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe