{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances #-}
module Data.Text.BoyerMoore.Replacer
(
replaceSingleLimited
)
where
import Data.Text (Text)
import Data.Text.BoyerMoore.Automaton (CodeUnitIndex, Automaton)
import qualified Data.Text as Text
import Data.Text.BoyerMoore.Automaton (CaseSensitivity (..))
import qualified Data.Text.BoyerMoore.Automaton as BoyerMoore
import qualified Data.Text.Utf16 as Utf16
replaceSingleLimited
:: CaseSensitivity
-> Automaton
-> Text
-> Text
-> CodeUnitIndex
-> Maybe Text
replaceSingleLimited caseSensitivity needle replacement haystack maxLength
| needleLength == 0 = Just $ if haystackLength == 0 then replacement else haystack
| otherwise = finish $ case caseSensitivity of
CaseSensitive -> BoyerMoore.runText initial foundMatch needle haystack
IgnoreCase -> BoyerMoore.runLower initial foundMatch needle haystack
where
needleLength = BoyerMoore.patternLength needle
haystackLength = Utf16.lengthUtf16 haystack
replacementLength = Utf16.lengthUtf16 replacement
initial = ReplaceState
{ rsChunks = []
, rsPreviousMatchEnd = 0
, rsLength = 0
}
foundMatch rs matchStart =
let
matchEnd = matchStart + needleLength
haystackPartLength = matchStart - rsPreviousMatchEnd rs
haystackPart = Utf16.unsafeSliceUtf16 (rsPreviousMatchEnd rs) haystackPartLength haystack
newChunks = replacement : haystackPart : rsChunks rs
newLength = replacementLength + haystackPartLength + rsLength rs
newState = ReplaceState
{ rsChunks = newChunks
, rsPreviousMatchEnd = matchEnd
, rsLength = newLength
}
in
if newLength > maxLength
then BoyerMoore.Done newState
else BoyerMoore.Step newState
finish rs =
let
haystackPartLength = haystackLength - rsPreviousMatchEnd rs
finalChunks
= Utf16.unsafeSliceUtf16 (rsPreviousMatchEnd rs) haystackPartLength haystack
: rsChunks rs
finalLength = rsLength rs + haystackPartLength
in
if finalLength > maxLength
then Nothing
else Just $ Text.concat $ reverse finalChunks
data ReplaceState = ReplaceState
{ rsChunks :: [Text]
, rsPreviousMatchEnd :: !CodeUnitIndex
, rsLength :: !CodeUnitIndex
}