I liked Mark's version, but let me add a related challenge.
I defined a translation of //-list comprehensions
that is analogous to the foldr-translation of list comprehensions
(which optimises the map-concat approach) but works in the infinite case
as well.
This requires an operator foldrinf, of type:
foldrinf :: (a -> [b] -> [b]) -> [a] -> [b] -> [b]
The idea is that the [a] list is our input, and the
[b] list is an already-built result which we have to interleave
with putting further elements into this using the input list
and our operation (the first paramater).
A translation using this operator would be something like this:
start with
pairdiag = [(x,y) // x<-[1..], y<-[2..]]
and the translation gives
pairdiag = foldrinf newop1 [] [1..]
newop1 x y = foldrinf (newop2 x) y [2..]
newop2 x y z = (x,y) : z
And diag itself can be written as:
diag xs = [ x // y<-xs, x<-y ]
which translates into:
diag xs = foldrinf op [] xs
op x y = foldrinf (:) y x
The operator foldrinf can be defined as follows:
foldrinf op ys xs =
folly ys xs 0
where
folly ys (x:xs) n = op x (aux n ys)
where aux 0 bs = folly bs xs (n+1)
aux n (b:bs) = b : aux (n-1) bs
aux n [] = foldr op [] xs
folly ys [] n = ys
But, of course, this is ugly, with numbers and stuff...
So the challenge is to clean up this version so that it
looks just as nice as Mark's diag operator.
Stefan Kahrs