regex-do-2.6.2: PCRE wrapper

Safe HaskellNone
LanguageHaskell2010

Text.Regex.Do.Pcre.Utf8.Replace

Description

see also Text.Regex.Do.Pcre.Ascii.Replace

Pattern & Body are wrapped in Utf8_ encoding tag. This tag adds clarity, prevents calling Ascii functions by mistake.

toByteString' converts String to Utf8_ ByteString

Synopsis

Documentation

class Replace pat repl body out where Source

see Text.Regex.Do.Pcre.Ascii.Replace for implemented types

to catch regex construction errors, precompile Regex with makeRegexM or makeRegexOptM

in full typed instance every b is wrapped in Utf8_ newtype

GroupReplacer is implemented only for ByteString

Methods

replace :: pat -> repl -> body -> out Source

Instances

(Regex b, Hint all, Replace' all Utf8_ b repl, Functor all, Enc' repl Utf8_) => Replace b (all (repl b)) b b Source

hint repl

>>> replacer::GroupReplacer (ByteString)
replacer = defaultReplacer 1 tweak1
      where tweak1 s1
                | s1 == toByteString "[команды]" = toByteString "А - Я"
                | s1 == toByteString "[счёт]" = toByteString "5:0"
                | s1 == toByteString "[какая боль, ]" = empty
                | otherwise = traceShow s1 $ toByteString "?"
>>> let rx1 = toByteString "(\\[[^\\]]+\\])"
        body1 = toByteString "[какая боль, ][команды] : [счёт]"
    in replace rx1 (All replacer) body1

"А - Я : 5:0"

(Regex b, Replace' All Utf8_ b repl, Enc' repl Utf8_) => Replace b (repl b) (All b) b Source

hint Body

>>> replace "праздник"
        (Replacement "радость")
        (All "экзамен - всегда праздник")
(Regex b, Replace' Once Utf8_ b repl, Enc' repl Utf8_) => Replace b (repl b) (Once b) b Source

hint Body

>>> replace "праздник"
        (Replacement "радость")
        (Once "экзамен - всегда праздник")
(Regex b, Hint all, Replace' all Utf8_ b repl, Functor all, Enc' repl Utf8_) => Replace (all b) (repl b) b b Source

hint Pattern

>>> replace (All "праздник")
        (Replacement "радость")
        "экзамен - всегда праздник"
Replace' all enc b repl => Replace (all (Pattern (enc b))) (repl (enc b)) (Body (enc b)) b Source

full typed arg

>>> replace (Once $ Pattern $ Utf8_ "праздник")
        (Replacement $ Utf8_ "радость")
        (Body $ Utf8_ "экзамен - всегда праздник")

class Replace' all enc a repl Source

internal class & instances

use replace instead

Minimal complete definition

replace'

Instances

Replace' All Utf8_ String Replacement Source 
Replace' All Utf8_ ByteString Replacement Source 
Replace' All Utf8_ ByteString GroupReplacer Source
>>> replacer::GroupReplacer (Utf8_ ByteString)
        replacer = defaultReplacer 1 tweak1
         where tweak1 bs1 = toByteString' $
                               if bs1 == toByteString' "左" then
                                     "ー右ー"
                                      else "?"
>>> runFn1 `shouldBe` toByteString "100メートルー右ー折後、左"
       where runFn1 =
                let rx1 = Pattern $ toByteString' "(?<=ル)(左)"
                    body1 = Body $ toByteString' "100メートル左折後、左"
                in replace (All rx1) replacer body1        
Replace' Once Utf8_ String Replacement Source 
Replace' Once Utf8_ ByteString Replacement Source 
Replace' Once Utf8_ ByteString GroupReplacer Source