regex-do-2.6.1: PCRE wrapper

Safe HaskellSafe
LanguageHaskell2010

Text.Regex.Do.Type.Do

Synopsis

Documentation

newtype GroupReplacer b Source

see Text.Regex.Do.Pcre.ReplaceOpen defaultReplacer for example implementation

Constructors

GroupReplacer (MatchArray -> ReplaceAcc b -> ReplaceAcc b) 

Instances

Enc enc => Enc' GroupReplacer enc Source 
ReplaceOpen [] GroupReplacer Source 
ReplaceOpen Maybe GroupReplacer 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_ ByteString GroupReplacer Source 

data ReplaceAcc b Source

Constructors

ReplaceAcc 

Fields

acc :: b

content with some replacements made

pos_adj :: Int

position adjustment: group replacement length may differ from replaced text length

data Pattern a Source

Needle

Constructors

Pattern a 

Instances

Functor Pattern Source 
Applicative Pattern Source 
(Regex a, Hint all, Replace' all a repl b) => Replace (all (Pattern a)) (repl b) (Body b) b Source

full typed arg

>>> replace (Once (Pattern "^a\\s")) (Replacement "A") (Body "a bc")
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_ "экзамен - всегда праздник")

data Body b Source

Haystack

Constructors

Body b 

Instances

Functor Body Source 
Applicative Body Source 
(Regex a, Hint all, Replace' all a repl b) => Replace (all (Pattern a)) (repl b) (Body b) b Source

full typed arg

>>> replace (Once (Pattern "^a\\s")) (Replacement "A") (Body "a bc")
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_ "экзамен - всегда праздник")

type PosLen = (MatchOffset, MatchLength) Source

Offset, Length

newtype Utf8_ a Source

Constructors

Utf8_ a

values

Instances

Functor Utf8_ Source 
Applicative Utf8_ Source

does not do any codec. Plain wrap / unwrap newtype

Enc Utf8_ Source 
MatchHint PosLen_ Utf8_ String Source 
MatchHint PosLen_ Utf8_ ByteString Source 
MatchHint PosLen' Utf8_ String Source
>>> PosLen' ("и"::String) =~ "бывает и хуже"

[(13,2)]

MatchHint PosLen' Utf8_ ByteString Source 
MatchHint All Utf8_ String Source 
MatchHint All Utf8_ ByteString Source 
MatchHint Once Utf8_ String Source
>>> Once ("^all"::String) =~ "all the time"

["all"]

MatchHint Once Utf8_ ByteString Source 
MatchHint Test Utf8_ String Source 
MatchHint Test Utf8_ ByteString Source
>>> Test (toByteString "в") =~ toByteString "тихо в лесу"

True

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 
Rx_ a b => Match Utf8_ a b Bool Source

test. Note that a and b may be different types e.g. ByteString and String

>>> toByteString "в" =~ ("тихо в лесу"::String)::Bool

True

Rx_ a b => Match Utf8_ a b [[PosLen]] Source

match all

Rx_ a b => Match Utf8_ a b [PosLen] Source

match once

>>> ("и"::String) =~ ("бывает и хуже"::String)::[PosLen]

[(13,2)]

Rx_ a b => Match Utf8_ a b [[b]] Source

match all

>>> ("well"::String) =~ ("all is well that ends well"::String)::[[String]]

[["well"],["well"]]

Rx_ a b => Match Utf8_ a b [b] Source

match once

precompiled regex as pattern

>>> let rx1 = makeRegexOpt' (Pattern $ toByteString' "左") [] []      --  add options as needed
        rx2 = Utf8_ <$> rx1
        m1 = U.match rx2 (Body $ toByteString' "100メートル左折後、左")::[ByteString]
     m1 `shouldBe` [toByteString "左"]        
Eq a => Eq (Utf8_ a) Source 
Ord a => Ord (Utf8_ a) Source 
Regex a => Regex (Utf8_ a) Source 
Extract' (Utf8_ ByteString) Source 

class Enc enc where Source

does not do any codec. Plain wrap / unwrap newtype

Methods

val :: enc a -> a Source

enc :: a -> enc a Source

Instances

class Enc' f enc where Source

Methods

val' :: f (enc a) -> f a Source

enc' :: f a -> f (enc a) Source

Instances