alfred-margaret-2.1.0.0: Fast Aho-Corasick string searching
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Text.AhoCorasick.Replacer

Description

Implements sequential string replacements based on the Aho-Corasick algorithm.

Synopsis

State machine

type Needle = Text Source #

Descriptive type alias for strings to search for.

data Payload Source #

Constructors

Payload 

Fields

Instances

Instances details
FromJSON Payload Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

ToJSON Payload Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

Generic Payload Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

Associated Types

type Rep Payload :: Type -> Type #

Methods

from :: Payload -> Rep Payload x #

to :: Rep Payload x -> Payload #

Show Payload Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

NFData Payload Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

Methods

rnf :: Payload -> () #

Eq Payload Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

Methods

(==) :: Payload -> Payload -> Bool #

(/=) :: Payload -> Payload -> Bool #

Hashable Payload Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

Methods

hashWithSalt :: Int -> Payload -> Int #

hash :: Payload -> Int #

type Rep Payload Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

type Replacement = Text Source #

Descriptive type alias for replacements.

data Replacer Source #

A state machine used for efficient replacements with many different needles.

Constructors

Replacer 

Instances

Instances details
FromJSON Replacer Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

ToJSON Replacer Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

Generic Replacer Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

Associated Types

type Rep Replacer :: Type -> Type #

Methods

from :: Replacer -> Rep Replacer x #

to :: Rep Replacer x -> Replacer #

Show Replacer Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

NFData Replacer Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

Methods

rnf :: Replacer -> () #

Eq Replacer Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

Hashable Replacer Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

Methods

hashWithSalt :: Int -> Replacer -> Int #

hash :: Replacer -> Int #

type Rep Replacer Source # 
Instance details

Defined in Data.Text.AhoCorasick.Replacer

type Rep Replacer = D1 ('MetaData "Replacer" "Data.Text.AhoCorasick.Replacer" "alfred-margaret-2.1.0.0-GaLGdvCW2mGJuL9TH52qO1" 'False) (C1 ('MetaCons "Replacer" 'PrefixI 'True) (S1 ('MetaSel ('Just "replacerSearcher") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Searcher Payload))))

build :: CaseSensitivity -> [(Needle, Replacement)] -> Replacer Source #

Build an Aho-Corasick automaton that can be used for performing fast sequential replaces.

Case-insensitive matching performs per-letter language-agnostic lower-casing. Therefore, it will work in most cases, but not in languages where lower-casing depends on the context of the character in question.

We need to revisit this algorithm when we want to implement full Unicode support.

compose :: Replacer -> Replacer -> Maybe Replacer Source #

Return the composition replacer2 after replacer1, if they have the same case sensitivity. If the case sensitivity differs, Nothing is returned.

mapReplacement :: (Replacement -> Replacement) -> Replacer -> Replacer Source #

Modify the replacement of a replacer. It doesn't modify the needles.

setCaseSensitivity :: CaseSensitivity -> Replacer -> Replacer Source #

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