Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Decidable f => Discriminating f where
- disc :: f a -> [(a, b)] -> [[b]]
- newtype Group a = Group {}
- 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]]
- runGroup :: Group a -> [(a, b)] -> [[b]]
- 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
Discriminating Group Source # | |
Defined in Data.Discrimination.Class | |
Discriminating Sort Source # | |
Defined in Data.Discrimination.Class |
Unordered
Productive Stable Unordered Discriminator
class Grouping a where Source #
Eq
equipped with a compatible stable unordered discriminator.
Law:
groupingEq
x y ≡ (x==
y)
Note: Eq
is a moral super class of Grouping
.
It isn't because of some missing instances.
Nothing
Instances
class Grouping1 f where Source #
Nothing
Instances
Grouping1 [] Source # | |
Grouping1 Maybe Source # | |
Grouping1 Complex Source # | |
Grouping1 NonEmpty Source # | |
Grouping a => Grouping1 (Either a) Source # | |
Grouping a => Grouping1 ((,) a) Source # | |
(Grouping a, Grouping b) => Grouping1 ((,,) a b) Source # | |
(Grouping a, Grouping b, Grouping c) => Grouping1 ((,,,) a b c) Source # | |
(Grouping1 f, Grouping1 g) => Grouping1 (Compose f g) Source # | |
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.
Ordered
Stable Ordered Discriminator
class Grouping a => Sorting a where Source #
Nothing
Instances
class Grouping1 f => Sorting1 f where Source #
Nothing
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
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 []
Joins
:: 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.
:: 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.
:: 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.
:: 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.
:: 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.