| Safe Haskell | Trustworthy |
|---|---|
| Language | Haskell2010 |
Data.GenericTrie.Internal
Description
Unstable implementation details
- class TrieKey k where
- newtype Trie k a = MkTrie (TrieRep k a)
- newtype OrdKey k = OrdKey {
- getOrdKey :: k
- genericTrieNull :: TrieRep k ~ TrieRepDefault k => Trie k a -> Bool
- genericTrieMap :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k) => (a -> b) -> Trie k a -> Trie k b
- genericTrieTraverse :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Applicative f) => (a -> f b) -> Trie k a -> f (Trie k b)
- genericTrieShowsPrec :: (Show a, GTrieKeyShow (Rep k), TrieRep k ~ TrieRepDefault k) => Int -> Trie k a -> ShowS
- genericInsert :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> a -> Trie k a -> Trie k a
- genericLookup :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> Trie k a -> Maybe a
- genericDelete :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> Trie k a -> Trie k a
- genericMapMaybeWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => (k -> a -> Maybe b) -> Trie k a -> Trie k b
- genericSingleton :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> a -> Trie k a
- genericEmpty :: TrieRep k ~ TrieRepDefault k => Trie k a
- genericFoldWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => (k -> a -> r -> r) -> r -> Trie k a -> r
- genericTraverseWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k, Applicative f) => (k -> a -> f b) -> Trie k a -> f (Trie k b)
- data TrieRepDefault k a
- class GTrieKey f where
- data family GTrie (f :: * -> *) a
Documentation
class TrieKey k where Source #
Types that may be used as the key of a Trie.
For data declarations, the instance can be automatically derived from
a Generic instance.
Methods
trieEmpty :: Trie k a Source #
Construct an empty trie
trieNull :: Trie k a -> Bool Source #
Test for an empty trie
trieLookup :: k -> Trie k a -> Maybe a Source #
Lookup element from trie
trieInsert :: k -> a -> Trie k a -> Trie k a Source #
Insert element into trie
trieDelete :: k -> Trie k a -> Trie k a Source #
Delete element from trie
trieSingleton :: k -> a -> Trie k a Source #
Construct a trie holding a single value
trieMap :: (a -> b) -> Trie k a -> Trie k b Source #
Apply a function to all values stored in a trie
trieTraverse :: Applicative f => (a -> f b) -> Trie k a -> f (Trie k b) Source #
Traverse the values stored in a trie
trieShowsPrec :: Show a => Int -> Trie k a -> ShowS Source #
Show the representation of a trie
trieMapMaybeWithKey :: (k -> a -> Maybe b) -> Trie k a -> Trie k b Source #
Apply a function to the values of a Trie and keep the elements
of the trie that result in a Just value.
trieFoldWithKey :: (k -> a -> r -> r) -> r -> Trie k a -> r Source #
Fold a trie with a function of both key and value.
trieTraverseWithKey :: Applicative f => (k -> a -> f b) -> Trie k a -> f (Trie k b) Source #
Traverse a trie with a function of both key and value.
trieMergeWithKey :: (k -> a -> b -> Maybe c) -> (Trie k a -> Trie k c) -> (Trie k b -> Trie k c) -> Trie k a -> Trie k b -> Trie k c Source #
trieEmpty :: TrieRep k ~ TrieRepDefault k => Trie k a Source #
Construct an empty trie
trieSingleton :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> a -> Trie k a Source #
Construct a trie holding a single value
trieNull :: TrieRep k ~ TrieRepDefault k => Trie k a -> Bool Source #
Test for an empty trie
trieLookup :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> Trie k a -> Maybe a Source #
Lookup element from trie
trieInsert :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> a -> Trie k a -> Trie k a Source #
Insert element into trie
trieDelete :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> Trie k a -> Trie k a Source #
Delete element from trie
trieMap :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k) => (a -> b) -> Trie k a -> Trie k b Source #
Apply a function to all values stored in a trie
trieTraverse :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Applicative f) => (a -> f b) -> Trie k a -> f (Trie k b) Source #
Traverse the values stored in a trie
trieShowsPrec :: (Show a, GTrieKeyShow (Rep k), TrieRep k ~ TrieRepDefault k) => Int -> Trie k a -> ShowS Source #
Show the representation of a trie
trieMapMaybeWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => (k -> a -> Maybe b) -> Trie k a -> Trie k b Source #
Apply a function to the values of a Trie and keep the elements
of the trie that result in a Just value.
trieFoldWithKey :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Generic k) => (k -> a -> r -> r) -> r -> Trie k a -> r Source #
Fold a trie with a function of both key and value.
trieTraverseWithKey :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Generic k, Applicative f) => (k -> a -> f b) -> Trie k a -> f (Trie k b) Source #
Traverse a trie with a function of both key and value.
trieMergeWithKey :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Generic k) => (k -> a -> b -> Maybe c) -> (Trie k a -> Trie k c) -> (Trie k b -> Trie k c) -> Trie k a -> Trie k b -> Trie k c Source #
Instances
| TrieKey Bool Source # | |
| TrieKey Char Source # | |
| TrieKey Int Source # | |
| TrieKey Integer Source # | |
| TrieKey () Source # | |
| TrieKey k => TrieKey [k] Source # | |
| TrieKey k => TrieKey (Maybe k) Source # | |
| (Show k, Ord k) => TrieKey (OrdKey k) Source # |
|
| (TrieKey a, TrieKey b) => TrieKey (Either a b) Source # | |
| (TrieKey a, TrieKey b) => TrieKey (a, b) Source # | |
| (TrieKey a, TrieKey b, TrieKey c) => TrieKey (a, b, c) Source # | |
| (TrieKey a, TrieKey b, TrieKey c, TrieKey d) => TrieKey (a, b, c, d) Source # | |
| (TrieKey a, TrieKey b, TrieKey c, TrieKey d, TrieKey e) => TrieKey (a, b, c, d, e) Source # | |
A map from keys of type k, to values of type a.
Tries indexed by OrdKey will be represented as an ordinary Map
and the keys will be compared based on the Ord instance for k.
Instances
| Eq k => Eq (OrdKey k) Source # | |
| Ord k => Ord (OrdKey k) Source # | |
| Read k => Read (OrdKey k) Source # | |
| Show k => Show (OrdKey k) Source # | |
| (Show k, Ord k) => TrieKey (OrdKey k) Source # |
|
| type TrieRep (OrdKey k) Source # | |
Generic derivation implementation
genericTrieNull :: TrieRep k ~ TrieRepDefault k => Trie k a -> Bool Source #
Generic implementation of trieNull. This is the default implementation.
genericTrieMap :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k) => (a -> b) -> Trie k a -> Trie k b Source #
Generic implementation of trieMap. This is the default implementation.
genericTrieTraverse :: (GTrieKey (Rep k), TrieRep k ~ TrieRepDefault k, Applicative f) => (a -> f b) -> Trie k a -> f (Trie k b) Source #
Generic implementation of trieTraverse. This is the default implementation.
genericTrieShowsPrec :: (Show a, GTrieKeyShow (Rep k), TrieRep k ~ TrieRepDefault k) => Int -> Trie k a -> ShowS Source #
Generic implementation of trieShowsPrec. This is the default implementation.
genericInsert :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> a -> Trie k a -> Trie k a Source #
Generic implementation of insert. This is the default implementation.
genericLookup :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> Trie k a -> Maybe a Source #
Generic implementation of lookup. This is the default implementation.
genericDelete :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> Trie k a -> Trie k a Source #
Generic implementation of delete. This is the default implementation.
genericMapMaybeWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => (k -> a -> Maybe b) -> Trie k a -> Trie k b Source #
Generic implementation of mapMaybe. This is the default implementation.
genericSingleton :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => k -> a -> Trie k a Source #
Generic implementation of singleton. This is the default implementation.
genericEmpty :: TrieRep k ~ TrieRepDefault k => Trie k a Source #
Generic implementation of empty. This is the default implementation.
genericFoldWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k) => (k -> a -> r -> r) -> r -> Trie k a -> r Source #
Generic implementation of foldWithKey. This is the default implementation.
genericTraverseWithKey :: (GTrieKey (Rep k), Generic k, TrieRep k ~ TrieRepDefault k, Applicative f) => (k -> a -> f b) -> Trie k a -> f (Trie k b) Source #
Generic implementation of traverseWithKey. This is the default implementation.
data TrieRepDefault k a Source #
class GTrieKey f where Source #
TrieKey operations on Generic representations used to provide the default implementations of tries.
Minimal complete definition
gtrieLookup, gtrieInsert, gtrieSingleton, gtrieDelete, gtrieMap, gtrieTraverse, gmapMaybeWithKey, gfoldWithKey, gtraverseWithKey, gmergeWithKey
Methods
gtrieLookup :: f p -> GTrie f a -> Maybe a Source #
gtrieInsert :: f p -> a -> GTrie f a -> GTrie f a Source #
gtrieSingleton :: f p -> a -> GTrie f a Source #
gtrieDelete :: f p -> GTrie f a -> Maybe (GTrie f a) Source #
gtrieMap :: (a -> b) -> GTrie f a -> GTrie f b Source #
gtrieTraverse :: Applicative m => (a -> m b) -> GTrie f a -> m (GTrie f b) Source #
gmapMaybeWithKey :: (f p -> a -> Maybe b) -> GTrie f a -> Maybe (GTrie f b) Source #
gfoldWithKey :: (f p -> a -> r -> r) -> r -> GTrie f a -> r Source #
gtraverseWithKey :: Applicative m => (f p -> a -> m b) -> GTrie f a -> m (GTrie f b) Source #
gmergeWithKey :: (f p -> a -> b -> Maybe c) -> (GTrie f a -> Maybe (GTrie f c)) -> (GTrie f b -> Maybe (GTrie f c)) -> GTrie f a -> GTrie f b -> Maybe (GTrie f c) Source #
Instances
| GTrieKey (V1 *) Source # | Tries of types without constructors are represented by a unit. |
| GTrieKey (U1 *) Source # | Tries of constructors without fields are represented by a single value. |
| TrieKey k => GTrieKey (K1 * i k) Source # | Generic fields are represented by tries of the field type. |
| (GTrieKey f, GTrieKey g) => GTrieKey ((:+:) * f g) Source # | Generic sums are represented by up to a pair of sub-tries. |
| (GTrieKey f, GTrieKey g) => GTrieKey ((:*:) * f g) Source # | Generic products are represented by tries of tries. |
| GTrieKey f => GTrieKey (M1 * i c f) Source # | Generic metadata is skipped in trie representation and operations. |