tries-0.0.6.1: Various trie implementations in Haskell

Safe HaskellNone
LanguageHaskell2010

Data.Trie.List

Documentation

newtype ListTrie t x Source #

Constructors

ListTrie 

Fields

Instances
Eq s => Trie NonEmpty s ListTrie Source # 
Instance details

Defined in Data.Trie.List

Methods

lookup :: NonEmpty s -> ListTrie s a -> Maybe a Source #

insert :: NonEmpty s -> a -> ListTrie s a -> ListTrie s a Source #

delete :: NonEmpty s -> ListTrie s a -> ListTrie s a Source #

Functor (ListTrie t) Source # 
Instance details

Defined in Data.Trie.List

Methods

fmap :: (a -> b) -> ListTrie t a -> ListTrie t b #

(<$) :: a -> ListTrie t b -> ListTrie t a #

Foldable (ListTrie t) Source # 
Instance details

Defined in Data.Trie.List

Methods

fold :: Monoid m => ListTrie t m -> m #

foldMap :: Monoid m => (a -> m) -> ListTrie t a -> m #

foldr :: (a -> b -> b) -> b -> ListTrie t a -> b #

foldr' :: (a -> b -> b) -> b -> ListTrie t a -> b #

foldl :: (b -> a -> b) -> b -> ListTrie t a -> b #

foldl' :: (b -> a -> b) -> b -> ListTrie t a -> b #

foldr1 :: (a -> a -> a) -> ListTrie t a -> a #

foldl1 :: (a -> a -> a) -> ListTrie t a -> a #

toList :: ListTrie t a -> [a] #

null :: ListTrie t a -> Bool #

length :: ListTrie t a -> Int #

elem :: Eq a => a -> ListTrie t a -> Bool #

maximum :: Ord a => ListTrie t a -> a #

minimum :: Ord a => ListTrie t a -> a #

sum :: Num a => ListTrie t a -> a #

product :: Num a => ListTrie t a -> a #

Traversable (ListTrie t) Source # 
Instance details

Defined in Data.Trie.List

Methods

traverse :: Applicative f => (a -> f b) -> ListTrie t a -> f (ListTrie t b) #

sequenceA :: Applicative f => ListTrie t (f a) -> f (ListTrie t a) #

mapM :: Monad m => (a -> m b) -> ListTrie t a -> m (ListTrie t b) #

sequence :: Monad m => ListTrie t (m a) -> m (ListTrie t a) #

(Eq t, Eq x) => Eq (ListTrie t x) Source # 
Instance details

Defined in Data.Trie.List

Methods

(==) :: ListTrie t x -> ListTrie t x -> Bool #

(/=) :: ListTrie t x -> ListTrie t x -> Bool #

(Data t, Data x) => Data (ListTrie t x) Source # 
Instance details

Defined in Data.Trie.List

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListTrie t x -> c (ListTrie t x) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ListTrie t x) #

toConstr :: ListTrie t x -> Constr #

dataTypeOf :: ListTrie t x -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (ListTrie t x)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (ListTrie t x)) #

gmapT :: (forall b. Data b => b -> b) -> ListTrie t x -> ListTrie t x #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListTrie t x -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListTrie t x -> r #

gmapQ :: (forall d. Data d => d -> u) -> ListTrie t x -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ListTrie t x -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListTrie t x -> m (ListTrie t x) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListTrie t x -> m (ListTrie t x) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListTrie t x -> m (ListTrie t x) #

(Show t, Show x) => Show (ListTrie t x) Source # 
Instance details

Defined in Data.Trie.List

Methods

showsPrec :: Int -> ListTrie t x -> ShowS #

show :: ListTrie t x -> String #

showList :: [ListTrie t x] -> ShowS #

Generic (ListTrie t x) Source # 
Instance details

Defined in Data.Trie.List

Associated Types

type Rep (ListTrie t x) :: Type -> Type #

Methods

from :: ListTrie t x -> Rep (ListTrie t x) x0 #

to :: Rep (ListTrie t x) x0 -> ListTrie t x #

(Arbitrary t, Arbitrary x) => Arbitrary (ListTrie t x) Source # 
Instance details

Defined in Data.Trie.List

Methods

arbitrary :: Gen (ListTrie t x) #

shrink :: ListTrie t x -> [ListTrie t x] #

(NFData t, NFData x) => NFData (ListTrie t x) Source # 
Instance details

Defined in Data.Trie.List

Methods

rnf :: ListTrie t x -> () #

type Key (ListTrie s) Source # 
Instance details

Defined in Data.Trie.List

type Key (ListTrie s) = NonEmpty s
type Rep (ListTrie t x) Source # 
Instance details

Defined in Data.Trie.List

type Rep (ListTrie t x) = D1 (MetaData "ListTrie" "Data.Trie.List" "tries-0.0.6.1-Bv92dt7msP1Givg7qeJP0r" True) (C1 (MetaCons "ListTrie" PrefixI True) (S1 (MetaSel (Just "unListTrie") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Tree (t, Maybe x)))))