| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Data.Discrimination.Sorting
Synopsis
- newtype Sort a = Sort {- runSort :: forall b. [(a, b)] -> [[b]]
 
- class Grouping a => Sorting a where
- class Grouping1 f => Sorting1 f where
- sort :: Sorting a => [a] -> [a]
- sortWith :: Sorting b => (a -> b) -> [a] -> [a]
- desc :: Sort a -> Sort a
- sortingCompare :: Sorting a => a -> a -> Ordering
- toMap :: Sorting k => [(k, v)] -> Map k v
- toMapWith :: Sorting k => (v -> v -> v) -> [(k, v)] -> Map k v
- toMapWithKey :: Sorting k => (k -> v -> v -> v) -> [(k, v)] -> Map k v
- toIntMap :: [(Int, v)] -> IntMap v
- toIntMapWith :: (v -> v -> v) -> [(Int, v)] -> IntMap v
- toIntMapWithKey :: (Int -> v -> v -> v) -> [(Int, v)] -> IntMap v
- toSet :: Sorting k => [k] -> Set k
- toIntSet :: [Int] -> IntSet
- sortingNat :: Int -> Sort Int
- sortingBag :: Foldable f => Sort k -> Sort (f k)
- sortingSet :: Foldable f => Sort k -> Sort (f k)
Documentation
Stable Ordered Discriminator
Sorting
class Grouping a => Sorting a where Source #
Ord equipped with a compatible stable, ordered discriminator.
Minimal complete definition
Nothing
Methods
Instances
| Sorting Bool Source # | |
| Sorting Char Source # | |
| Sorting Int Source # | |
| Sorting Int8 Source # | |
| Sorting Int16 Source # | |
| Sorting Int32 Source # | |
| Sorting Int64 Source # | |
| Sorting Integer Source # | |
| Sorting Natural Source # | |
| Sorting Word Source # | |
| Sorting Word8 Source # | |
| Sorting Word16 Source # | |
| Sorting Word32 Source # | |
| Sorting Word64 Source # | |
| Sorting () Source # | |
| Defined in Data.Discrimination.Sorting | |
| Sorting Void Source # | |
| Sorting a => Sorting [a] Source # | |
| Defined in Data.Discrimination.Sorting | |
| Sorting a => Sorting (Maybe a) Source # | |
| (Sorting a, Sorting b) => Sorting (Either a b) Source # | |
| (Sorting a, Sorting b) => Sorting (a, b) Source # | |
| Defined in Data.Discrimination.Sorting | |
| (Sorting a, Sorting b, Sorting c) => Sorting (a, b, c) Source # | |
| Defined in Data.Discrimination.Sorting | |
| (Sorting a, Sorting b, Sorting c, Sorting d) => Sorting (a, b, c, d) Source # | |
| Defined in Data.Discrimination.Sorting | |
| (Sorting1 f, Sorting1 g, Sorting a) => Sorting (Compose f g a) Source # | |
class Grouping1 f => Sorting1 f where Source #
Minimal complete definition
Nothing
Methods
sorting1 :: Sort a -> Sort (f a) Source #
sorting1 :: Deciding1 Sorting f => Sort a -> Sort (f a) Source #
Combinators
Useful combinators.
sortingCompare :: Sorting a => a -> a -> Ordering Source #
Container Construction
toMapWith :: Sorting k => (v -> v -> v) -> [(k, v)] -> Map k v Source #
O(n). Construct a Map, combining values.
This is an asymptotically faster version of fromListWith, which exploits ordered discrimination.
(Note: values combine in anti-stable order for compatibility with fromListWith)
>>>toMapWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5 :: Int,"c")]fromList [(3, "ab"), (5, "cba")]
>>>toMapWith (++) [] == emptyTrue
toMapWithKey :: Sorting k => (k -> v -> v -> v) -> [(k, v)] -> Map k v Source #
O(n). Construct a Map, combining values with access to the key.
This is an asymptotically faster version of fromListWithKey, which exploits ordered discrimination.
(Note: the values combine in anti-stable order for compatibility with fromListWithKey)
>>>let f key new_value old_value = show key ++ ":" ++ new_value ++ "|" ++ old_value>>>toMapWithKey f [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5 :: Int,"c")]fromList [(3, "3:a|b"), (5, "5:c|5:b|a")]
>>>toMapWithKey f [] == emptyTrue
toIntMap :: [(Int, v)] -> IntMap v Source #
O(n). Construct an IntMap.
>>>toIntMap [] == emptyTrue
>>>toIntMap [(5,"a"), (3,"b"), (5, "c")]fromList [(5,"c"), (3,"b")]
>>>toIntMap [(5,"c"), (3,"b"), (5, "a")]fromList [(5,"a"), (3,"b")]
toIntMapWith :: (v -> v -> v) -> [(Int, v)] -> IntMap v Source #
O(n). Construct an IntMap, combining values.
This is an asymptotically faster version of fromListWith, which exploits ordered discrimination.
(Note: values combine in anti-stable order for compatibility with fromListWith)
>>>toIntMapWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"c")]fromList [(3, "ab"), (5, "cba")]
>>>toIntMapWith (++) [] == emptyTrue
toIntMapWithKey :: (Int -> v -> v -> v) -> [(Int, v)] -> IntMap v Source #
O(n). Construct a Map, combining values with access to the key.
This is an asymptotically faster version of fromListWithKey, which exploits ordered discrimination.
(Note: the values combine in anti-stable order for compatibility with fromListWithKey)
>>>let f key new_value old_value = show key ++ ":" ++ new_value ++ "|" ++ old_value>>>toIntMapWithKey f [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"c")]fromList [(3, "3:a|b"), (5, "5:c|5:b|a")]
>>>toIntMapWithKey f [] == emptyTrue
Internals
sortingBag :: Foldable f => Sort k -> Sort (f k) Source #
Construct a stable ordered discriminator that sorts a list as multisets of elements from another stable ordered discriminator.
The resulting discriminator only cares about the set of keys and their multiplicity, and is sorted as if we'd sorted each key in turn before comparing.
sortingSet :: Foldable f => Sort k -> Sort (f k) Source #
Construct a stable ordered discriminator that sorts a list as sets of elements from another stable ordered discriminator.
The resulting discriminator only cares about the set of keys, and is sorted as if we'd sorted each key in turn before comparing.