Hans Aberg:
: So now the problem is no longer how to properly create the infinite list,
: but how to properly print it out once it has been created. That consists of
: finding a suitable projection pi: N -> I subset S = N[w], and then print
: l_pi(i), i = 0,1,2, ...
I may have missed a few postings, but I haven't seen
anything doing the proper thing, yeat (I think):
I've come up with the following which works both for
finite and infinite lists:
> diag :: [a] -> [a] -> [(a,a)]
> diag as bs
> = diag' as bs [] []
> where diag' :: [a] -> [a] -> [a] -> [a] -> [(a,a)]
> diag' [] [] _ _ = []
> diag' [] bs _ cs
> = [(c,b) | c <- cs, b <- bs]
> diag' as [] rs _
> = [(a,r) | a <- as, r <- rs]
> diag' (a:as) (b:bs) rs cs
> = foldr (\c ls -> (a,c):ls)
> (foldr (\r ls -> (r,a):ls)
> ((a,b):diag' as bs (snoc a rs) (snoc b cs))
> rs) cs
> where snoc :: a -> [a] -> [a]
> snoc a as = foldr (:) [a] as
For [1..] [1..] it'll generate:
[(1,1),(2,1),(1,2),(2,2),(3,1),(3,2),(1,3),(2,3),(3,3),(4,1),(4,2),(4,3),(1,4),(2,4),(3,4)
,(4,4),(5,1),(5,2),(5,3),(5,4),(1,5),(2,5),(3,5),(4,5),(5,5),(6,1),(6,2),(6,3),(6,4),(6,5)
..
For [0..2] [0..4] it'll generate:
[(0,0),(1,0),(0,1),(1,1),(2,0),(2,1),(0,2),(1,2),(2,2),(0,3),(0,4),(1,3),(1,4),(2,3),(2,4)
]
For [0..4] [0..2] it'll generate:
[(0,0),(1,0),(0,1),(1,1),(2,0),(2,1),(0,2),(1,2),(2,2),(3,0),(3,1),(3,2),(4,0),(4,1),(4,2)
]
Regards,
Marc van Dongen
_______________________________________________________
Marc van Dongen, CS Dept | phone: +353 21 903578
University College Cork, NUIC | Fax: +353 21 903113
College Road, Cork, Ireland | Email: [EMAIL PROTECTED]