| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Text.Regex.Do.Type.Do
Synopsis
- newtype GroupReplacer b = GroupReplacer (MatchArray -> ReplaceAcc b -> ReplaceAcc b)
 - data ReplaceAcc b = ReplaceAcc {}
 - type PosLen = (MatchOffset, MatchLength)
 - type E a = Either String a
 - newtype Once a = Once a
 - newtype All a = All a
 - data Regex
 - type MatchArray = Array Int (MatchOffset, MatchLength)
 - newtype CompOption = CompOption CInt
 - data ExecOption
 
Documentation
newtype GroupReplacer b Source #
see Text.Regex.Do.Replace.Open defaultReplacer for example implementation
Constructors
| GroupReplacer (MatchArray -> ReplaceAcc b -> ReplaceAcc b) | 
Instances
data ReplaceAcc b Source #
Constructors
| ReplaceAcc | |
Instances
| Functor ReplaceAcc Source # | |
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
Constructors
| Once a | replace once  | 
Instances
Constructors
| All a | replace all  | 
Instances
| Functor All Source # | |
| Applicative All Source # | |
| Replace [] repl ByteString => Replace All Regex repl ByteString ByteString Source # | succeeds unless  repl:   | 
Defined in Text.Regex.Do.Replace.Utf8 Methods replace :: All Regex -> repl -> ByteString -> ByteString Source #  | |
| Replace All Regex String String String Source # | always succeeds  | 
| (RegexLike Regex b, Replace [] repl b) => Replace All Regex repl b b Source # | succeeds unless  repl:   | 
| Replace All String String String (E String) Source # | |
| Replace All ByteString ByteString ByteString (E ByteString) Source # | |
Defined in Text.Regex.Do.Replace.Utf8 Methods replace :: All ByteString -> ByteString -> ByteString -> E ByteString Source #  | |
| (RegexLike Regex b, Regex b) => Replace All b b b (E b) Source # | b:   | 
| 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    
 | 
Defined in Text.Regex.Do.Replace.Utf8 Methods replace :: All ByteString -> GroupReplacer ByteString -> ByteString -> E ByteString Source #  | |
| (RegexLike Regex b, Regex b) => Replace All b (GroupReplacer b) b (E b) Source # | b:   | 
Defined in Text.Regex.Do.Replace.Latin  | |
A compiled regular expression
Instances
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
data ExecOption #