Re: Data.List permutations

2009-08-05 Thread Slavomir Kaslev
Thank you for the comprehensive reply Yitzchak.

On Wed, Aug 5, 2009 at 2:22 PM, Yitzchak Gale wrote:
> Hi Slavomir,
>
> Slavomir Kaslev wrote:
>>> inter x [] = [[x]]
>>> inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)
>>
>>> perm [] = [[]]
>>> perm (x:xs) = concatMap (inter x) (perm xs)
>>
>> I was surprised to find that not only my version is much simpler from the one
>> in Data.List but it also performs better.
>> I would like to suggest to change the current implementation in Data.List 
>> with
>> the simpler one.
>
> Thanks for looking into this.
>
> A lot of work went into the permutations function in Data.List,
> most of it by Twan van Laarhoven, including studying the order
> in which the permutations are returned, laziness, and extensive
> performance testing. The result was compared against Knuth's
> algorithmic work on this topic.
>
> Your algorithm is indeed similar to one that was considered
> during that development process.
>
> See the following thread for the details:
>
> http://www.haskell.org/pipermail/libraries/2007-December/008788.html
>
> and continued in:
>
> http://www.haskell.org/pipermail/libraries/2008-January/008859.html

Thanks for the links. I didn't realize how much effort and
considerations have gone in the development of permutations. I should
have guessed better. One can never determine the effort that certain
code needed to be developed from the code itself.

> Things do change with time, so it's always worthwhile to
> revisit these things and not take them for granted. If you
> can improve on this work, please let us know on the
> libraries mailing list.

I should have sent the message to the libraries mailing list in the
first place. But I was under the (outdated) impression that Data.List
is ghc specific library.

For a possible improvement, I guess I have to work harder to outdo the
work that went into permutations. While this is a noble goal, it
wasn't my initial intention. I was just helping a friend. Although, I
may get onto it when I have enough spare time (I am preparing for my
graduation exam in the moment).

>> Also, it would be nice to add variations and combinations in
>> the Data.List module.
>
> Personally, I disagree. I think those should go in a separate
> combinatorics library, not Data.List. As an example, take a
> look at the combinat package on Hackage:
>
> http://hackage.haskell.org/package/combinat

You are right. There's no reason to bloat Data.List with such
functions, when a different module will do. Thanks for the link.

Cheers.

-- 
Slavomir Kaslev
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Data.List permutations

2009-08-05 Thread Yitzchak Gale
Hi Slavomir,

Slavomir Kaslev wrote:
>> inter x [] = [[x]]
>> inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)
>
>> perm [] = [[]]
>> perm (x:xs) = concatMap (inter x) (perm xs)
>
> I was surprised to find that not only my version is much simpler from the one
> in Data.List but it also performs better.
> I would like to suggest to change the current implementation in Data.List with
> the simpler one.

Thanks for looking into this.

A lot of work went into the permutations function in Data.List,
most of it by Twan van Laarhoven, including studying the order
in which the permutations are returned, laziness, and extensive
performance testing. The result was compared against Knuth's
algorithmic work on this topic.

Your algorithm is indeed similar to one that was considered
during that development process.

See the following thread for the details:

http://www.haskell.org/pipermail/libraries/2007-December/008788.html

and continued in:

http://www.haskell.org/pipermail/libraries/2008-January/008859.html

Things do change with time, so it's always worthwhile to
revisit these things and not take them for granted. If you
can improve on this work, please let us know on the
libraries mailing list.

> Also, it would be nice to add variations and combinations in
> the Data.List module.

Personally, I disagree. I think those should go in a separate
combinatorics library, not Data.List. As an example, take a
look at the combinat package on Hackage:

http://hackage.haskell.org/package/combinat

But you don't have to agree with me. If you think that they
should go into Data.List, propose it using the following procedure:

http://www.haskell.org/haskellwiki/Library_submissions

Regards,
Yitz
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Data.List permutations

2009-08-04 Thread Malcolm Wallace

Your function is not equivalent:

perm _|_ = _|_

permutations _|_ = _|_ : _|_


I have a vague memory that the library version diagonalises properly,  
so that if you give it a lazy infinite input, it still generates  
sensible output lazily.  If so, this important property should be  
noted in the haddocks.


Regards,
Malcolm

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Data.List permutations

2009-08-04 Thread Daniel Fischer
Am Dienstag 04 August 2009 20:30:58 schrieb Slavomir Kaslev:
> On Tue, Aug 4, 2009 at 9:23 PM, Daniel Fischer 
> wrote:

>
> Which version of ghc are you testing on? I guess, it's more recent than
> mine.

6.10.3. But I think if you compiled it with 6.8.*, the library code would still 
be faster, 
perhaps by a smaller margin.

>
> > Apparently the library code is more amenable to the optimiser (note that
> > the actual library is faster still:
> >
> > Prelude Data.List> length $ permutations [1 .. 10]
> > 3628800
> > (0.49 secs, 551532812 bytes)
> > Prelude Data.List> length $ permutations [1 .. 11]
> > 39916800
> > (3.73 secs, 5953485816 bytes)
> >
> > I have no idea why).
>
> Probably because it's compiled (and not interpreted) in this case.

All my times were from compiled (with -O2) code. The question is, why does the 
same source 
code produce slower object code in module Perms than in Data.List?
I suppose it's because Data.List was compiled with different command line 
options, but 
I've no idea which.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Data.List permutations

2009-08-04 Thread Slavomir Kaslev
On Tue, Aug 4, 2009 at 9:23 PM, Daniel Fischer wrote:
> Am Dienstag 04 August 2009 19:48:25 schrieb Slavomir Kaslev:
>> A friend mine, new to functional programming, was entertaining himself by
>> writing different combinatorial algorithms in Haskell. He asked me for some
>> help so I sent him my quick and dirty solutions for generating variations
>> and
>>
>> permutations:
>> > inter x [] = [[x]]
>> > inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)
>> >
>> > perm [] = [[]]
>> > perm (x:xs) = concatMap (inter x) (perm xs)
>> >
>> > vari 0 _ = [[]]
>> > vari _ [] = []
>> > vari k (x:xs) = concatMap (inter x) (vari (k-1) xs) ++ vari k xs
>>
>> After that I found out that nowadays there is a permutation function in the
>>
>> Data.List module:
>> > permutations            :: [a] -> [[a]]
>> > permutations xs0        =  xs0 : perms xs0 []
>> >   where
>> >     perms []     _  = []
>> >     perms (t:ts) is = foldr interleave (perms ts (t:is)) (permutations
>> > is) where interleave    xs     r = let (_,zs) = interleave' id xs r in zs
>> > interleave' _ []     r = (ts, r)
>> >             interleave' f (y:ys) r = let (us,zs) = interleave' (f . (y:))
>> > ys r in  (y:us, f (t:y:us) : zs)
>>
>> I was surprised to find that not only my version is much simpler from the
>> one in Data.List but it also performs better. Here are some numbers from my
>> rather old ghc 6.8.1 running ubuntu on my box:
>>
>> *Main> length $ permutations [1..10]
>> 3628800
>> (10.80 secs, 2391647384 bytes)
>> *Main> length $ perm [1..10]
>> 3628800
>> (8.58 secs, 3156902672 bytes)
>
> But you compare *interpreted* code here, that's not what counts.
>
> Prelude Perms> length $ perm [1 .. 10]
> 3628800
> (1.20 secs, 1259105892 bytes)
> Prelude Perms> length $ permutations [1 .. 10]
> 3628800
> (0.56 secs, 551532668 bytes)
> Prelude Perms> length $ perm [1 .. 11]
> 39916800
> (13.18 secs, 14651808004 bytes)
> Prelude Perms> length $ permutations [1 .. 11]
> 39916800
> (4.30 secs, 5953485728 bytes)

Which version of ghc are you testing on? I guess, it's more recent than mine.

> Apparently the library code is more amenable to the optimiser (note that the 
> actual
> library is faster still:
>
> Prelude Data.List> length $ permutations [1 .. 10]
> 3628800
> (0.49 secs, 551532812 bytes)
> Prelude Data.List> length $ permutations [1 .. 11]
> 39916800
> (3.73 secs, 5953485816 bytes)
>
> I have no idea why).

Probably because it's compiled (and not interpreted) in this case.

-- 
Slavomir Kaslev
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Data.List permutations

2009-08-04 Thread Daniel Fischer
Am Dienstag 04 August 2009 19:48:25 schrieb Slavomir Kaslev:
> A friend mine, new to functional programming, was entertaining himself by
> writing different combinatorial algorithms in Haskell. He asked me for some
> help so I sent him my quick and dirty solutions for generating variations
> and
>
> permutations:
> > inter x [] = [[x]]
> > inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)
> >
> > perm [] = [[]]
> > perm (x:xs) = concatMap (inter x) (perm xs)
> >
> > vari 0 _ = [[]]
> > vari _ [] = []
> > vari k (x:xs) = concatMap (inter x) (vari (k-1) xs) ++ vari k xs
>
> After that I found out that nowadays there is a permutation function in the
>
> Data.List module:
> > permutations:: [a] -> [[a]]
> > permutations xs0=  xs0 : perms xs0 []
> >   where
> > perms [] _  = []
> > perms (t:ts) is = foldr interleave (perms ts (t:is)) (permutations
> > is) where interleavexs r = let (_,zs) = interleave' id xs r in zs
> > interleave' _ [] r = (ts, r)
> > interleave' f (y:ys) r = let (us,zs) = interleave' (f . (y:))
> > ys r in  (y:us, f (t:y:us) : zs)
>
> I was surprised to find that not only my version is much simpler from the
> one in Data.List but it also performs better. Here are some numbers from my
> rather old ghc 6.8.1 running ubuntu on my box:
>
> *Main> length $ permutations [1..10]
> 3628800
> (10.80 secs, 2391647384 bytes)
> *Main> length $ perm [1..10]
> 3628800
> (8.58 secs, 3156902672 bytes)

But you compare *interpreted* code here, that's not what counts.

Prelude Perms> length $ perm [1 .. 10]
3628800
(1.20 secs, 1259105892 bytes)
Prelude Perms> length $ permutations [1 .. 10]
3628800
(0.56 secs, 551532668 bytes)
Prelude Perms> length $ perm [1 .. 11]
39916800
(13.18 secs, 14651808004 bytes)
Prelude Perms> length $ permutations [1 .. 11]
39916800
(4.30 secs, 5953485728 bytes)

Apparently the library code is more amenable to the optimiser (note that the 
actual 
library is faster still:

Prelude Data.List> length $ permutations [1 .. 10]
3628800
(0.49 secs, 551532812 bytes)
Prelude Data.List> length $ permutations [1 .. 11]
39916800
(3.73 secs, 5953485816 bytes)

I have no idea why).

>
> I would like to suggest to change the current implementation in Data.List
> with the simpler one. Also, it would be nice to add variations and
> combinations in the Data.List module.
>
> Cheers.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Data.List permutations

2009-08-04 Thread Slavomir Kaslev
On Tue, Aug 4, 2009 at 8:53 PM, Krasimir Angelov wrote:
> Your function is not equivalent:
>
> perm _|_ = _|_
>
> permutations _|_ = _|_ : _|_

Nice catch. One can use the same trick as in permutations:

> perm2 [] = [[]]
> perm2 xxs@(x:xs) = xxs : tail (concatMap (inter x) (perm2 xs))

I've just noticed that permutations and perm enumerate the
permutations in different order.

> On 8/4/09, Slavomir Kaslev  wrote:
>> A friend mine, new to functional programming, was entertaining himself by
>> writing different combinatorial algorithms in Haskell. He asked me for some
>> help so I sent him my quick and dirty solutions for generating variations and
>> permutations:
>>
>> > inter x [] = [[x]]
>> > inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)
>>
>> > perm [] = [[]]
>> > perm (x:xs) = concatMap (inter x) (perm xs)
>>
>> > vari 0 _ = [[]]
>> > vari _ [] = []
>> > vari k (x:xs) = concatMap (inter x) (vari (k-1) xs) ++ vari k xs
>>
>> After that I found out that nowadays there is a permutation function in the
>> Data.List module:
>>
>> > permutations            :: [a] -> [[a]]
>> > permutations xs0        =  xs0 : perms xs0 []
>> >   where
>> >     perms []     _  = []
>> >     perms (t:ts) is = foldr interleave (perms ts (t:is)) (permutations is)
>> >       where interleave    xs     r = let (_,zs) = interleave' id xs r in zs
>> >             interleave' _ []     r = (ts, r)
>> >             interleave' f (y:ys) r = let (us,zs) = interleave' (f . (y:)) 
>> > ys r
>> >                                      in  (y:us, f (t:y:us) : zs)
>>
>> I was surprised to find that not only my version is much simpler from the one
>> in Data.List but it also performs better. Here are some numbers from my 
>> rather
>> old ghc 6.8.1 running ubuntu on my box:
>>
>> *Main> length $ permutations [1..10]
>> 3628800
>> (10.80 secs, 2391647384 bytes)
>> *Main> length $ perm [1..10]
>> 3628800
>> (8.58 secs, 3156902672 bytes)
>>
>> I would like to suggest to change the current implementation in Data.List 
>> with
>> the simpler one. Also, it would be nice to add variations and combinations in
>> the Data.List module.
>>
>> Cheers.
>>
>> --
>> Slavomir Kaslev
>> ___
>> Glasgow-haskell-users mailing list
>> Glasgow-haskell-users@haskell.org
>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>
>



-- 
Slavomir Kaslev
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Data.List permutations

2009-08-04 Thread Krasimir Angelov
Your function is not equivalent:

perm _|_ = _|_

permutations _|_ = _|_ : _|_


On 8/4/09, Slavomir Kaslev  wrote:
> A friend mine, new to functional programming, was entertaining himself by
> writing different combinatorial algorithms in Haskell. He asked me for some
> help so I sent him my quick and dirty solutions for generating variations and
> permutations:
>
> > inter x [] = [[x]]
> > inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)
>
> > perm [] = [[]]
> > perm (x:xs) = concatMap (inter x) (perm xs)
>
> > vari 0 _ = [[]]
> > vari _ [] = []
> > vari k (x:xs) = concatMap (inter x) (vari (k-1) xs) ++ vari k xs
>
> After that I found out that nowadays there is a permutation function in the
> Data.List module:
>
> > permutations:: [a] -> [[a]]
> > permutations xs0=  xs0 : perms xs0 []
> >   where
> > perms [] _  = []
> > perms (t:ts) is = foldr interleave (perms ts (t:is)) (permutations is)
> >   where interleavexs r = let (_,zs) = interleave' id xs r in zs
> > interleave' _ [] r = (ts, r)
> > interleave' f (y:ys) r = let (us,zs) = interleave' (f . (y:)) 
> > ys r
> >  in  (y:us, f (t:y:us) : zs)
>
> I was surprised to find that not only my version is much simpler from the one
> in Data.List but it also performs better. Here are some numbers from my rather
> old ghc 6.8.1 running ubuntu on my box:
>
> *Main> length $ permutations [1..10]
> 3628800
> (10.80 secs, 2391647384 bytes)
> *Main> length $ perm [1..10]
> 3628800
> (8.58 secs, 3156902672 bytes)
>
> I would like to suggest to change the current implementation in Data.List with
> the simpler one. Also, it would be nice to add variations and combinations in
> the Data.List module.
>
> Cheers.
>
> --
> Slavomir Kaslev
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Data.List permutations

2009-08-04 Thread Slavomir Kaslev
A friend mine, new to functional programming, was entertaining himself by
writing different combinatorial algorithms in Haskell. He asked me for some
help so I sent him my quick and dirty solutions for generating variations and
permutations:

> inter x [] = [[x]]
> inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)

> perm [] = [[]]
> perm (x:xs) = concatMap (inter x) (perm xs)

> vari 0 _ = [[]]
> vari _ [] = []
> vari k (x:xs) = concatMap (inter x) (vari (k-1) xs) ++ vari k xs

After that I found out that nowadays there is a permutation function in the
Data.List module:

> permutations:: [a] -> [[a]]
> permutations xs0=  xs0 : perms xs0 []
>   where
> perms [] _  = []
> perms (t:ts) is = foldr interleave (perms ts (t:is)) (permutations is)
>   where interleavexs r = let (_,zs) = interleave' id xs r in zs
> interleave' _ [] r = (ts, r)
> interleave' f (y:ys) r = let (us,zs) = interleave' (f . (y:)) ys r
>  in  (y:us, f (t:y:us) : zs)

I was surprised to find that not only my version is much simpler from the one
in Data.List but it also performs better. Here are some numbers from my rather
old ghc 6.8.1 running ubuntu on my box:

*Main> length $ permutations [1..10]
3628800
(10.80 secs, 2391647384 bytes)
*Main> length $ perm [1..10]
3628800
(8.58 secs, 3156902672 bytes)

I would like to suggest to change the current implementation in Data.List with
the simpler one. Also, it would be nice to add variations and combinations in
the Data.List module.

Cheers.

-- 
Slavomir Kaslev
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users