Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
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:
- Faster
member
. - Partial match provided by
beginWith
function. - Efficient
append
,prefixes
, andsuffixes
functions.
But notice for some disadvantages:
- Some operations are slower than
Set [c]
. Especially,count
is much much slower thansize
(becauseSet.size
is already recorded in the data structure). ConsiderTSet.count
be likelength
of list. - Constructed
TSet c
from a list of lists[[c]]
do not share each member lists with original list unlikeSet [c]
does. This means holding bothTSet c
and[[c]]
in memory consumes much more memory thanSet [c]
and[[c]]
.
Synopsis
- data TSet c
- member :: Ord c => [c] -> TSet c -> Bool
- notMember :: Ord c => [c] -> TSet c -> Bool
- beginWith :: Ord c => TSet c -> [c] -> TSet c
- null :: TSet c -> Bool
- count :: TSet c -> Int
- enumerate :: TSet c -> [[c]]
- foldMap :: Monoid r => ([c] -> r) -> TSet c -> r
- foldr :: ([c] -> r -> r) -> r -> TSet c -> r
- foldl' :: (r -> [c] -> r) -> r -> TSet c -> r
- empty :: TSet c
- epsilon :: TSet c
- singleton :: [c] -> TSet c
- insert :: (Ord c, Foldable f) => f c -> TSet c -> TSet c
- delete :: (Ord c, Foldable f) => f c -> TSet c -> TSet c
- union :: Ord c => TSet c -> TSet c -> TSet c
- intersection :: Ord c => TSet c -> TSet c -> TSet c
- difference :: Ord c => TSet c -> TSet c -> TSet c
- append :: Ord c => TSet c -> TSet c -> TSet c
- prefixes :: TSet c -> TSet c
- suffixes :: Ord c => TSet c -> TSet c
- infixes :: Ord c => TSet c -> TSet c
- fromList :: Ord c => [[c]] -> TSet c
- toList :: TSet c -> [[c]]
- fromAscList :: Eq c => [[c]] -> TSet c
- toAscList :: TSet c -> [[c]]
- fromSet :: Eq c => Set [c] -> TSet c
- toSet :: TSet c -> Set [c]
- toParser :: Alternative f => (c -> f a) -> f b -> TSet c -> f [a]
- toParser_ :: Alternative f => (c -> f a) -> f b -> TSet c -> f ()
Types
Queries
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).
Construction
Combine
Other operations
Conversion
fromAscList :: Eq c => [[c]] -> TSet c Source #
Parsing
:: 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.
:: 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.