trie-simple-0.4.1.1: Simple Map-based Trie

Safe HaskellSafe
LanguageHaskell2010

Data.Trie.Set.Internal

Description

This module exposes internal representation of TSet. TSet has one invariant condition:

  • Subtrees of an TSet should not be empty.

For example, consider following tree structure which is valid:

> fromList ["a", "aa", "bc"]
Root -> False
  'a' -> True
    'a' -> True
  'b' -> False
    'c' -> True

Adding redundant node which represents empty set does not change what an TSet represents.

Root -> False
  'a' -> True
    'a' -> True
  'b' -> False
    'c' -> True
  'd' -> False
    'e' -> False
      'f' -> False

But such TSet should not exist because it confuses Eq and Ord instances and null function.

Documentation

newtype TSet c Source #

Constructors

TSet 

Fields

Instances
Eq c => Eq (TSet c) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

(==) :: TSet c -> TSet c -> Bool #

(/=) :: TSet c -> TSet c -> Bool #

Ord c => Ord (TSet c) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

compare :: TSet c -> TSet c -> Ordering #

(<) :: TSet c -> TSet c -> Bool #

(<=) :: TSet c -> TSet c -> Bool #

(>) :: TSet c -> TSet c -> Bool #

(>=) :: TSet c -> TSet c -> Bool #

max :: TSet c -> TSet c -> TSet c #

min :: TSet c -> TSet c -> TSet c #

Show c => Show (TSet c) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

showsPrec :: Int -> TSet c -> ShowS #

show :: TSet c -> String #

showList :: [TSet c] -> ShowS #

Ord c => Semigroup (TSet c) Source #

Semigroup(union)

Instance details

Defined in Data.Trie.Set.Hidden

Methods

(<>) :: TSet c -> TSet c -> TSet c #

sconcat :: NonEmpty (TSet c) -> TSet c #

stimes :: Integral b => b -> TSet c -> TSet c #

Ord c => Monoid (TSet c) Source #

Monoid(empty, union)

Instance details

Defined in Data.Trie.Set.Hidden

Methods

mempty :: TSet c #

mappend :: TSet c -> TSet c -> TSet c #

mconcat :: [TSet c] -> TSet c #

NFData c => NFData (TSet c) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

rnf :: TSet c -> () #

data Node c r Source #

Constructors

Node !Bool !(Map c r) 
Instances
Functor (Node c) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

fmap :: (a -> b) -> Node c a -> Node c b #

(<$) :: a -> Node c b -> Node c a #

Foldable (Node c) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

fold :: Monoid m => Node c m -> m #

foldMap :: Monoid m => (a -> m) -> Node c a -> m #

foldr :: (a -> b -> b) -> b -> Node c a -> b #

foldr' :: (a -> b -> b) -> b -> Node c a -> b #

foldl :: (b -> a -> b) -> b -> Node c a -> b #

foldl' :: (b -> a -> b) -> b -> Node c a -> b #

foldr1 :: (a -> a -> a) -> Node c a -> a #

foldl1 :: (a -> a -> a) -> Node c a -> a #

toList :: Node c a -> [a] #

null :: Node c a -> Bool #

length :: Node c a -> Int #

elem :: Eq a => a -> Node c a -> Bool #

maximum :: Ord a => Node c a -> a #

minimum :: Ord a => Node c a -> a #

sum :: Num a => Node c a -> a #

product :: Num a => Node c a -> a #

Traversable (Node c) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

traverse :: Applicative f => (a -> f b) -> Node c a -> f (Node c b) #

sequenceA :: Applicative f => Node c (f a) -> f (Node c a) #

mapM :: Monad m => (a -> m b) -> Node c a -> m (Node c b) #

sequence :: Monad m => Node c (m a) -> m (Node c a) #

(Eq c, Eq r) => Eq (Node c r) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

(==) :: Node c r -> Node c r -> Bool #

(/=) :: Node c r -> Node c r -> Bool #

(Ord c, Ord r) => Ord (Node c r) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

compare :: Node c r -> Node c r -> Ordering #

(<) :: Node c r -> Node c r -> Bool #

(<=) :: Node c r -> Node c r -> Bool #

(>) :: Node c r -> Node c r -> Bool #

(>=) :: Node c r -> Node c r -> Bool #

max :: Node c r -> Node c r -> Node c r #

min :: Node c r -> Node c r -> Node c r #

(Show c, Show r) => Show (Node c r) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

showsPrec :: Int -> Node c r -> ShowS #

show :: Node c r -> String #

showList :: [Node c r] -> ShowS #

(NFData c, NFData r) => NFData (Node c r) Source # 
Instance details

Defined in Data.Trie.Set.Hidden

Methods

rnf :: Node c r -> () #

foldTSet :: (Node c r -> r) -> TSet c -> r Source #

paraTSet :: (Node c (TSet c, r) -> r) -> TSet c -> r Source #