Generic permutations

How can I make a generic permutations function? -- boolean permutations bpms :: Int → [[Bool]] bpms 0 = [[]] bpms n = map (False:) bss ++ map (True:) bss where bss = bpms (n - 1) -- generic permutations pms a :: Int → [[a]] Best Regards, Cetin Sert

I have come up with this myself ^_^
mps :: [a] → [[a]] → [[a]]
mps [] _ = []
mps _ [] = []
mps (x:xs) yss = map (x:) yss ++ mps xs yss
pms :: [a] → Int → [[a]]
pms [] _ = [[]]
pms _ 0 = [[]]
pms xxs n = mps xxs (pms (xxs) (n - 1))
-- now bpms can pointlessly be redefined as
bpms = pms [False,True]
On 26/01/2008, Cetin Sert
How can I make a generic permutations function?
-- boolean permutations bpms :: Int → [[Bool]] bpms 0 = [[]] bpms n = map (False:) bss ++ map (True:) bss where bss = bpms (n - 1)
-- generic permutations pms a :: Int → [[a]]
Best Regards, Cetin Sert

When you say permuations, I think of reorderings of a list, for example: permutations [1,2,3] = [ [1,2,3], [1,3,2], [2,1,3], [2,3,1], [3,1,2], [3,2,1] ] Here's an implementation: -- split [1,2,3] => [ -- ( 1, [2,3] ), -- ( 2, [1,3] ), -- ( 3, [1,2] ) ] split :: [a] -> [(a, [a])] split [] = error "split: empty list" split [a] = [(a, [])] split (a:as) = (a, as) : map prefix (split as) where prefix (x, xs) = (x, a : xs) permutations :: [a] -> [[a]] permutations [] = return [] permutations xs = do (first, rest) <- split xs rest' <- permutations rest return (first : rest') The problem you solved can be solved much more elegantly: pms : [a] -> Int -> [[a]] pms xs n = foldM combine [] (replicate n xs) where combine rest as = liftM (:rest) as or, for the unreadable version: pms xs n = foldM (map . flip (:)) [] $ replicate n xs (note that, in the list monad, liftM = map). -- ryan

Thank you very much ^_^.
What would be a mathematically correct and understandable name for what we
call 'pms' here?
And in what module do foldM, combine, replicate, rest, liftM and so on
reside? How can I import them? o_O
-- Cetin Sert
On 26/01/2008, Ryan Ingram
When you say permuations, I think of reorderings of a list, for example:
permutations [1,2,3] = [ [1,2,3], [1,3,2], [2,1,3], [2,3,1], [3,1,2], [3,2,1] ]
Here's an implementation:
-- split [1,2,3] => [ -- ( 1, [2,3] ), -- ( 2, [1,3] ), -- ( 3, [1,2] ) ] split :: [a] -> [(a, [a])] split [] = error "split: empty list" split [a] = [(a, [])] split (a:as) = (a, as) : map prefix (split as) where prefix (x, xs) = (x, a : xs)
permutations :: [a] -> [[a]] permutations [] = return [] permutations xs = do (first, rest) <- split xs rest' <- permutations rest return (first : rest')
The problem you solved can be solved much more elegantly:
pms : [a] -> Int -> [[a]] pms xs n = foldM combine [] (replicate n xs) where combine rest as = liftM (:rest) as
or, for the unreadable version: pms xs n = foldM (map . flip (:)) [] $ replicate n xs
(note that, in the list monad, liftM = map).
-- ryan

Hello again Ryan,
I have found out where to import those stuff from and tested your more
elegant suggestion and my original performance.
-- print ((length ∘ pmsO [0,1]) 24) 9~ seconds
-- print ((length ∘ pmsE [0,1]) 24) 23~ seconds
-- print ((length ∘ pmsU [0,1]) 24) 23~ seconds
-- O: original, E: elegant, U: unreadable
I prefer performance over elegance (and for me using monads almost feels
like adding an unnecessary dependency to the definition of pms. Though I
know I may be dead wrong on that. I just don't quite understand monads yet.)
I would love to have you and/or others suggest more performant versions of
pms (and maybe also come up with a better name for it).
mnt :: [a] → [[a]] → [[a]]
mnt [] _ = []
mnt _ [] = []
mnt (x:xs) yss = map (x:) yss ++ mnt xs yss
pms :: [a] → Int → [[a]]
pms [] _ = [[]]
pms _ 0 = [[]]
pms xxs n = mnt xxs (pms xxs (n - 1))
I generalized 'pms' from the 'bools' function on page 108 of Programming in
Haskell (Hutton, 2007)
-- Cetin Sert
On 26/01/2008, Cetin Sert
Thank you very much ^_^.
What would be a mathematically correct and understandable name for what we call 'pms' here?
And in what module do foldM, combine, replicate, rest, liftM and so on reside? How can I import them? o_O
-- Cetin Sert
On 26/01/2008, Ryan Ingram
wrote: When you say permuations, I think of reorderings of a list, for example:
permutations [1,2,3] = [ [1,2,3], [1,3,2], [2,1,3], [2,3,1], [3,1,2], [3,2,1] ]
Here's an implementation:
-- split [1,2,3] => [ -- ( 1, [2,3] ), -- ( 2, [1,3] ), -- ( 3, [1,2] ) ] split :: [a] -> [(a, [a])] split [] = error "split: empty list" split [a] = [(a, [])] split (a:as) = (a, as) : map prefix (split as) where prefix (x, xs) = (x, a : xs)
permutations :: [a] -> [[a]] permutations [] = return [] permutations xs = do (first, rest) <- split xs rest' <- permutations rest return (first : rest')
The problem you solved can be solved much more elegantly:
pms : [a] -> Int -> [[a]] pms xs n = foldM combine [] (replicate n xs) where combine rest as = liftM (:rest) as
or, for the unreadable version: pms xs n = foldM (map . flip (:)) [] $ replicate n xs
(note that, in the list monad, liftM = map).
-- ryan

On 26 Jan 2008, ryani.spam@gmail.com wrote:
The problem you solved can be solved much more elegantly:
pms : [a] -> Int -> [[a]] pms xs n = foldM combine [] (replicate n xs) where combine rest as = liftM (:rest) as
or, for the unreadable version: pms xs n = foldM (map . flip (:)) [] $ replicate n xs
or, if you don't mind getting the elements in a different order: replicateM 3 [True,False] Jed

Thanks Jed,
replicateM is almost as performant as pms on my pc (+ 2~ seconds).
That's a killer suggestion... thank you very much ^_^
--Cetin Sert
On 27/01/2008, Jed Brown
The problem you solved can be solved much more elegantly:
pms : [a] -> Int -> [[a]] pms xs n = foldM combine [] (replicate n xs) where combine rest as = liftM (:rest) as
or, for the unreadable version: pms xs n = foldM (map . flip (:)) [] $ replicate n xs
or, if you don't mind getting the elements in a different order:
replicateM 3 [True,False]
Jed
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Cetin Sert
-
Jed Brown
-
Ryan Ingram