regex-do-1.0: PCRE regex funs

Safe HaskellNone
LanguageHaskell2010

Regexdo.Pcre.Replace

Synopsis

Documentation

data ReplaceCase Source

Constructors

Once 
All 
Utf8 
Multiline 

Instances

class Replace_cl a where Source

Methods

replace :: [ReplaceCase] -> (Needle a, Replacement a) -> Haystack a -> a Source

Instances

Replace_cl String Source
>>> replace [Once,Utf8] (Needle "поп", Replacement  "крестьянин") (Haystack "у попа была собака")

"у крестьянина была собака"

>>> replace [Once,Utf8] (Needle "^a\\s", Replacement "A") (Haystack "a bc хол.гор.")

"Abc хол.гор."

Replace_cl ByteString Source 

replaceGroup :: Mm a => [ReplaceCase] -> (Needle a, GroupReplacer a) -> Haystack a -> a Source

dynamic group replace

custom replacer fn returns replacement value

>>> replacer::GroupReplacer String
    replacer marr1 acc1 = case val1 of
                           "101" -> fn1 "[A]"
                           "3" -> fn1 "[Be]"
    where ol1 = marr1 ! 3 :: (MatchOffset, MatchLength)
          val1 = extract ol1 acc1
          fn1 str1 = replaceMatch ol1 (str1,acc1)

see extract

below test compares Once vs All options

>>> groupReplace::IO()
    groupReplace =  hspec $ do
        describe "Pcre.Replace group" $ do
            it "Once" $ do
               runFn1 [Once] `shouldBe` "a=[A] b=3 12"
            it "All" $ do
               runFn1 [All] `shouldBe` "a=[A] b=[Be] 12"
            where runFn1 opts1 =
                     let   rx1 = Needle "(\\w)(=)(\\d{1,3})"
                           body1 = Haystack "a=101 b=3 12"
                     in replaceGroup opts1 (rx1,replacer) body1

replaceMatch Source

Arguments

:: Replace_cl' a 
=> (MatchOffset, MatchLength) 
-> (a, a)

(new val, acc passed to GroupReplacer)

-> a 

use in your custom GroupReplacer passed to replaceGroup

see example replacer above