| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Data.Discrimination
- class Decidable f => Discriminating f where- disc :: f a -> [(a, b)] -> [[b]]
 
- 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]]
- groupingBag :: Foldable f => Group k -> Group (f k)
- groupingSet :: Foldable f => Group k -> Group (f k)
- groupingEq :: Grouping a => a -> a -> Bool
- newtype Sort a = Sort {- runSort :: forall b. [(a, b)] -> [[b]]
 
- class Grouping a => Sorting a where
- class Grouping1 f => Sorting1 f where
- desc :: Sort a -> Sort a
- sort :: Sorting a => [a] -> [a]
- sortWith :: Sorting b => (a -> b) -> [a] -> [a]
- sortingBag :: Foldable f => Sort k -> Sort (f k)
- sortingSet :: Foldable f => Sort k -> Sort (f k)
- 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
- joining :: Discriminating f => f d -> ([a] -> [b] -> c) -> (a -> d) -> (b -> d) -> [a] -> [b] -> [c]
- inner :: Discriminating f => f d -> (a -> b -> c) -> (a -> d) -> (b -> d) -> [a] -> [b] -> [[c]]
- outer :: Discriminating f => f d -> (a -> b -> c) -> (a -> c) -> (b -> c) -> (a -> d) -> (b -> d) -> [a] -> [b] -> [[c]]
- leftOuter :: Discriminating f => f d -> (a -> b -> c) -> (a -> c) -> (a -> d) -> (b -> d) -> [a] -> [b] -> [[c]]
- rightOuter :: Discriminating f => f d -> (a -> b -> c) -> (b -> c) -> (a -> d) -> (b -> d) -> [a] -> [b] -> [[c]]
Discrimination
class Decidable f => Discriminating f where Source
Instances
Unordered
Discriminator
Eq equipped with a compatible stable unordered discriminator.
Minimal complete definition
Nothing
Instances
| 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) | 
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.
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.
Ordered
Stable Ordered Discriminator
class Grouping a => Sorting a where Source
Ord equipped with a compatible stable, ordered discriminator.
Minimal complete definition
Nothing
Methods
Instances
| Sorting Bool | |
| Sorting Int | |
| Sorting Int8 | |
| Sorting Int16 | |
| Sorting Int32 | |
| Sorting Int64 | |
| Sorting Word | |
| Sorting Word8 | |
| Sorting Word16 | |
| Sorting Word32 | |
| Sorting Word64 | |
| Sorting Void | |
| Sorting a => Sorting [a] | |
| Sorting a => Sorting (Maybe a) | |
| (Sorting a, Sorting b) => Sorting (Either a b) | |
| (Sorting a, Sorting b) => Sorting (a, b) | |
| (Sorting a, Sorting b, Sorting c) => Sorting (a, b, c) | |
| (Sorting1 f, Sorting1 g, Sorting a) => Sorting (Compose f g a) | |
| (Sorting a, Sorting b, Sorting c, Sorting d) => Sorting (a, b, c, d) | 
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.
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
Joins
Arguments
| :: Discriminating f | |
| => f d | the discriminator to use | 
| -> ([a] -> [b] -> c) | how to join two tables | 
| -> (a -> d) | selector for the left table | 
| -> (b -> d) | selector for the right table | 
| -> [a] | left table | 
| -> [b] | right table | 
| -> [c] | 
O(n). Perform a full outer join while explicit merging of the two result tables a table at a time.
The results are grouped by the discriminator.
Arguments
| :: Discriminating f | |
| => f d | the discriminator to use | 
| -> (a -> b -> c) | how to join two rows | 
| -> (a -> d) | selector for the left table | 
| -> (b -> d) | selector for the right table | 
| -> [a] | left table | 
| -> [b] | right table | 
| -> [[c]] | 
O(n). Perform an inner join, with operations defined one row at a time.
The results are grouped by the discriminator.
This takes operation time linear in both the input and result sets.
Arguments
| :: Discriminating f | |
| => f d | the discriminator to use | 
| -> (a -> b -> c) | how to join two rows | 
| -> (a -> c) | row present on the left, missing on the right | 
| -> (b -> c) | row present on the right, missing on the left | 
| -> (a -> d) | selector for the left table | 
| -> (b -> d) | selector for the right table | 
| -> [a] | left table | 
| -> [b] | right table | 
| -> [[c]] | 
O(n). Perform a full outer join with operations defined one row at a time.
The results are grouped by the discriminator.
This takes operation time linear in both the input and result sets.
Arguments
| :: Discriminating f | |
| => f d | the discriminator to use | 
| -> (a -> b -> c) | how to join two rows | 
| -> (a -> c) | row present on the left, missing on the right | 
| -> (a -> d) | selector for the left table | 
| -> (b -> d) | selector for the right table | 
| -> [a] | left table | 
| -> [b] | right table | 
| -> [[c]] | 
O(n). Perform a left outer join with operations defined one row at a time.
The results are grouped by the discriminator.
This takes operation time linear in both the input and result sets.
Arguments
| :: Discriminating f | |
| => f d | the discriminator to use | 
| -> (a -> b -> c) | how to join two rows | 
| -> (b -> c) | row present on the right, missing on the left | 
| -> (a -> d) | selector for the left table | 
| -> (b -> d) | selector for the right table | 
| -> [a] | left table | 
| -> [b] | right table | 
| -> [[c]] | 
O(n). Perform a right outer join with operations defined one row at a time.
The results are grouped by the discriminator.
This takes operation time linear in both the input and result sets.