On 11 Jul, Wolfram Kahl wrote:
> Koen Claessen <[EMAIL PROTECTED]>
> proposes the following diagonalisation function:
> >
> > [ (a,b) | (a,b) <- [1..] // [1..] ]
> >
> > For a suitable definition of (//), for example:
> >
> > (//) :: [a] -> [b] -> [(a,b)]
> > xs // ys = diagonalize 1 [[(x,y) | x <- xs] | y <- ys]
> > where
> > diagonalize n xss =
> > xs ++ diagonalize (n+1) (xss1 ++ xss2)
> > where
> > (xs,xss1) = unzip [ (x,xs) | (x:xs) <- take n xss ]
> > xss2 = drop n xss
> >
> > And it works for any type.
>
> The core function here is
>
> > (diagonalize (1 :: Integer)) :: [[a]] -> [a]
>
> This function diagonalises finite or infinite lists
> with arbitrary finite or infinite element lists.
>
>
> To me, it seems unsatisfactory to have a solution to this pure list problem
> with auxiliary functions relying on integers.
I got rather lost in the ensuing discussion, so I've composed this
reply from back here. It seems to me that the core function is (//),
which can be written like this:
> module Diagonalise ((//)) where
> import List
A diagonalisation function that doesn't use numbers.
> (//):: [a] -> [b] -> [(a,b)]
> a // b = diag a b []
the third argument acc is an accumulator for the reversed initial
segment of a ie reverse acc ++ a == a0
> diag [] b [] = []
> diag [] [] acc = []
> diag [] (b: bs) acc = zip acc bs ++ diag [] bs acc
> diag (a: as) b acc = zip acc' b ++ diag as b acc'
> where acc' = a: acc
Or have I totally lost it?
--
Jón Fairbairn [EMAIL PROTECTED]
18 Kimberley Road [EMAIL PROTECTED]
Cambridge CB4 1HH +44 1223 570179 (pm only, please)