#if __GLASGOW_HASKELL__ >= 800
#endif
module Text.RE.TDFA.ByteString.Lazy
(
(*=~)
, (?=~)
, (*=~/)
, (?=~/)
, (=~)
, (=~~)
, Matches
, matchesSource
, allMatches
, anyMatches
, countMatches
, matches
, Match
, matchSource
, matched
, matchedText
, RE
, SimpleREOptions(..)
, reSource
, compileRegex
, compileRegexWith
, escape
, escapeWith
, module Text.RE.TDFA.RE
) where
import Prelude.Compat
import qualified Data.ByteString.Lazy.Char8 as LBS
import Data.Typeable
import Text.Regex.Base
import Text.RE
import Text.RE.Internal.AddCaptureNames
import Text.RE.SearchReplace
import Text.RE.Types.IsRegex
import Text.RE.Types.REOptions
import Text.RE.Types.Replace
import Text.RE.TDFA.RE
import qualified Text.Regex.TDFA as TDFA
(*=~) :: LBS.ByteString
-> RE
-> Matches LBS.ByteString
(*=~) bs rex = addCaptureNamesToMatches (reCaptureNames rex) $ match (reRegex rex) bs
(?=~) :: LBS.ByteString
-> RE
-> Match LBS.ByteString
(?=~) bs rex = addCaptureNamesToMatch (reCaptureNames rex) $ match (reRegex rex) bs
(?=~/) :: LBS.ByteString -> SearchReplace RE LBS.ByteString -> LBS.ByteString
(?=~/) = flip searchReplaceFirst
(*=~/) :: LBS.ByteString -> SearchReplace RE LBS.ByteString -> LBS.ByteString
(*=~/) = flip searchReplaceAll
(=~) :: ( Typeable a
, RegexContext TDFA.Regex LBS.ByteString a
, RegexMaker TDFA.Regex TDFA.CompOption TDFA.ExecOption String
)
=> LBS.ByteString
-> RE
-> a
(=~) bs rex = addCaptureNames (reCaptureNames rex) $ match (reRegex rex) bs
(=~~) :: ( Monad m
, Functor m
, Typeable a
, RegexContext TDFA.Regex LBS.ByteString a
, RegexMaker TDFA.Regex TDFA.CompOption TDFA.ExecOption String
)
=> LBS.ByteString
-> RE
-> m a
(=~~) bs rex = addCaptureNames (reCaptureNames rex) <$> matchM (reRegex rex) bs
instance IsRegex RE LBS.ByteString where
matchOnce = flip (?=~)
matchMany = flip (*=~)
makeRegexWith = \o -> compileRegexWith o . unpackR
makeSearchReplaceWith = \o r t -> compileSearchReplaceWith o (unpackR r) (unpackR t)
regexSource = packR . reSource