Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
b7b7c049
by Andrew Lelechenko at 2025-11-21T21:04:01+00:00
10 changed files:
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/Data/List.hs
- libraries/base/src/Data/List/NonEmpty.hs
- + libraries/base/src/Data/List/NubOrdSet.hs
- libraries/ghc-internal/src/GHC/Internal/Data/OldList.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:
| ... | ... | @@ -303,6 +303,7 @@ Library |
| 303 | 303 | , GHC.JS.Foreign.Callback
|
| 304 | 304 | |
| 305 | 305 | other-modules:
|
| 306 | + Data.List.NubOrdSet
|
|
| 306 | 307 | System.CPUTime.Unsupported
|
| 307 | 308 | System.CPUTime.Utils
|
| 308 | 309 | if os(windows)
|
| ... | ... | @@ -10,6 +10,7 @@ |
| 10 | 10 | * Fix bug where `naturalAndNot` was incorrectly truncating results ([CLC proposal #350](github.com/haskell/core-libraries-committee/issues/350))
|
| 11 | 11 | * Remove extra laziness from `Data.Bifunctor.Bifunctor` instances for all tuples to have the same laziness as their `Data.Functor.Functor` counterparts (i.e. they became more strict than before) ([CLC proposal #339](https://github.com/haskell/core-libraries-committee/issues/339))
|
| 12 | 12 | * Adjust the strictness of `Data.List.iterate'` to be more reasonable: every element of the output list is forced to WHNF when the `(:)` containing it is forced. ([CLC proposal #335)](https://github.com/haskell/core-libraries-committee/issues/335)
|
| 13 | + * Add `nubOrd` / `nubOrdBy` to `Data.List` and `Data.List.NonEmpty`. ([CLC proposal #336](https://github.com/haskell/core-libraries-committee/issues/336))
|
|
| 13 | 14 | |
| 14 | 15 | ## 4.22.0.0 *TBA*
|
| 15 | 16 | * Shipped with GHC 9.14.1
|
| ... | ... | @@ -136,7 +136,11 @@ module Data.List |
| 136 | 136 | unlines,
|
| 137 | 137 | unwords,
|
| 138 | 138 | -- ** \"Set\" operations
|
| 139 | + -- | Consider using @Data.Set@ from @containers@ package,
|
|
| 140 | + -- which offers a much wider and often more efficient range
|
|
| 141 | + -- of operations on sets.
|
|
| 139 | 142 | nub,
|
| 143 | + nubOrd,
|
|
| 140 | 144 | delete,
|
| 141 | 145 | (\\),
|
| 142 | 146 | union,
|
| ... | ... | @@ -157,6 +161,7 @@ module Data.List |
| 157 | 161 | -- *** User-supplied equality (replacing an @Eq@ context)
|
| 158 | 162 | -- | The predicate is assumed to define an equivalence.
|
| 159 | 163 | nubBy,
|
| 164 | + nubOrdBy,
|
|
| 160 | 165 | deleteBy,
|
| 161 | 166 | deleteFirstsBy,
|
| 162 | 167 | unionBy,
|
| ... | ... | @@ -180,12 +185,14 @@ module Data.List |
| 180 | 185 | ) where
|
| 181 | 186 | |
| 182 | 187 | import GHC.Internal.Data.Bool (otherwise)
|
| 188 | +import GHC.Internal.Data.Function (const)
|
|
| 183 | 189 | import GHC.Internal.Data.List
|
| 184 | 190 | import GHC.Internal.Data.List.NonEmpty (NonEmpty(..))
|
| 185 | -import GHC.Internal.Data.Ord (Ordering(..), (<), (>))
|
|
| 191 | +import GHC.Internal.Data.Ord (Ord, compare, Ordering(..), (<), (>))
|
|
| 186 | 192 | import GHC.Internal.Int (Int)
|
| 187 | 193 | import GHC.Internal.Num ((-))
|
| 188 | 194 | import GHC.List (build)
|
| 195 | +import qualified Data.List.NubOrdSet as NubOrdSet
|
|
| 189 | 196 | |
| 190 | 197 | inits1, tails1 :: [a] -> [NonEmpty a]
|
| 191 | 198 | |
| ... | ... | @@ -282,3 +289,25 @@ compareLength xs n |
| 282 | 289 | (\m -> if m > 0 then LT else EQ)
|
| 283 | 290 | xs
|
| 284 | 291 | n
|
| 292 | + |
|
| 293 | +-- | Same as 'nub', but asymptotically faster, taking only /O/(/n/ log /d/) time,
|
|
| 294 | +-- where /d/ is the number of distinct elements in the list.
|
|
| 295 | +--
|
|
| 296 | +-- @since 4.23.0.0
|
|
| 297 | +nubOrd :: Ord a => [a] -> [a]
|
|
| 298 | +nubOrd = nubOrdBy compare
|
|
| 299 | +{-# INLINE nubOrd #-}
|
|
| 300 | + |
|
| 301 | +-- | Overloaded version of 'Data.List.nubOrd'.
|
|
| 302 | +--
|
|
| 303 | +-- The supplied comparison relation is supposed to be reflexive, transitive
|
|
| 304 | +-- and antisymmetric, same as for 'sortBy'.
|
|
| 305 | +--
|
|
| 306 | +-- @since 4.23.0.0
|
|
| 307 | +nubOrdBy :: (a -> a -> Ordering) -> [a] -> [a]
|
|
| 308 | +nubOrdBy cmp xs = foldr
|
|
| 309 | + (\x cont seen -> if NubOrdSet.member cmp x seen then cont seen else x : cont (NubOrdSet.insert cmp x seen))
|
|
| 310 | + (const [])
|
|
| 311 | + xs
|
|
| 312 | + NubOrdSet.empty
|
|
| 313 | +{-# INLINE nubOrdBy #-} |
| ... | ... | @@ -94,7 +94,9 @@ module Data.List.NonEmpty ( |
| 94 | 94 | , isPrefixOf -- :: Eq a => [a] -> NonEmpty a -> Bool
|
| 95 | 95 | -- * \"Set\" operations
|
| 96 | 96 | , nub -- :: Eq a => NonEmpty a -> NonEmpty a
|
| 97 | + , nubOrd -- :: Ord a => NonEmpty a -> NonEmpty a
|
|
| 97 | 98 | , nubBy -- :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
|
| 99 | + , nubOrdBy -- :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
|
|
| 98 | 100 | -- * Indexing streams
|
| 99 | 101 | , (!!) -- :: NonEmpty a -> Int -> a
|
| 100 | 102 | -- * Zipping and unzipping streams
|
| ... | ... | @@ -119,6 +121,7 @@ import qualified Prelude |
| 119 | 121 | |
| 120 | 122 | import Control.Applicative (Applicative (..), Alternative (many))
|
| 121 | 123 | import qualified Data.List as List
|
| 124 | +import qualified Data.List.NubOrdSet as NubOrdSet
|
|
| 122 | 125 | import qualified Data.Maybe as List (mapMaybe)
|
| 123 | 126 | import GHC.Internal.Data.Foldable hiding (length, toList)
|
| 124 | 127 | import qualified GHC.Internal.Data.Foldable as Foldable
|
| ... | ... | @@ -568,6 +571,13 @@ unzip ((a, b) :| asbs) = (a :| as, b :| bs) |
| 568 | 571 | -- (The name 'nub' means \'essence\'.)
|
| 569 | 572 | -- It is a special case of 'nubBy', which allows the programmer to
|
| 570 | 573 | -- supply their own inequality test.
|
| 574 | +--
|
|
| 575 | +-- This function knows too little about the elements to be efficient.
|
|
| 576 | +-- Its asymptotic complexity is
|
|
| 577 | +-- /O/(/n/ ⋅ /d/), where /d/ is the number of distinct elements in the list.
|
|
| 578 | +--
|
|
| 579 | +-- If there exists @instance Ord a@, it's faster to use 'Data.List.NonEmpty.nubOrd'.
|
|
| 580 | +--
|
|
| 571 | 581 | nub :: Eq a => NonEmpty a -> NonEmpty a
|
| 572 | 582 | nub = nubBy (==)
|
| 573 | 583 | |
| ... | ... | @@ -577,6 +587,25 @@ nub = nubBy (==) |
| 577 | 587 | nubBy :: (a -> a -> Bool) -> NonEmpty a -> NonEmpty a
|
| 578 | 588 | nubBy eq (a :| as) = a :| List.nubBy eq (List.filter (\b -> not (eq a b)) as)
|
| 579 | 589 | |
| 590 | +-- | Same as 'nub', but asymptotically faster, taking only /O/(/n/ log /d/) time.
|
|
| 591 | +-- where /d/ is the number of distinct elements in the list.
|
|
| 592 | +--
|
|
| 593 | +-- @since 4.23.0.0
|
|
| 594 | +nubOrd :: Ord a => NonEmpty a -> NonEmpty a
|
|
| 595 | +nubOrd = nubOrdBy compare
|
|
| 596 | +{-# INLINE nubOrd #-}
|
|
| 597 | + |
|
| 598 | +-- | Overloaded version of 'Data.List.NonEmpty.nubOrd'.
|
|
| 599 | +--
|
|
| 600 | +-- @since 4.23.0.0
|
|
| 601 | +nubOrdBy :: (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
|
|
| 602 | +nubOrdBy cmp (y :| ys) = y :| foldr
|
|
| 603 | + (\x cont seen -> if NubOrdSet.member cmp x seen then cont seen else x : cont (NubOrdSet.insert cmp x seen))
|
|
| 604 | + (const [])
|
|
| 605 | + ys
|
|
| 606 | + (NubOrdSet.insert cmp y NubOrdSet.empty)
|
|
| 607 | +{-# INLINE nubOrdBy #-}
|
|
| 608 | + |
|
| 580 | 609 | -- | 'transpose' for 'NonEmpty', behaves the same as 'GHC.Internal.Data.List.transpose'
|
| 581 | 610 | -- The rows/columns need not be the same length, in which case
|
| 582 | 611 | -- > transpose . transpose /= id
|
| 1 | +-- This is an internal module with a naive set implementation,
|
|
| 2 | +-- solely for the purposes of `Data.List.{,NonEmpty.}nubOrd{,By}`.
|
|
| 3 | + |
|
| 4 | +{-# LANGUAGE BangPatterns #-}
|
|
| 5 | +{-# LANGUAGE LambdaCase #-}
|
|
| 6 | + |
|
| 7 | +module Data.List.NubOrdSet (
|
|
| 8 | + NubOrdSet,
|
|
| 9 | + empty,
|
|
| 10 | + member,
|
|
| 11 | + insert,
|
|
| 12 | +) where
|
|
| 13 | + |
|
| 14 | +import GHC.Internal.Data.Bool (Bool(..))
|
|
| 15 | +import GHC.Internal.Data.Function ((.))
|
|
| 16 | +import GHC.Internal.Data.Ord (Ordering(..))
|
|
| 17 | + |
|
| 18 | +-- | Implemented as a red-black tree, a la Okasaki.
|
|
| 19 | +data NubOrdSet a
|
|
| 20 | + = Empty
|
|
| 21 | + | NodeRed !(NubOrdSet a) !a !(NubOrdSet a)
|
|
| 22 | + | NodeBlack !(NubOrdSet a) !a !(NubOrdSet a)
|
|
| 23 | + |
|
| 24 | +empty :: NubOrdSet a
|
|
| 25 | +empty = Empty
|
|
| 26 | + |
|
| 27 | +member :: (a -> a -> Ordering) -> a -> NubOrdSet a -> Bool
|
|
| 28 | +member cmp = member'
|
|
| 29 | + where
|
|
| 30 | + member' !x = go
|
|
| 31 | + where
|
|
| 32 | + go = \case
|
|
| 33 | + Empty -> False
|
|
| 34 | + NodeRed left center right -> chooseWay left center right
|
|
| 35 | + NodeBlack left center right -> chooseWay left center right
|
|
| 36 | + |
|
| 37 | + chooseWay left center right = case cmp x center of
|
|
| 38 | + LT -> go left
|
|
| 39 | + EQ -> True
|
|
| 40 | + GT -> go right
|
|
| 41 | +{-# INLINE member #-}
|
|
| 42 | + |
|
| 43 | +insert :: (a -> a -> Ordering) -> a -> NubOrdSet a -> NubOrdSet a
|
|
| 44 | +insert cmp = insert'
|
|
| 45 | + where
|
|
| 46 | + insert' !x = blacken . go
|
|
| 47 | + where
|
|
| 48 | + go node = case node of
|
|
| 49 | + Empty -> NodeRed Empty x Empty
|
|
| 50 | + NodeRed left center right -> case cmp x center of
|
|
| 51 | + LT -> NodeRed (go left) center right
|
|
| 52 | + EQ -> node
|
|
| 53 | + GT -> NodeRed left center (go right)
|
|
| 54 | + NodeBlack left center right -> case cmp x center of
|
|
| 55 | + LT -> balanceBlackLeft (go left) center right
|
|
| 56 | + EQ -> node
|
|
| 57 | + GT -> balanceBlackRight left center (go right)
|
|
| 58 | + |
|
| 59 | + blacken node = case node of
|
|
| 60 | + Empty -> Empty
|
|
| 61 | + NodeRed left center right -> NodeBlack left center right
|
|
| 62 | + NodeBlack{} -> node
|
|
| 63 | +{-# INLINE insert #-}
|
|
| 64 | + |
|
| 65 | +balanceBlackLeft :: NubOrdSet a -> a -> NubOrdSet a -> NubOrdSet a
|
|
| 66 | +balanceBlackLeft (NodeRed (NodeRed a b c) d e) f g =
|
|
| 67 | + NodeRed (NodeBlack a b c) d (NodeBlack e f g)
|
|
| 68 | +balanceBlackLeft (NodeRed a b (NodeRed c d e)) f g =
|
|
| 69 | + NodeRed (NodeBlack a b c) d (NodeBlack e f g)
|
|
| 70 | +balanceBlackLeft left center right =
|
|
| 71 | + NodeBlack left center right
|
|
| 72 | +{-# INLINE balanceBlackLeft #-}
|
|
| 73 | + |
|
| 74 | +balanceBlackRight :: NubOrdSet a -> a -> NubOrdSet a -> NubOrdSet a
|
|
| 75 | +balanceBlackRight a b (NodeRed (NodeRed c d e) f g) =
|
|
| 76 | + NodeRed (NodeBlack a b c) d (NodeBlack e f g)
|
|
| 77 | +balanceBlackRight a b (NodeRed c d (NodeRed e f g)) =
|
|
| 78 | + NodeRed (NodeBlack a b c) d (NodeBlack e f g)
|
|
| 79 | +balanceBlackRight left center right =
|
|
| 80 | + NodeBlack left center right
|
|
| 81 | +{-# INLINE balanceBlackRight #-} |
| ... | ... | @@ -494,21 +494,16 @@ dropLengthMaybe (_:x') (_:y') = dropLengthMaybe x' y' |
| 494 | 494 | isInfixOf :: (Eq a) => [a] -> [a] -> Bool
|
| 495 | 495 | isInfixOf needle haystack = any (isPrefixOf needle) (tails haystack)
|
| 496 | 496 | |
| 497 | --- | \(\mathcal{O}(n^2)\). The 'nub' function removes duplicate elements from a
|
|
| 497 | +-- | The 'nub' function removes duplicate elements from a
|
|
| 498 | 498 | -- list. In particular, it keeps only the first occurrence of each element. (The
|
| 499 | 499 | -- name 'nub' means \`essence\'.) It is a special case of 'nubBy', which allows
|
| 500 | 500 | -- the programmer to supply their own equality test.
|
| 501 | 501 | --
|
| 502 | +-- This function knows too little about the elements to be efficient.
|
|
| 503 | +-- Its asymptotic complexity is
|
|
| 504 | +-- /O/(/n/ ⋅ /d/), where /d/ is the number of distinct elements in the list.
|
|
| 502 | 505 | --
|
| 503 | --- If there exists @instance Ord a@, it's faster to use `nubOrd` from the `containers` package
|
|
| 504 | --- ([link to the latest online documentation](https://hackage.haskell.org/package/containers/docs/Data-Containers-ListUtils.html#v:nubOrd)),
|
|
| 505 | --- which takes only \(\mathcal{O}(n \log d)\) time where `d` is the number of
|
|
| 506 | --- distinct elements in the list.
|
|
| 507 | ---
|
|
| 508 | --- Another approach to speed up 'nub' is to use
|
|
| 509 | --- 'map' @Data.List.NonEmpty.@'Data.List.NonEmpty.head' . @Data.List.NonEmpty.@'Data.List.NonEmpty.group' . 'sort',
|
|
| 510 | --- which takes \(\mathcal{O}(n \log n)\) time, requires @instance Ord a@ and doesn't
|
|
| 511 | --- preserve the order.
|
|
| 506 | +-- If there exists @instance Ord a@, it's faster to use 'Data.List.nubOrd'.
|
|
| 512 | 507 | --
|
| 513 | 508 | -- ==== __Examples__
|
| 514 | 509 | --
|
| ... | ... | @@ -1379,6 +1379,8 @@ module Data.List where |
| 1379 | 1379 | notElem :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Internal.Classes.Eq a) => a -> t a -> GHC.Internal.Types.Bool
|
| 1380 | 1380 | nub :: forall a. GHC.Internal.Classes.Eq a => [a] -> [a]
|
| 1381 | 1381 | nubBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a]
|
| 1382 | + nubOrd :: forall a. GHC.Internal.Classes.Ord a => [a] -> [a]
|
|
| 1383 | + nubOrdBy :: forall a. (a -> a -> GHC.Internal.Types.Ordering) -> [a] -> [a]
|
|
| 1382 | 1384 | null :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t a -> GHC.Internal.Types.Bool
|
| 1383 | 1385 | or :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Internal.Types.Bool -> GHC.Internal.Types.Bool
|
| 1384 | 1386 | partition :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> ([a], [a])
|
| ... | ... | @@ -1473,6 +1475,8 @@ module Data.List.NonEmpty where |
| 1473 | 1475 | nonEmpty :: forall a. [a] -> GHC.Internal.Maybe.Maybe (NonEmpty a)
|
| 1474 | 1476 | nub :: forall a. GHC.Internal.Classes.Eq a => NonEmpty a -> NonEmpty a
|
| 1475 | 1477 | nubBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> NonEmpty a -> NonEmpty a
|
| 1478 | + nubOrd :: forall a. GHC.Internal.Classes.Ord a => NonEmpty a -> NonEmpty a
|
|
| 1479 | + nubOrdBy :: forall a. (a -> a -> GHC.Internal.Types.Ordering) -> NonEmpty a -> NonEmpty a
|
|
| 1476 | 1480 | partition :: forall a. (a -> GHC.Internal.Types.Bool) -> NonEmpty a -> ([a], [a])
|
| 1477 | 1481 | permutations :: forall a. [a] -> NonEmpty [a]
|
| 1478 | 1482 | permutations1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
|
| ... | ... | @@ -1379,6 +1379,8 @@ module Data.List where |
| 1379 | 1379 | notElem :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Internal.Classes.Eq a) => a -> t a -> GHC.Internal.Types.Bool
|
| 1380 | 1380 | nub :: forall a. GHC.Internal.Classes.Eq a => [a] -> [a]
|
| 1381 | 1381 | nubBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a]
|
| 1382 | + nubOrd :: forall a. GHC.Internal.Classes.Ord a => [a] -> [a]
|
|
| 1383 | + nubOrdBy :: forall a. (a -> a -> GHC.Internal.Types.Ordering) -> [a] -> [a]
|
|
| 1382 | 1384 | null :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t a -> GHC.Internal.Types.Bool
|
| 1383 | 1385 | or :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Internal.Types.Bool -> GHC.Internal.Types.Bool
|
| 1384 | 1386 | partition :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> ([a], [a])
|
| ... | ... | @@ -1473,6 +1475,8 @@ module Data.List.NonEmpty where |
| 1473 | 1475 | nonEmpty :: forall a. [a] -> GHC.Internal.Maybe.Maybe (NonEmpty a)
|
| 1474 | 1476 | nub :: forall a. GHC.Internal.Classes.Eq a => NonEmpty a -> NonEmpty a
|
| 1475 | 1477 | nubBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> NonEmpty a -> NonEmpty a
|
| 1478 | + nubOrd :: forall a. GHC.Internal.Classes.Ord a => NonEmpty a -> NonEmpty a
|
|
| 1479 | + nubOrdBy :: forall a. (a -> a -> GHC.Internal.Types.Ordering) -> NonEmpty a -> NonEmpty a
|
|
| 1476 | 1480 | partition :: forall a. (a -> GHC.Internal.Types.Bool) -> NonEmpty a -> ([a], [a])
|
| 1477 | 1481 | permutations :: forall a. [a] -> NonEmpty [a]
|
| 1478 | 1482 | permutations1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
|
| ... | ... | @@ -1379,6 +1379,8 @@ module Data.List where |
| 1379 | 1379 | notElem :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Internal.Classes.Eq a) => a -> t a -> GHC.Internal.Types.Bool
|
| 1380 | 1380 | nub :: forall a. GHC.Internal.Classes.Eq a => [a] -> [a]
|
| 1381 | 1381 | nubBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a]
|
| 1382 | + nubOrd :: forall a. GHC.Internal.Classes.Ord a => [a] -> [a]
|
|
| 1383 | + nubOrdBy :: forall a. (a -> a -> GHC.Internal.Types.Ordering) -> [a] -> [a]
|
|
| 1382 | 1384 | null :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t a -> GHC.Internal.Types.Bool
|
| 1383 | 1385 | or :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Internal.Types.Bool -> GHC.Internal.Types.Bool
|
| 1384 | 1386 | partition :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> ([a], [a])
|
| ... | ... | @@ -1473,6 +1475,8 @@ module Data.List.NonEmpty where |
| 1473 | 1475 | nonEmpty :: forall a. [a] -> GHC.Internal.Maybe.Maybe (NonEmpty a)
|
| 1474 | 1476 | nub :: forall a. GHC.Internal.Classes.Eq a => NonEmpty a -> NonEmpty a
|
| 1475 | 1477 | nubBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> NonEmpty a -> NonEmpty a
|
| 1478 | + nubOrd :: forall a. GHC.Internal.Classes.Ord a => NonEmpty a -> NonEmpty a
|
|
| 1479 | + nubOrdBy :: forall a. (a -> a -> GHC.Internal.Types.Ordering) -> NonEmpty a -> NonEmpty a
|
|
| 1476 | 1480 | partition :: forall a. (a -> GHC.Internal.Types.Bool) -> NonEmpty a -> ([a], [a])
|
| 1477 | 1481 | permutations :: forall a. [a] -> NonEmpty [a]
|
| 1478 | 1482 | permutations1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
|
| ... | ... | @@ -1379,6 +1379,8 @@ module Data.List where |
| 1379 | 1379 | notElem :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Internal.Classes.Eq a) => a -> t a -> GHC.Internal.Types.Bool
|
| 1380 | 1380 | nub :: forall a. GHC.Internal.Classes.Eq a => [a] -> [a]
|
| 1381 | 1381 | nubBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> [a] -> [a]
|
| 1382 | + nubOrd :: forall a. GHC.Internal.Classes.Ord a => [a] -> [a]
|
|
| 1383 | + nubOrdBy :: forall a. (a -> a -> GHC.Internal.Types.Ordering) -> [a] -> [a]
|
|
| 1382 | 1384 | null :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t a -> GHC.Internal.Types.Bool
|
| 1383 | 1385 | or :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Internal.Types.Bool -> GHC.Internal.Types.Bool
|
| 1384 | 1386 | partition :: forall a. (a -> GHC.Internal.Types.Bool) -> [a] -> ([a], [a])
|
| ... | ... | @@ -1473,6 +1475,8 @@ module Data.List.NonEmpty where |
| 1473 | 1475 | nonEmpty :: forall a. [a] -> GHC.Internal.Maybe.Maybe (NonEmpty a)
|
| 1474 | 1476 | nub :: forall a. GHC.Internal.Classes.Eq a => NonEmpty a -> NonEmpty a
|
| 1475 | 1477 | nubBy :: forall a. (a -> a -> GHC.Internal.Types.Bool) -> NonEmpty a -> NonEmpty a
|
| 1478 | + nubOrd :: forall a. GHC.Internal.Classes.Ord a => NonEmpty a -> NonEmpty a
|
|
| 1479 | + nubOrdBy :: forall a. (a -> a -> GHC.Internal.Types.Ordering) -> NonEmpty a -> NonEmpty a
|
|
| 1476 | 1480 | partition :: forall a. (a -> GHC.Internal.Types.Bool) -> NonEmpty a -> ([a], [a])
|
| 1477 | 1481 | permutations :: forall a. [a] -> NonEmpty [a]
|
| 1478 | 1482 | permutations1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
|