[Haskell-cafe] Review request for my permutations implementation

2010-01-07 Thread CK Kashyap
Hi All,

I've written this piece of code to do permutations -

perms :: String - [String]
perms []= []
perms (x:[])= [[x]]
perms (x:xs)= concat (f [x] (perms xs))

spread :: String - String - [String] -- interpolate first string at various 
positions of second string
spread str1 str2 = _spread str1 str2 (length str2)
where
_spread str1 str2 0= [str1 ++ str2]
_spread str1 str2 n= [(take n str2) ++ str1 ++ (drop n str2)] ++ (_spread str1 
str2 (n-1))

f xs = map (spread xs)


The number of outcomes seem to indicate that correctness of the algo .. 
however, I'd be very obliged
if I could get some feedback on the Haskellness etc of this ... also any 
performance pointers ...


Regards,
Kashyap


  

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Review request for my permutations implementation

2010-01-07 Thread Jochem Berndsen
CK Kashyap wrote:
 I've written this piece of code to do permutations -

First off, this is a recurring topic. If you search the archives, you'll
find some more topics about it.

 perms :: String - [String]

Why this type? Since a String is just a list of Char, and you don't use
the fact that you're actually using a list of characters. It's better to
keep this function generic, and say

  perms :: [a] - [[a]]

 perms []= []

I don't think this is what you expect or want. I would consider a
permutation of X to be a bijection X - X. The number of bijections X -
X when X is empty, is in fact 1. So I think

  perms [] = [[]]

 perms (x:[])= [[x]]

I think you can drop this case if you do perms [] = [[]]. (Didn't prove
it, though.)

 perms (x:xs)= concat (f [x] (perms xs))

A small stylistic issue: Normally I'd write a space before the '='.

 spread :: String - String - [String] -- interpolate first string at various 
 positions of second string

This function becomes easier if you define it like

  spread :: a - [a] - [[a]]

since you only use it in that way.

 spread str1 str2 = _spread str1 str2 (length str2)
 where
 _spread str1 str2 0= [str1 ++ str2]
 _spread str1 str2 n= [(take n str2) ++ str1 ++ (drop n str2)] ++ (_spread 
 str1 str2 (n-1))
 
 f xs = map (spread xs)

There is a better way to write spread, something like

  spread str1 xs = zipWith (\x y - x ++ str1 ++ y)
   (inits xs)
   (tails xs)

with inits and tails from Data.List.


HTH, regards, Jochem
-- 
Jochem Berndsen | joc...@functor.nl | joc...@牛在田里.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Review request for my permutations implementation

2010-01-07 Thread Daniel Fischer
Am Donnerstag 07 Januar 2010 09:37:42 schrieb CK Kashyap:
 Hi All,

 I've written this piece of code to do permutations -

 perms :: String - [String]

Nothing in the algorithm needs the list elements to be Chars, there's no type 
class 
involved, so it should be

perms :: [a] - [[a]]

 perms []= []

This should actually be

perms [] = [[]]

 perms (x:[])= [[x]]

That is then superfluous.

 perms (x:xs)= concat (f [x] (perms xs))


'f' is a good name for a function parameter, not for a top level binding.
Why not

perms (x:xs) = concat (map (spread [x]) (perms xs))

whcih you can reformulate as

perms (x:xs) = concatMap (spread [x]) (perms xs)

or, if you like Monads, since concatMap is just the bind operator of the 
[]-monad,

perms (x:xs) = perms xs = spread [x]

Which can be written as a simple do-block:

perms (x:xs) = do
prm - perms xs
spread [x] prm

or a list-comprehension

perms (x:xs) = [permutation | tailPerm - perms xs, permutation - spread [x] 
tailPerm]

 spread :: String - String - [String] -- interpolate first string at
 various positions of second string spread str1 str2 = _spread str1 str2
 (length str2)
 where
 _spread str1 str2 0= [str1 ++ str2]
 _spread str1 str2 n= [(take n str2) ++ str1 ++ (drop n str2)] ++ (_spread
 str1 str2 (n-1))


import Data.List

spread short long = zipWith (\a b - a ++ short ++ b) (inits long) (tails long)

If you only use spread for perms, you never interpolate anything but single 
element lists, 
so you might consider

spread' :: a - [a] - [[a]]
spread' x xs = zipWith (\a b - a ++ x:b) (inits xs) (tails xs)

But if you import Data.List, you could also say

perms = permutations

and be done with it :) (except if you 1. need the permutations in a particular 
order, 
which is different from the one Data.List.permutations generates, or 2. you 
need it to be 
as fast as possible - Data.List.permutations was written to also cope with 
infinite lists, 
so a few things that could speed up generation of permutations for short lists 
couldn't be 
used).

 f xs = map (spread xs)


 The number of outcomes seem to indicate that correctness of the algo ..

Apart from the case of empty input, it is correct.

 however, I'd be very obliged if I could get some feedback on the
 Haskellness etc of this ... also any performance pointers ...

Re performance:
I think the repeated (take k) and (drop k) in your spread are likely to be 
slower than 
using inits and tails, but it would need measuring the performance to be sure.
I don't see anything that would automatically give bad performance.

But there's the question of repeated elements.

perms ab

spills out 3628800 permutations, but there are only 252 distinct permutations, 
each of 
them appearing 120^2 = 14400 times.

If your input may contain repeated elements and you're
1. only interested in the distinct permutations (and 2.) or
2. don't care about the order in which the permutations are generated,

distinctPerms :: Ord a = [a] - [[a]]
distinctPerms = foldr inserts [[]] . group . sort

inserts :: [a] - [[a]] - [[a]]
inserts xs yss = yss = (mingle xs)

mingle :: [a] - [a] - [[a]]
mingle xs [] = [xs]
mingle [] ys = [ys]
mingle xxs@(x:xs) yys@(y:ys) 
= [x:zs | zs - mingle xs yys] ++ [y:zs | zs - mingle xxs ys]

generates the distinct permutations much faster if there are many repeated 
elements;
if you want each distinct permutation repeated the appropriate number of times, 
the 
modification is easy.



 Regards,
 Kashyap


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Review request for my permutations implementation

2010-01-07 Thread Rafael Gustavo da Cunha Pereira Pinto
Hi,

Is there an entry in the haskell wiki for permutations? Since this is a
recurring topic, as primes, shouldn't we create a topic for that in the
wiki?

Regards,

Rafael


On Thu, Jan 7, 2010 at 08:46, Daniel Fischer daniel.is.fisc...@web.dewrote:

  Am Donnerstag 07 Januar 2010 09:37:42 schrieb CK Kashyap:

  Hi All,

 

  I've written this piece of code to do permutations -

 

  perms :: String - [String]

 Nothing in the algorithm needs the list elements to be Chars, there's no
 type class involved, so it should be

 perms :: [a] - [[a]]

  perms []= []

 This should actually be

 perms [] = [[]]

  perms (x:[])= [[x]]

 That is then superfluous.

  perms (x:xs)= concat (f [x] (perms xs))

 

 'f' is a good name for a function parameter, not for a top level binding.

 Why not

 perms (x:xs) = concat (map (spread [x]) (perms xs))

 whcih you can reformulate as

 perms (x:xs) = concatMap (spread [x]) (perms xs)

 or, if you like Monads, since concatMap is just the bind operator of the
 []-monad,

 perms (x:xs) = perms xs = spread [x]

 Which can be written as a simple do-block:

 perms (x:xs) = do

 prm - perms xs

 spread [x] prm

 or a list-comprehension

 perms (x:xs) = [permutation | tailPerm - perms xs, permutation - spread
 [x] tailPerm]

  spread :: String - String - [String] -- interpolate first string at

  various positions of second string spread str1 str2 = _spread str1 str2

  (length str2)

  where

  _spread str1 str2 0= [str1 ++ str2]

  _spread str1 str2 n= [(take n str2) ++ str1 ++ (drop n str2)] ++ (_spread

  str1 str2 (n-1))

 

 import Data.List

 spread short long = zipWith (\a b - a ++ short ++ b) (inits long) (tails
 long)

 If you only use spread for perms, you never interpolate anything but single
 element lists, so you might consider

 spread' :: a - [a] - [[a]]

 spread' x xs = zipWith (\a b - a ++ x:b) (inits xs) (tails xs)

 But if you import Data.List, you could also say

 perms = permutations

 and be done with it :) (except if you 1. need the permutations in a
 particular order, which is different from the one Data.List.permutations
 generates, or 2. you need it to be as fast as possible -
 Data.List.permutations was written to also cope with infinite lists, so a
 few things that could speed up generation of permutations for short lists
 couldn't be used).

  f xs = map (spread xs)

 

 

  The number of outcomes seem to indicate that correctness of the algo ..

 Apart from the case of empty input, it is correct.

  however, I'd be very obliged if I could get some feedback on the

  Haskellness etc of this ... also any performance pointers ...

 Re performance:

 I think the repeated (take k) and (drop k) in your spread are likely to be
 slower than using inits and tails, but it would need measuring the
 performance to be sure.

 I don't see anything that would automatically give bad performance.

 But there's the question of repeated elements.

 perms ab

 spills out 3628800 permutations, but there are only 252 distinct
 permutations, each of them appearing 120^2 = 14400 times.

 If your input may contain repeated elements and you're

 1. only interested in the distinct permutations (and 2.) or

 2. don't care about the order in which the permutations are generated,

 distinctPerms :: Ord a = [a] - [[a]]

 distinctPerms = foldr inserts [[]] . group . sort

 inserts :: [a] - [[a]] - [[a]]

 inserts xs yss = yss = (mingle xs)

 mingle :: [a] - [a] - [[a]]

 mingle xs [] = [xs]

 mingle [] ys = [ys]

 mingle xxs@(x:xs) yys@(y:ys)

 = [x:zs | zs - mingle xs yys] ++ [y:zs | zs - mingle xxs ys]

 generates the distinct permutations much faster if there are many repeated
 elements;

 if you want each distinct permutation repeated the appropriate number of
 times, the modification is easy.

 

 

  Regards,

  Kashyap


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Rafael Gustavo da Cunha Pereira Pinto
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Review request for my permutations implementation

2010-01-07 Thread CK Kashyap
Thanks everyone,
Thanks Daniel for this really detailed explanation - thank you very much.

Regards,
Kashyap


From: Daniel Fischer daniel.is.fisc...@web.de
To: haskell-cafe@haskell.org
Cc: CK Kashyap ck_kash...@yahoo.com
Sent: Thu, January 7, 2010 4:16:33 PM
Subject: Re: [Haskell-cafe] Review request for my permutations implementation

 
Am Donnerstag 07 Januar 2010 09:37:42 schrieb CK Kashyap:
 Hi All,

 I've written this piece of code to do permutations -

 perms :: String - [String]
Nothing in the algorithm needs the list elements to be Chars, there's no type 
class involved, so it should be
perms :: [a] - [[a]]
 perms []= []
This should actually be
perms [] = [[]]
 perms (x:[])= [[x]]
That is then superfluous.
 perms (x:xs)= concat (f [x] (perms xs))

'f' is a good name for a function parameter, not for a top level binding.
Why not
perms (x:xs) = concat (map (spread [x]) (perms xs))
whcih you can reformulate as
perms (x:xs) = concatMap (spread [x]) (perms xs)
or, if you like Monads, since concatMap is just the bind operator of the 
[]-monad,
perms (x:xs) = perms xs = spread [x]
Which can be written as a simple do-block:
perms (x:xs) = do
prm - perms xs
spread [x] prm
or a list-comprehension
perms (x:xs) = [permutation | tailPerm - perms xs, permutation - spread [x] 
tailPerm]
 spread :: String - String - [String] -- interpolate first string at
 various positions of second string spread str1 str2 = _spread str1 str2
 (length str2)
 where
 _spread str1 str2 0= [str1 ++ str2]
 _spread str1 str2 n= [(take n str2) ++ str1 ++ (drop n str2)] ++ (_spread
 str1 str2 (n-1))

import Data.List
spread short long = zipWith (\a b - a ++ short ++ b) (inits long) (tails long)
If you only use spread for perms, you never interpolate anything but single 
element lists, so you might consider
spread' :: a - [a] - [[a]]
spread' x xs = zipWith (\a b - a ++ x:b) (inits xs) (tails xs)
But if you import Data.List, you could also say
perms = permutations
and be done with it :) (except if you 1. need the permutations in a particular 
order, which is different from the one Data.List.permutations generates, or 2. 
you need it to be as fast as possible - Data.List.permutations was written to 
also cope with infinite lists, so a few things that could speed up generation 
of permutations for short lists couldn't be used).
 f xs = map (spread xs)


 The number of outcomes seem to indicate that correctness of the algo ..
Apart from the case of empty input, it is correct.
 however, I'd be very obliged if I could get some feedback on the
 Haskellness etc of this ... also any performance pointers ...
Re performance:
I think the repeated (take k) and (drop k) in your spread are likely to be 
slower than using inits and tails, but it would need measuring the performance 
to be sure.
I don't see anything that would automatically give bad performance.
But there's the question of repeated elements.
perms ab
spills out 3628800 permutations, but there are only 252 distinct permutations, 
each of them appearing 120^2 = 14400 times.
If your input may contain repeated elements and you're
1. only interested in the distinct permutations (and 2.) or
2. don't care about the order in which the permutations are generated,
distinctPerms :: Ord a = [a] - [[a]]
distinctPerms = foldr inserts [[]] . group . sort
inserts :: [a] - [[a]] - [[a]]
inserts xs yss = yss = (mingle xs)
mingle :: [a] - [a] - [[a]]
mingle xs [] = [xs]
mingle [] ys = [ys]
mingle xxs@(x:xs) yys@(y:ys) 
= [x:zs | zs - mingle xs yys] ++ [y:zs | zs - mingle xxs ys]
generates the distinct permutations much faster if there are many repeated 
elements;
if you want each distinct permutation repeated the appropriate number of 
times, the modification is easy.


 Regards,
 Kashyap


  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe