discrimination-0.4.1: Fast generic linear-time sorting, joins and container construction.
Safe HaskellNone
LanguageHaskell2010

Data.Discrimination.Sorting

Synopsis

Documentation

newtype Sort a Source #

Stable Ordered Discriminator

Constructors

Sort 

Fields

  • runSort :: forall b. [(a, b)] -> [[b]]
     

Instances

Instances details
Contravariant Sort Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

contramap :: (a -> b) -> Sort b -> Sort a #

(>$) :: b -> Sort b -> Sort a #

Divisible Sort Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

divide :: (a -> (b, c)) -> Sort b -> Sort c -> Sort a #

conquer :: Sort a #

Decidable Sort Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

lose :: (a -> Void) -> Sort a #

choose :: (a -> Either b c) -> Sort b -> Sort c -> Sort a #

Discriminating Sort Source # 
Instance details

Defined in Data.Discrimination.Class

Methods

disc :: Sort a -> [(a, b)] -> [[b]] Source #

Semigroup (Sort a) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

(<>) :: Sort a -> Sort a -> Sort a #

sconcat :: NonEmpty (Sort a) -> Sort a #

stimes :: Integral b => b -> Sort a -> Sort a #

Monoid (Sort a) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

mempty :: Sort a #

mappend :: Sort a -> Sort a -> Sort a #

mconcat :: [Sort a] -> Sort a #

Sorting

class Grouping a => Sorting a where Source #

Ord equipped with a compatible stable, ordered discriminator.

Law:

sortingCompare x y ≡ compare x y

Minimal complete definition

Nothing

Methods

sorting :: Sort a Source #

For every strictly monotone-increasing function f:

contramap f sortingsorting

default sorting :: Deciding Sorting a => Sort a Source #

Instances

Instances details
Sorting Bool Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Char Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Int Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting :: Sort Int Source #

Sorting Int8 Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Int16 Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Int32 Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Int64 Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Integer Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Natural Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Ordering Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Word Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Word8 Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Word16 Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Word32 Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting Word64 Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting () Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting :: Sort () Source #

Sorting Void Source # 
Instance details

Defined in Data.Discrimination.Sorting

Sorting a => Sorting [a] Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting :: Sort [a] Source #

Sorting a => Sorting (Maybe a) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting :: Sort (Maybe a) Source #

Sorting a => Sorting (NonEmpty a) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting :: Sort (NonEmpty a) Source #

(Sorting a, Sorting b) => Sorting (Either a b) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting :: Sort (Either a b) Source #

(Sorting a, Sorting b) => Sorting (a, b) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting :: Sort (a, b) Source #

(Sorting a, Sorting b, Sorting c) => Sorting (a, b, c) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting :: Sort (a, b, c) Source #

(Sorting a, Sorting b, Sorting c, Sorting d) => Sorting (a, b, c, d) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting :: Sort (a, b, c, d) Source #

(Sorting1 f, Sorting1 g, Sorting a) => Sorting (Compose f g a) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting :: Sort (Compose f g a) Source #

class Grouping1 f => Sorting1 f where Source #

Minimal complete definition

Nothing

Methods

sorting1 :: Sort a -> Sort (f a) Source #

default sorting1 :: Deciding1 Sorting f => Sort a -> Sort (f a) Source #

Instances

Instances details
Sorting1 [] Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting1 :: Sort a -> Sort [a] Source #

Sorting1 Maybe Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting1 :: Sort a -> Sort (Maybe a) Source #

Sorting1 NonEmpty Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting1 :: Sort a -> Sort (NonEmpty a) Source #

Sorting a => Sorting1 (Either a) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting1 :: Sort a0 -> Sort (Either a a0) Source #

(Sorting1 f, Sorting1 g) => Sorting1 (Compose f g) Source # 
Instance details

Defined in Data.Discrimination.Sorting

Methods

sorting1 :: Sort a -> Sort (Compose f g a) Source #

Combinators

Useful combinators.

sort :: Sorting a => [a] -> [a] Source #

O(n). Sort a list using discrimination.

sort = sortWith id

sortWith :: Sorting b => (a -> b) -> [a] -> [a] Source #

O(n). Sort a list with a Schwartzian transformation by using discrimination.

This linear time replacement for sortWith and sortOn uses discrimination.

desc :: Sort a -> Sort a Source #

sortingCompare :: Sorting a => a -> a -> Ordering Source #

Valid definition for compare in terms of Sorting.

Container Construction

toMap :: Sorting k => [(k, v)] -> Map k v Source #

O(n). Construct a Map.

This is an asymptotically faster version of fromList, which exploits ordered discrimination.

>>> toMap []
fromList []
>>> toMap [(5,"a"), (3 :: Int,"b"), (5, "c")]
fromList [(3,"b"),(5,"c")]
>>> Map.fromList [(5,"a"), (3 :: Int,"b"), (5, "c")]
fromList [(3,"b"),(5,"c")]
>>> toMap [(5,"c"), (3,"b"), (5 :: Int, "a")]
fromList [(3,"b"),(5,"a")]
>>> Map.fromList [(5,"c"), (3,"b"), (5 :: Int, "a")]
fromList [(3,"b"),(5,"a")]

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")]
>>> Map.fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5 :: Int,"c")]
fromList [(3,"ab"),(5,"cba")]
>>> toMapWith (++) []
fromList []

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 []
fromList []

toIntMap :: [(Int, v)] -> IntMap v Source #

O(n). Construct an IntMap.

>>> toIntMap []
fromList []
>>> toIntMap [(5,"a"), (3,"b"), (5, "c")]
fromList [(3,"b"),(5,"c")]
>>> IntMap.fromList [(5,"a"), (3,"b"), (5, "c")]
fromList [(3,"b"),(5,"c")]
>>> toIntMap [(5,"c"), (3,"b"), (5, "a")]
fromList [(3,"b"),(5,"a")]
>>> IntMap.fromList [(5,"c"), (3,"b"), (5, "a")]
fromList [(3,"b"),(5,"a")]

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")]
>>> IntMap.fromListWith (++) [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"c")]
fromList [(3,"ab"),(5,"cba")]
>>> toIntMapWith (++) []
fromList []

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")]
>>> IntMap.fromListWithKey f [(5,"a"), (5,"b"), (3,"b"), (3,"a"), (5,"c")]
fromList [(3,"3:a|b"),(5,"5:c|5:b|a")]
>>> toIntMapWithKey f []
fromList []

toSet :: Sorting k => [k] -> Set k Source #

O(n). Construct a Set in linear time.

This is an asymptotically faster version of fromList, which exploits ordered discrimination.

toIntSet :: [Int] -> IntSet Source #

O(n). Construct an IntSet in linear time.

This is an asymptotically faster version of fromList, which exploits ordered discrimination.

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.