[Haskell-cafe] Review request for my permutations implementation

Jochem Berndsen jochem at functor.nl
Thu Jan 7 04:46:40 EST 2010


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 | jochem at functor.nl | jochem@牛在田里.com


More information about the Haskell-Cafe mailing list