trie-simple-0.4.1.1: Simple Map-based Trie

Safe HaskellSafe
LanguageHaskell2010

Data.Trie.Set

Contents

Description

This module provides a type TSet c, which is a set of list of some characters. It serves almost same purpose to Set [c], and functions of this module mirrors functions with same name from Data.Set module.

The advantages to use this module over Data.Set are:

But notice for some disadvantages:

  • Some operations are slower than Set [c]. Especially, count is much much slower than size (because Set.size is already recorded in the data structure). Consider TSet.count be like length of list.
  • Constructed TSet c from a list of lists [[c]] do not share each member lists with original list unlike Set [c] does. This means holding both TSet c and [[c]] in memory consumes much more memory than Set [c] and [[c]].
Synopsis

Types

data TSet c Source #

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 -> () #

Queries

member :: Ord c => [c] -> TSet c -> Bool Source #

notMember :: Ord c => [c] -> TSet c -> Bool Source #

beginWith :: Ord c => TSet c -> [c] -> TSet c Source #

beginWith t xs returns new TSet t' which contains all string ys such that t contains xs ++ ys.

count :: TSet c -> Int Source #

Returns number of elements. count takes O(number of nodes) unlike size which is O(1).

enumerate :: TSet c -> [[c]] Source #

List of all elements.

foldMap :: Monoid r => ([c] -> r) -> TSet c -> r Source #

foldr :: ([c] -> r -> r) -> r -> TSet c -> r Source #

foldl' :: (r -> [c] -> r) -> r -> TSet c -> r Source #

Construction

epsilon :: TSet c Source #

epsilon = singleton []

singleton :: [c] -> TSet c Source #

insert :: (Ord c, Foldable f) => f c -> TSet c -> TSet c Source #

delete :: (Ord c, Foldable f) => f c -> TSet c -> TSet c Source #

Combine

union :: Ord c => TSet c -> TSet c -> TSet c Source #

intersection :: Ord c => TSet c -> TSet c -> TSet c Source #

difference :: Ord c => TSet c -> TSet c -> TSet c Source #

append :: Ord c => TSet c -> TSet c -> TSet c Source #

Other operations

suffixes :: Ord c => TSet c -> TSet c Source #

infixes :: Ord c => TSet c -> TSet c Source #

Conversion

fromList :: Ord c => [[c]] -> TSet c Source #

toList :: TSet c -> [[c]] Source #

fromAscList :: Eq c => [[c]] -> TSet c Source #

toAscList :: TSet c -> [[c]] Source #

fromSet :: Eq c => Set [c] -> TSet c Source #

toSet :: TSet c -> Set [c] Source #

Parsing

toParser Source #

Arguments

:: Alternative f 
=> (c -> f a)

char

-> f b

eot

-> TSet c 
-> f [a] 

Construct a "parser" which recognizes member strings of a TSet.

  • char constructs a parser which recognizes a character.
  • eot recognizes the end of a token.

toParser_ Source #

Arguments

:: Alternative f 
=> (c -> f a)

char

-> f b

eot

-> TSet c 
-> f () 

Construct a "parser" which recognizes member strings of a TSet. It discards the information which string it is recognizing.

  • char constructs a parser which recognizes a character.
  • eot recognizes the end of a token.