Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
- newtype Group a = Group {
- runGroup :: forall b. [(a, b)] -> [[b]]
- class Grouping a where
- class Grouping1 f where
- nub :: Grouping a => [a] -> [a]
- nubWith :: Grouping b => (a -> b) -> [a] -> [a]
- group :: Grouping a => [a] -> [[a]]
- groupWith :: Grouping b => (a -> b) -> [a] -> [[a]]
- groupingEq :: Grouping a => a -> a -> Bool
- groupingBag :: Foldable f => Group k -> Group (f k)
- groupingSet :: Foldable f => Group k -> Group (f k)
- groupingShort :: Group Int
- groupingNat :: Int -> Group Int
Documentation
Discriminator
Eq
equipped with a compatible stable unordered discriminator.
Nothing
Grouping Bool | |
Grouping Int | |
Grouping Int8 | |
Grouping Int16 | |
Grouping Int32 | |
Grouping Int64 | |
Grouping Word | |
Grouping Word8 | |
Grouping Word16 | |
Grouping Word32 | |
Grouping Word64 | |
Grouping Void | |
Grouping a => Grouping [a] | |
(Grouping a, Integral a) => Grouping (Ratio a) | |
Grouping a => Grouping (Complex a) | |
Grouping a => Grouping (Maybe a) | |
(Grouping a, Grouping b) => Grouping (Either a b) | |
(Grouping a, Grouping b) => Grouping (a, b) | |
(Grouping a, Grouping b, Grouping c) => Grouping (a, b, c) | |
(Grouping1 f, Grouping1 g, Grouping a) => Grouping (Compose f g a) | |
(Grouping a, Grouping b, Grouping c, Grouping d) => Grouping (a, b, c, d) |
Combinators
groupWith :: Grouping b => (a -> b) -> [a] -> [[a]] Source
O(n). This is a replacement for groupWith
using discrimination.
The result equivalence classes are _not_ sorted, but the grouping is stable.
Internals
groupingBag :: Foldable f => Group k -> Group (f k) Source
Construct an stable unordered discriminator that partitions into equivalence classes based on the equivalence of keys as a multiset.
groupingSet :: Foldable f => Group k -> Group (f k) Source
Construct an stable unordered discriminator that partitions into equivalence classes based on the equivalence of keys as a set.
groupingShort :: Group Int Source
Shared bucket set for small integers
groupingNat :: Int -> Group Int Source
Perform stable unordered discrimination by bucket.
This reuses arrays unlike the more obvious ST implementation, so it wins by a huge margin in a race, especially when we have a large keyspace, sparsely used, with low contention. This will leak a number of arrays equal to the maximum concurrent contention for this resource. If this becomes a bottleneck we can make multiple stacks of working pads and index the stack with the hash of the current thread id to reduce contention at the expense of taking more memory.
You should create a thunk that holds the discriminator from groupingNat n
for a known n
and then reuse it.