{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 800
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
#endif
module Text.RE.TDFA.Text.Lazy
(
(*=~)
, (?=~)
, (*=~/)
, (?=~/)
, Matches
, matchesSource
, allMatches
, anyMatches
, countMatches
, matches
, Match
, matchSource
, matched
, matchedText
, module Text.RE.TestBench.Parsers
, RE
, reSource
, SimpleREOptions(..)
, SearchReplace(..)
, compileRegex
, compileRegexWith
, compileSearchReplace
, compileSearchReplaceWith
, escape
, escapeWith
, escapeREString
, (=~)
, (=~~)
, re
, reMultilineSensitive
, reMultilineInsensitive
, reBlockSensitive
, reBlockInsensitive
, reMS
, reMI
, reBS
, reBI
, re_
, edMultilineSensitive
, edMultilineInsensitive
, edBlockSensitive
, edBlockInsensitive
, ed
, edMS
, edMI
, edBS
, edBI
, ed_
, cp
, module Text.RE.Tools.IsRegex
) where
import Control.Monad.Fail
import qualified Data.Text.Lazy as TL
import Data.Typeable
import Prelude.Compat
import Text.RE.REOptions
import Text.RE.Replace
import Text.RE.TestBench.Parsers
import Text.RE.Tools.IsRegex
import Text.RE.ZeInternals
import Text.RE.ZeInternals.SearchReplace.TDFA.Text.Lazy
import Text.RE.ZeInternals.TDFA
import Text.Regex.Base
import qualified Text.Regex.TDFA as TDFA
(*=~) :: TL.Text
-> RE
-> Matches TL.Text
*=~ :: Text -> RE -> Matches Text
(*=~) Text
bs RE
rex = CaptureNames -> Matches Text -> Matches Text
forall a. CaptureNames -> Matches a -> Matches a
addCaptureNamesToMatches (RE -> CaptureNames
reCaptureNames RE
rex) (Matches Text -> Matches Text) -> Matches Text -> Matches Text
forall a b. (a -> b) -> a -> b
$ Regex -> Text -> Matches Text
forall regex source target.
RegexContext regex source target =>
regex -> source -> target
match (RE -> Regex
reRegex RE
rex) Text
bs
(?=~) :: TL.Text
-> RE
-> Match TL.Text
?=~ :: Text -> RE -> Match Text
(?=~) Text
bs RE
rex = CaptureNames -> Match Text -> Match Text
forall a. CaptureNames -> Match a -> Match a
addCaptureNamesToMatch (RE -> CaptureNames
reCaptureNames RE
rex) (Match Text -> Match Text) -> Match Text -> Match Text
forall a b. (a -> b) -> a -> b
$ Regex -> Text -> Match Text
forall regex source target.
RegexContext regex source target =>
regex -> source -> target
match (RE -> Regex
reRegex RE
rex) Text
bs
(*=~/) :: TL.Text -> SearchReplace RE TL.Text -> TL.Text
*=~/ :: Text -> SearchReplace RE Text -> Text
(*=~/) = (SearchReplace RE Text -> Text -> Text)
-> Text -> SearchReplace RE Text -> Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip SearchReplace RE Text -> Text -> Text
forall re s. IsRegex re s => SearchReplace re s -> s -> s
searchReplaceAll
(?=~/) :: TL.Text -> SearchReplace RE TL.Text -> TL.Text
?=~/ :: Text -> SearchReplace RE Text -> Text
(?=~/) = (SearchReplace RE Text -> Text -> Text)
-> Text -> SearchReplace RE Text -> Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip SearchReplace RE Text -> Text -> Text
forall re s. IsRegex re s => SearchReplace re s -> s -> s
searchReplaceFirst
(=~) :: ( Typeable a
, RegexContext TDFA.Regex TL.Text a
)
=> TL.Text
-> RE
-> a
=~ :: Text -> RE -> a
(=~) Text
bs RE
rex = CaptureNames -> a -> a
forall a. Typeable a => CaptureNames -> a -> a
addCaptureNames (RE -> CaptureNames
reCaptureNames RE
rex) (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ Regex -> Text -> a
forall regex source target.
RegexContext regex source target =>
regex -> source -> target
match (RE -> Regex
reRegex RE
rex) Text
bs
(=~~) :: ( Monad m, MonadFail m
, Functor m
, Typeable a
, RegexContext TDFA.Regex TL.Text a
)
=> TL.Text
-> RE
-> m a
=~~ :: Text -> RE -> m a
(=~~) Text
bs RE
rex = CaptureNames -> a -> a
forall a. Typeable a => CaptureNames -> a -> a
addCaptureNames (RE -> CaptureNames
reCaptureNames RE
rex) (a -> a) -> m a -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Regex -> Text -> m a
forall regex source target (m :: * -> *).
(RegexContext regex source target, MonadFail m) =>
regex -> source -> m target
matchM (RE -> Regex
reRegex RE
rex) Text
bs
instance IsRegex RE TL.Text where
matchOnce :: RE -> Text -> Match Text
matchOnce = (Text -> RE -> Match Text) -> RE -> Text -> Match Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> RE -> Match Text
(?=~)
matchMany :: RE -> Text -> Matches Text
matchMany = (Text -> RE -> Matches Text) -> RE -> Text -> Matches Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> RE -> Matches Text
(*=~)
makeRegexWith :: SimpleREOptions -> Text -> m RE
makeRegexWith = \SimpleREOptions
o -> SimpleREOptions -> String -> m RE
forall (m :: * -> *).
(Functor m, Monad m, MonadFail m) =>
SimpleREOptions -> String -> m RE
compileRegexWith SimpleREOptions
o (String -> m RE) -> (Text -> String) -> Text -> m RE
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
forall a. Replace a => a -> String
unpackR
makeSearchReplaceWith :: SimpleREOptions -> Text -> Text -> m (SearchReplace RE Text)
makeSearchReplaceWith = \SimpleREOptions
o Text
r Text
t -> SimpleREOptions -> String -> String -> m (SearchReplace RE Text)
forall (m :: * -> *) s.
(Monad m, MonadFail m, Functor m, IsRegex RE s) =>
SimpleREOptions -> String -> String -> m (SearchReplace RE s)
compileSearchReplaceWith SimpleREOptions
o (Text -> String
forall a. Replace a => a -> String
unpackR Text
r) (Text -> String
forall a. Replace a => a -> String
unpackR Text
t)
regexSource :: RE -> Text
regexSource = String -> Text
forall a. Replace a => String -> a
packR (String -> Text) -> (RE -> String) -> RE -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RE -> String
reSource