regex-do-3.2.2: PCRE wrapper
Safe HaskellNone
LanguageHaskell2010

Text.Regex.Do.Type.Do

Synopsis

Documentation

newtype GroupReplacer b Source #

see Text.Regex.Do.Replace.Open defaultReplacer for example implementation

Constructors

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

Instances

Instances details
Replace All ByteString (GroupReplacer ByteString) ByteString (E ByteString) Source #
replacer::GroupReplacer ByteString
replacer = defaultReplacer 1 tweak1
      where tweak1 bs1 = toByteString' $
                        if bs1 == toByteString "左" then
                              "ー右ー"
                               else "?"


    runFn1 `shouldBe` toByteString "100メートルー右ー折後、左"
        where runFn1 = let rx1 = toByteString "(?<=ル)(左)"
                           body1 = toByteString "100メートル左折後、左"
                       in replace (All rx1) replacer body1    
Instance details

Defined in Text.Regex.Do.Replace.Utf8

Replace Once ByteString (GroupReplacer ByteString) ByteString (E ByteString) Source # 
Instance details

Defined in Text.Regex.Do.Replace.Utf8

(RegexLike Regex b, Regex b) => Replace All b (GroupReplacer b) b (E b) Source #

b: String | ByteString

Instance details

Defined in Text.Regex.Do.Replace.Latin

Methods

replace :: All b -> GroupReplacer b -> b -> E b Source #

(RegexLike Regex b, Regex b) => Replace Once b (GroupReplacer b) b (E b) Source #

b: String | ByteString

Instance details

Defined in Text.Regex.Do.Replace.Latin

Methods

replace :: Once b -> GroupReplacer b -> b -> E b Source #

Replace [] (GroupReplacer b) b Source # 
Instance details

Defined in Text.Regex.Do.Replace.Open

Methods

replace :: (Extract' b, ToArray arr) => [arr] -> GroupReplacer b -> b -> b Source #

Replace Maybe (GroupReplacer b) b Source # 
Instance details

Defined in Text.Regex.Do.Replace.Open

Methods

replace :: (Extract' b, ToArray arr) => Maybe arr -> GroupReplacer b -> b -> b 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

Instances

Instances details
Functor ReplaceAcc Source # 
Instance details

Defined in Text.Regex.Do.Type.Do_

Methods

fmap :: (a -> b) -> ReplaceAcc a -> ReplaceAcc b #

(<$) :: a -> ReplaceAcc b -> ReplaceAcc a #

type PosLen = (MatchOffset, MatchLength) Source #

Offset, Length

type E a = Either String a Source #

Left String returns regex construction error

newtype Once a Source #

Constructors

Once a

replace once

Instances

Instances details
Functor Once Source # 
Instance details

Defined in Text.Regex.Do.Type.MatchHint

Methods

fmap :: (a -> b) -> Once a -> Once b #

(<$) :: a -> Once b -> Once a #

Applicative Once Source # 
Instance details

Defined in Text.Regex.Do.Type.MatchHint

Methods

pure :: a -> Once a #

(<*>) :: Once (a -> b) -> Once a -> Once b #

liftA2 :: (a -> b -> c) -> Once a -> Once b -> Once c #

(*>) :: Once a -> Once b -> Once b #

(<*) :: Once a -> Once b -> Once a #

Replace Maybe repl ByteString => Replace Once Regex repl ByteString ByteString Source #

succeeds unless GroupReplacer fails due to mismatched pattern etc

repl: ByteString | GroupReplacer ByteString

Instance details

Defined in Text.Regex.Do.Replace.Utf8

Methods

replace :: Once Regex -> repl -> ByteString -> ByteString Source #

Replace Once Regex String String String Source #

always succeeds

Instance details

Defined in Text.Regex.Do.Replace.Utf8

(RegexLike Regex b, Replace Maybe repl b) => Replace Once Regex repl b b Source #

succeeds unless GroupReplacer fails due to mismatched pattern etc

repl: String | ByteString | GroupReplacer repl

Instance details

Defined in Text.Regex.Do.Replace.Latin

Methods

replace :: Once Regex -> repl -> b -> b Source #

Replace Once String String String (E String) Source # 
Instance details

Defined in Text.Regex.Do.Replace.Utf8

Replace Once ByteString ByteString ByteString (E ByteString) Source # 
Instance details

Defined in Text.Regex.Do.Replace.Utf8

(RegexLike Regex b, Regex b) => Replace Once b b b (E b) Source #

b: String | ByteString

Instance details

Defined in Text.Regex.Do.Replace.Latin

Methods

replace :: Once b -> b -> b -> E b Source #

Replace Once ByteString (GroupReplacer ByteString) ByteString (E ByteString) Source # 
Instance details

Defined in Text.Regex.Do.Replace.Utf8

(RegexLike Regex b, Regex b) => Replace Once b (GroupReplacer b) b (E b) Source #

b: String | ByteString

Instance details

Defined in Text.Regex.Do.Replace.Latin

Methods

replace :: Once b -> GroupReplacer b -> b -> E b Source #

newtype All a Source #

Constructors

All a

replace all

Instances

Instances details
Functor All Source # 
Instance details

Defined in Text.Regex.Do.Type.MatchHint

Methods

fmap :: (a -> b) -> All a -> All b #

(<$) :: a -> All b -> All a #

Applicative All Source # 
Instance details

Defined in Text.Regex.Do.Type.MatchHint

Methods

pure :: a -> All a #

(<*>) :: All (a -> b) -> All a -> All b #

liftA2 :: (a -> b -> c) -> All a -> All b -> All c #

(*>) :: All a -> All b -> All b #

(<*) :: All a -> All b -> All a #

Replace [] repl ByteString => Replace All Regex repl ByteString ByteString Source #

succeeds unless GroupReplacer fails due to mismatched pattern etc

repl: ByteString | GroupReplacer ByteString

Instance details

Defined in Text.Regex.Do.Replace.Utf8

Methods

replace :: All Regex -> repl -> ByteString -> ByteString Source #

Replace All Regex String String String Source #

always succeeds

Instance details

Defined in Text.Regex.Do.Replace.Utf8

(RegexLike Regex b, Replace [] repl b) => Replace All Regex repl b b Source #

succeeds unless GroupReplacer fails due to mismatched pattern etc

repl: String | ByteString | GroupReplacer repl

Instance details

Defined in Text.Regex.Do.Replace.Latin

Methods

replace :: All Regex -> repl -> b -> b Source #

Replace All String String String (E String) Source # 
Instance details

Defined in Text.Regex.Do.Replace.Utf8

Replace All ByteString ByteString ByteString (E ByteString) Source # 
Instance details

Defined in Text.Regex.Do.Replace.Utf8

(RegexLike Regex b, Regex b) => Replace All b b b (E b) Source #

b: String | ByteString

Instance details

Defined in Text.Regex.Do.Replace.Latin

Methods

replace :: All b -> b -> b -> E b Source #

Replace All ByteString (GroupReplacer ByteString) ByteString (E ByteString) Source #
replacer::GroupReplacer ByteString
replacer = defaultReplacer 1 tweak1
      where tweak1 bs1 = toByteString' $
                        if bs1 == toByteString "左" then
                              "ー右ー"
                               else "?"


    runFn1 `shouldBe` toByteString "100メートルー右ー折後、左"
        where runFn1 = let rx1 = toByteString "(?<=ル)(左)"
                           body1 = toByteString "100メートル左折後、左"
                       in replace (All rx1) replacer body1    
Instance details

Defined in Text.Regex.Do.Replace.Utf8

(RegexLike Regex b, Regex b) => Replace All b (GroupReplacer b) b (E b) Source #

b: String | ByteString

Instance details

Defined in Text.Regex.Do.Replace.Latin

Methods

replace :: All b -> GroupReplacer b -> b -> E b Source #

data Regex #

A compiled regular expression

Instances

Instances details
Regex Regex Source # 
Instance details

Defined in Text.Regex.Do.Match.Regex

RegexOptions Regex CompOption ExecOption 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexLike Regex b => MatchOnce Regex b Bool Source #

b: String, ByteString

always succeeds

Instance details

Defined in Text.Regex.Do.Match.Utf8

Methods

(~?) :: Regex -> b -> Bool Source #

RegexLike Regex b => MatchOnce Regex b Bool Source #

test.

always succeeds

Instance details

Defined in Text.Regex.Do.Match.Latin

Methods

(~?) :: Regex -> b -> Bool Source #

Replace [] repl ByteString => Replace All Regex repl ByteString ByteString Source #

succeeds unless GroupReplacer fails due to mismatched pattern etc

repl: ByteString | GroupReplacer ByteString

Instance details

Defined in Text.Regex.Do.Replace.Utf8

Methods

replace :: All Regex -> repl -> ByteString -> ByteString Source #

Replace All Regex String String String Source #

always succeeds

Instance details

Defined in Text.Regex.Do.Replace.Utf8

Replace Maybe repl ByteString => Replace Once Regex repl ByteString ByteString Source #

succeeds unless GroupReplacer fails due to mismatched pattern etc

repl: ByteString | GroupReplacer ByteString

Instance details

Defined in Text.Regex.Do.Replace.Utf8

Methods

replace :: Once Regex -> repl -> ByteString -> ByteString Source #

Replace Once Regex String String String Source #

always succeeds

Instance details

Defined in Text.Regex.Do.Replace.Utf8

(RegexLike Regex b, Replace [] repl b) => Replace All Regex repl b b Source #

succeeds unless GroupReplacer fails due to mismatched pattern etc

repl: String | ByteString | GroupReplacer repl

Instance details

Defined in Text.Regex.Do.Replace.Latin

Methods

replace :: All Regex -> repl -> b -> b Source #

(RegexLike Regex b, Replace Maybe repl b) => Replace Once Regex repl b b Source #

succeeds unless GroupReplacer fails due to mismatched pattern etc

repl: String | ByteString | GroupReplacer repl

Instance details

Defined in Text.Regex.Do.Replace.Latin

Methods

replace :: Once Regex -> repl -> b -> b Source #

RegexLike Regex b => MatchAll Regex b [[PosLen]] Source #

b: String, ByteString

always succeeds

Instance details

Defined in Text.Regex.Do.Match.Utf8

Methods

(~*) :: Regex -> b -> [[PosLen]] Source #

RegexLike Regex b => MatchAll Regex b [[b]] Source #

b: String, ByteString

always succeeds

Instance details

Defined in Text.Regex.Do.Match.Utf8

Methods

(~*) :: Regex -> b -> [[b]] Source #

RegexLike Regex b => MatchOnce Regex b [PosLen] Source #

b: String, ByteString

always succeeds

Instance details

Defined in Text.Regex.Do.Match.Utf8

Methods

(~?) :: Regex -> b -> [PosLen] Source #

RegexLike Regex b => MatchOnce Regex b [b] Source #

b: String, ByteString

always succeeds

precompiled regex as pattern

let Right rx1 = makeRegexOpt (toByteString "左") [Utf8] []      --  add options as needed
    m1 = rx1 ~? (toByteString "100メートル左折後、左")::[ByteString]
m1 shouldBe [toByteString "左"]       
Instance details

Defined in Text.Regex.Do.Match.Utf8

Methods

(~?) :: Regex -> b -> [b] Source #

RegexLike Regex b => MatchAll Regex b [[PosLen]] Source #

always succeeds

Instance details

Defined in Text.Regex.Do.Match.Latin

Methods

(~*) :: Regex -> b -> [[PosLen]] Source #

RegexLike Regex b => MatchAll Regex b [[b]] Source #

always succeeds

Instance details

Defined in Text.Regex.Do.Match.Latin

Methods

(~*) :: Regex -> b -> [[b]] Source #

RegexLike Regex b => MatchOnce Regex b [PosLen] Source #

always succeeds

Instance details

Defined in Text.Regex.Do.Match.Latin

Methods

(~?) :: Regex -> b -> [PosLen] Source #

RegexLike Regex b => MatchOnce Regex b [b] Source #

always succeeds

Instance details

Defined in Text.Regex.Do.Match.Latin

Methods

(~?) :: Regex -> b -> [b] Source #

type MatchArray = Array Int (MatchOffset, MatchLength) #

0 based array, with 0th index indicating the full match. If the full match location is not available, represent as (0,0).

newtype CompOption #

Constructors

CompOption CInt 

Instances

Instances details
Eq CompOption 
Instance details

Defined in Text.Regex.PCRE.Wrap

Num CompOption 
Instance details

Defined in Text.Regex.PCRE.Wrap

Show CompOption 
Instance details

Defined in Text.Regex.PCRE.Wrap

Bits CompOption 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexOptions Regex CompOption ExecOption 
Instance details

Defined in Text.Regex.PCRE.Wrap

data ExecOption #

Instances

Instances details
Eq ExecOption 
Instance details

Defined in Text.Regex.PCRE.Wrap

Num ExecOption 
Instance details

Defined in Text.Regex.PCRE.Wrap

Show ExecOption 
Instance details

Defined in Text.Regex.PCRE.Wrap

Bits ExecOption 
Instance details

Defined in Text.Regex.PCRE.Wrap

RegexOptions Regex CompOption ExecOption 
Instance details

Defined in Text.Regex.PCRE.Wrap