[Git][ghc/ghc][master] 2 commits: Add permutations for non-empty lists.

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Nov 17 01:54:05 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
9bc0dd1f by Ignat Insarov at 2023-11-16T20:53:34-05:00
Add permutations for non-empty lists.

Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837

- - - - -
5643ecf9 by Andrew Lelechenko at 2023-11-16T20:53:34-05:00
Update changelog and since annotations for Data.List.NonEmpty.permutations

Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837

- - - - -


6 changed files:

- libraries/base/changelog.md
- libraries/base/src/Data/List/NonEmpty.hs
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32


Changes:

=====================================
libraries/base/changelog.md
=====================================
@@ -2,6 +2,7 @@
 
 ## 4.20.0.0 *TBA*
   * Export `foldl'` from `Prelude` ([CLC proposal #167](https://github.com/haskell/core-libraries-committee/issues/167))
+  * Add `permutations` and `permutations1` to `Data.List.NonEmpty` ([CLC proposal #68](https://github.com/haskell/core-libraries-committee/issues/68))
   * Add a `RULE` to `Prelude.lookup`, allowing it to participate in list fusion ([CLC proposal #174](https://github.com/haskell/core-libraries-committee/issues/175))
   * The `Enum Int64` and `Enum Word64` instances now use native operations on 32-bit platforms, increasing performance by up to 1.5x on i386 and up to 5.6x with the JavaScript backend. ([CLC proposal #187](https://github.com/haskell/core-libraries-committee/issues/187))
   * Update to [Unicode 15.1.0](https://www.unicode.org/versions/Unicode15.1.0/).


=====================================
libraries/base/src/Data/List/NonEmpty.hs
=====================================
@@ -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,30 @@ 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.
+--
+-- @since 4.20.0.0
+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)
+-- The implementation of 'permutations' is adopted from 'Data.List.permutations',
+-- see there for discussion and explanations.
+
+-- | 'permutations1' operates like 'permutations', but uses the knowledge that its input is
+-- non-empty to produce output where every element is non-empty.
+--
+-- > permutations1 = fmap fromList . permutations . toList
+--
+-- @since 4.20.0.0
+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


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -1410,6 +1410,8 @@ module Data.List.NonEmpty where
   nub :: forall a. GHC.Classes.Eq a => NonEmpty a -> NonEmpty a
   nubBy :: forall a. (a -> a -> GHC.Types.Bool) -> NonEmpty a -> NonEmpty a
   partition :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a])
+  permutations :: forall a. [a] -> NonEmpty [a]
+  permutations1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
   prependList :: forall a. [a] -> NonEmpty a -> NonEmpty a
   repeat :: forall a. a -> NonEmpty a
   reverse :: forall a. NonEmpty a -> NonEmpty a


=====================================
testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
=====================================
@@ -1410,6 +1410,8 @@ module Data.List.NonEmpty where
   nub :: forall a. GHC.Classes.Eq a => NonEmpty a -> NonEmpty a
   nubBy :: forall a. (a -> a -> GHC.Types.Bool) -> NonEmpty a -> NonEmpty a
   partition :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a])
+  permutations :: forall a. [a] -> NonEmpty [a]
+  permutations1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
   prependList :: forall a. [a] -> NonEmpty a -> NonEmpty a
   repeat :: forall a. a -> NonEmpty a
   reverse :: forall a. NonEmpty a -> NonEmpty a


=====================================
testsuite/tests/interface-stability/base-exports.stdout-mingw32
=====================================
@@ -1410,6 +1410,8 @@ module Data.List.NonEmpty where
   nub :: forall a. GHC.Classes.Eq a => NonEmpty a -> NonEmpty a
   nubBy :: forall a. (a -> a -> GHC.Types.Bool) -> NonEmpty a -> NonEmpty a
   partition :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a])
+  permutations :: forall a. [a] -> NonEmpty [a]
+  permutations1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
   prependList :: forall a. [a] -> NonEmpty a -> NonEmpty a
   repeat :: forall a. a -> NonEmpty a
   reverse :: forall a. NonEmpty a -> NonEmpty a


=====================================
testsuite/tests/interface-stability/base-exports.stdout-ws-32
=====================================
@@ -1410,6 +1410,8 @@ module Data.List.NonEmpty where
   nub :: forall a. GHC.Classes.Eq a => NonEmpty a -> NonEmpty a
   nubBy :: forall a. (a -> a -> GHC.Types.Bool) -> NonEmpty a -> NonEmpty a
   partition :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a])
+  permutations :: forall a. [a] -> NonEmpty [a]
+  permutations1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
   prependList :: forall a. [a] -> NonEmpty a -> NonEmpty a
   repeat :: forall a. a -> NonEmpty a
   reverse :: forall a. NonEmpty a -> NonEmpty a



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b4f84e4bfac3648864d9482b7585a01d44b5eb58...5643ecf97150805032203bd9c8c92b5ded54d724

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b4f84e4bfac3648864d9482b7585a01d44b5eb58...5643ecf97150805032203bd9c8c92b5ded54d724
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20231116/b98c602d/attachment-0001.html>


More information about the ghc-commits mailing list