alfred-margaret-1.1.1.0: Fast Aho-Corasick string searching

Safe HaskellNone
LanguageHaskell2010

Data.Text.BoyerMoore.Searcher

Synopsis

Documentation

data Searcher v Source #

A set of needles with associated values, and Boyer-Moore automata to efficiently find those needles.

INVARIANT: searcherAutomaton = BoyerMoore.buildAutomaton . searcherNeedles To enforce this invariant, the fields are not exposed from this module. There is a separate constructor function.

The purpose of this wrapper is to have a type that is Hashable and Eq, so we can derive those for the types that embed the searcher, whithout requiring the automaton itself to be Hashable or Eq, which would be both wasteful and tedious. Because the automaton is fully determined by the needles and associated values, it is sufficient to implement Eq and Hashable in terms of the needles only.

We also use Hashed to cache the hash of the needles.

Instances
Eq v => Eq (Searcher v) Source # 
Instance details

Defined in Data.Text.BoyerMoore.Searcher

Methods

(==) :: Searcher v -> Searcher v -> Bool #

(/=) :: Searcher v -> Searcher v -> Bool #

Show (Searcher v) Source # 
Instance details

Defined in Data.Text.BoyerMoore.Searcher

Methods

showsPrec :: Int -> Searcher v -> ShowS #

show :: Searcher v -> String #

showList :: [Searcher v] -> ShowS #

Generic (Searcher v) Source # 
Instance details

Defined in Data.Text.BoyerMoore.Searcher

Associated Types

type Rep (Searcher v) :: Type -> Type #

Methods

from :: Searcher v -> Rep (Searcher v) x #

to :: Rep (Searcher v) x -> Searcher v #

Hashable v => Hashable (Searcher v) Source # 
Instance details

Defined in Data.Text.BoyerMoore.Searcher

Methods

hashWithSalt :: Int -> Searcher v -> Int #

hash :: Searcher v -> Int #

NFData v => NFData (Searcher v) Source # 
Instance details

Defined in Data.Text.BoyerMoore.Searcher

Methods

rnf :: Searcher v -> () #

type Rep (Searcher v) Source # 
Instance details

Defined in Data.Text.BoyerMoore.Searcher

type Rep (Searcher v) = D1 (MetaData "Searcher" "Data.Text.BoyerMoore.Searcher" "alfred-margaret-1.1.1.0-C7p4DoDIXY7azqNtjX433" False) (C1 (MetaCons "Searcher" PrefixI True) ((S1 (MetaSel (Just "searcherCaseSensitive") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CaseSensitivity) :*: S1 (MetaSel (Just "searcherNeedles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Hashed [(Text, v)]))) :*: (S1 (MetaSel (Just "searcherNumNeedles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "searcherAutomata") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Automaton, v)]))))

build :: CaseSensitivity -> [Text] -> Searcher () Source #

Builds the Searcher for a list of needles The caller is responsible that the needles are lower case in case the IgnoreCase is used for case sensitivity

buildWithValues :: Hashable v => CaseSensitivity -> [(Text, v)] -> Searcher v Source #

The caller is responsible that the needles are lower case in case the IgnoreCase is used for case sensitivity

needles :: Searcher v -> [(Text, v)] Source #

containsAny :: Searcher () -> Text -> Bool Source #

Return whether the haystack contains any of the needles. Case sensitivity depends on the properties of the searcher This function is marked noinline as an inlining boundary. BoyerMoore.runText is marked inline, so this function will be optimized to report only whether there is a match, and not construct a list of matches. We don't want this function be inline, to make sure that the conditions of the caller don't affect how this function is optimized. There is little to gain from additional inlining. The pragma is not an optimization in itself, rather it is a defence against fragile optimizer decisions.

setSearcherCaseSensitivity :: CaseSensitivity -> Searcher v -> Searcher v Source #

Updates the case sensitivity of the searcher. Does not change the capitilization of the needles. The caller should be certain that if IgnoreCase is passed, the needles are already lower case.