Mark P Jones <[EMAIL PROTECTED]> writes:
 > 
 > Here's my definition of an integer free diagonalization function.
 > [..] As written, I think
 > it is a nice example of programming with higher-order functions,
 > and, in particular, using function composition to construct a
 > pipelined program:
 > 
 > > diag :: [[a]] -> [a]
 > > diag  = concat . foldr skew [] . map (map (\x -> [x]))
 > >         where skew []     ys = ys
 > >               skew (x:xs) ys = x : comb (++) xs ys
 > 
 > This uses an auxiliary function comb, which is like zipWith
 > except that it doesn't throw away the tail of one list when it
 > reaches the end of the other:
 > 
 > > comb                :: (a -> a -> a) -> [a] -> [a] -> [a]
 > > comb f (x:xs) (y:ys) = f x y : comb f xs ys
 > > comb f []     ys     = ys
 > > comb f xs     []     = xs

This is in fact much nicer and much more intuitive than my version!

The only improvement that comes to my mind is to apply the equality

   ([x] ++) = (x :)

wherever possible:

> diag :: [[a]] -> [a]
> diag  = concat . foldr skew []
>         where skew []     ys = ys
>               skew (x:xs) ys = [x] : conscomb xs ys

> conscomb               :: [a] -> [[a]] -> [[a]]
> conscomb (x:xs) (y:ys) = (x : y) : conscomb xs ys
> conscomb []     ys     = ys
> conscomb xs     []     = map (:[]) xs

Perhaps this looks slightly less elegant, but it claws back quite
some efficiency: I compiled both versions (as DiagMPJ and DiagMPJ1)
and my original version (as DiagWK) with ghc-4.04 (perhaps a week old)
with ``-O'' and with the following test module
(substitute the respective definitions for ``@1''):

> module Main where

> import System

@1

> test = [[(x,y) | x <- [1..]] | y <- [1..]]
> main = do
>  (arg : _) <- System.getArgs
>  let n = (read arg :: Int)
>  print (length (show (take n (diag test))))

(I also tried Tom Pledgers second version, but it runs out of stack space...)

Best times out of five runs where:


Argument:  20000    200000  2000000

DiagMPJ   0:00.16  0:02.32  0:37.55
DiagMPJ1  0:00.12  0:01.50  0:23.83
DiagWK    0:00.11  0:01.33  0:19.10


This is not the first time that I get the impression that,
at least with current implementations,
functions are unbeatable when it comes to efficient data structures ---
perhaps this is why it is called functional programming ;-)


Cheers,

Wolfram



Reply via email to