Skip to content
Snippets Groups Projects
Commit 9bc0dd1f authored by kindaro's avatar kindaro Committed by Marge Bot
Browse files

Add permutations for non-empty lists.

Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837
parent b4f84e4b
No related branches found
No related tags found
No related merge requests found
......@@ -78,6 +78,8 @@ module Data.List.NonEmpty (
, groupBy1 -- :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
, groupWith1 -- :: (Foldable f, Eq b) => (a -> b) -> f a -> NonEmpty (NonEmpty a)
, groupAllWith1 -- :: (Foldable f, Ord b) => (a -> b) -> f a -> NonEmpty (NonEmpty a)
, permutations
, permutations1
-- * Sublist predicates
, isPrefixOf -- :: Foldable f => f a -> NonEmpty a -> Bool
-- * \"Set\" operations
......@@ -441,6 +443,22 @@ groupWith1 f = groupBy1 ((==) `on` f)
groupAllWith1 :: (Ord b) => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupAllWith1 f = groupWith1 f . sortWith f
-- | The 'permutations' function returns the list of all permutations of the argument.
permutations :: [a] -> NonEmpty [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)
-- | 'permutations1' operates like 'permutations', but uses the knowledge that its input is
-- non-empty to produce output which every element is non-empty.
permutations1 :: NonEmpty a -> NonEmpty (NonEmpty a)
permutations1 xs = fromList <$> permutations (toList xs)
-- | The 'isPrefixOf' function returns 'True' if the first argument is
-- a prefix of the second.
isPrefixOf :: Eq a => [a] -> NonEmpty a -> Bool
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment