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

Safe HaskellNone
LanguageHaskell2010

Data.Text.BoyerMoore.Automaton

Description

An efficient implementation of the Boyer-Moore string search algorithm. http://www-igm.univ-mlv.fr/~lecroq/string/node14.html#SECTION00140 https://en.wikipedia.org/wiki/Boyer%E2%80%93Moore_string-search_algorithm

This module contains a almost 1:1 translation from the C example code in the wikipedia article.

The algorithm here can be potentially improved by including the Galil rule (https:/en.wikipedia.orgwiki/Boyer%E2%80%93Moore_string-search_algorithm#The_Galil_rule)

Synopsis

Documentation

data Automaton Source #

A Boyer-Moore automaton is based on lookup-tables that allow skipping through the haystack. This allows for sub-linear matching in some cases, as we do not have to look at every input character.

NOTE: Unlike the AcMachine, a Boyer-Moore automaton only returns non-overlapping matches. This means that a Boyer-Moore automaton is not a 100% drop-in replacement for Aho-Corasick.

Returning overlapping matches would degrade the performance to O(nm) in pathological cases like finding aaaa in aaaaa....aaaaaa as for each match it would scan back the whole m characters of the pattern.

data CaseSensitivity Source #

Constructors

CaseSensitive 
IgnoreCase 
Instances
Eq CaseSensitivity Source # 
Instance details

Defined in Data.Text.AhoCorasick.Automaton

Show CaseSensitivity Source # 
Instance details

Defined in Data.Text.AhoCorasick.Automaton

Generic CaseSensitivity Source # 
Instance details

Defined in Data.Text.AhoCorasick.Automaton

Associated Types

type Rep CaseSensitivity :: Type -> Type #

Hashable CaseSensitivity Source # 
Instance details

Defined in Data.Text.AhoCorasick.Automaton

ToJSON CaseSensitivity Source # 
Instance details

Defined in Data.Text.AhoCorasick.Automaton

FromJSON CaseSensitivity Source # 
Instance details

Defined in Data.Text.AhoCorasick.Automaton

NFData CaseSensitivity Source # 
Instance details

Defined in Data.Text.AhoCorasick.Automaton

Methods

rnf :: CaseSensitivity -> () #

type Rep CaseSensitivity Source # 
Instance details

Defined in Data.Text.AhoCorasick.Automaton

type Rep CaseSensitivity = D1 (MetaData "CaseSensitivity" "Data.Text.AhoCorasick.Automaton" "alfred-margaret-1.1.1.0-C7p4DoDIXY7azqNtjX433" False) (C1 (MetaCons "CaseSensitive" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IgnoreCase" PrefixI False) (U1 :: Type -> Type))

runText :: forall a. a -> (a -> CodeUnitIndex -> Next a) -> Automaton -> Text -> a Source #

Finds all matches in the text, calling the match callback with the *first* matched character of each match of the pattern.

NOTE: This is unlike Aho-Corasick, which reports the index of the character right after a match.

NOTE: To get full advantage of inlining this function, you probably want to compile the compiling module with -fllvm and the same optimization flags as this module.

runLower :: forall a. a -> (a -> CodeUnitIndex -> Next a) -> Automaton -> Text -> a Source #

Finds all matches in the lowercased text. This function lowercases the text on the fly to avoid allocating a second lowercased text array. Lowercasing is applied to individual code units, so the indexes into the lowercased text can be used to index into the original text. It is still the responsibility of the caller to lowercase the needles. Needles that contain uppercase code points will not match.

NOTE: To get full advantage of inlining this function, you probably want to compile the compiling module with -fllvm and the same optimization flags as this module.

patternLength :: Automaton -> CodeUnitIndex Source #

Length of the matched pattern measured in Utf16 code units.

patternText :: Automaton -> Text Source #

Return the pattern that was used to construct the automaton.

newtype CodeUnitIndex Source #

An index into the raw UTF-16 data of a Text. This is not the code point index as conventionally accepted by Text, so we wrap it to avoid confusing the two. Incorrect index manipulation can lead to surrogate pairs being sliced, so manipulate indices with care. This type is also used for lengths.

Constructors

CodeUnitIndex 

Fields

Instances
Bounded CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

Eq CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

Num CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

Ord CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

Show CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

Generic CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

Associated Types

type Rep CodeUnitIndex :: Type -> Type #

Hashable CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

ToJSON CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

FromJSON CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

NFData CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

Methods

rnf :: CodeUnitIndex -> () #

type Rep CodeUnitIndex Source # 
Instance details

Defined in Data.Text.Utf16

type Rep CodeUnitIndex = D1 (MetaData "CodeUnitIndex" "Data.Text.Utf16" "alfred-margaret-1.1.1.0-C7p4DoDIXY7azqNtjX433" True) (C1 (MetaCons "CodeUnitIndex" PrefixI True) (S1 (MetaSel (Just "codeUnitIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data Next a Source #

Result of handling a match: stepping the automaton can exit early by returning a Done, or it can continue with a new accumulator with Step.

Constructors

Done !a 
Step !a