module Text.Regex.TDFA.Text.Lazy(
Regex
,CompOption
,ExecOption
,compile
,execute
,regexec
) where
import Data.Array.IArray(Array,(!),elems)
import qualified Data.Text.Lazy as L(Text,unpack)
import Text.Regex.Base(MatchArray,RegexContext(..),Extract(..),RegexMaker(..),RegexLike(..))
import Text.Regex.Base.Impl(polymatch,polymatchM)
import Text.Regex.TDFA.ReadRegex(parseRegex)
import Text.Regex.TDFA.String()
import Text.Regex.TDFA.TDFA(patternToRegex)
import Text.Regex.TDFA.Common(Regex(..),CompOption,ExecOption(captureGroups),Position)
import Data.Maybe(listToMaybe)
import Text.Regex.TDFA.NewDFA.Uncons(Uncons)
import qualified Text.Regex.TDFA.NewDFA.Engine as Engine(execMatch)
import qualified Text.Regex.TDFA.NewDFA.Tester as Tester(matchTest)
instance RegexContext Regex L.Text L.Text where
match :: Regex -> Text -> Text
match = Regex -> Text -> Text
forall a b. RegexLike a b => a -> b -> b
polymatch
matchM :: Regex -> Text -> m Text
matchM = Regex -> Text -> m Text
forall a b (m :: * -> *).
(RegexLike a b, MonadFail m) =>
a -> b -> m b
polymatchM
instance RegexMaker Regex CompOption ExecOption L.Text where
makeRegexOptsM :: CompOption -> ExecOption -> Text -> m Regex
makeRegexOptsM CompOption
c ExecOption
e Text
source = CompOption -> ExecOption -> String -> m Regex
forall regex compOpt execOpt source (m :: * -> *).
(RegexMaker regex compOpt execOpt source, MonadFail m) =>
compOpt -> execOpt -> source -> m regex
makeRegexOptsM CompOption
c ExecOption
e (Text -> String
L.unpack Text
source)
{-# SPECIALIZE execMatch :: Regex -> Position -> Char -> L.Text -> [MatchArray] #-}
execMatch :: Uncons text => Regex -> Position -> Char -> text -> [MatchArray]
execMatch :: Regex -> Position -> Char -> text -> [MatchArray]
execMatch = Regex -> Position -> Char -> text -> [MatchArray]
forall text.
Uncons text =>
Regex -> Position -> Char -> text -> [MatchArray]
Engine.execMatch
{-# SPECIALIZE myMatchTest :: Regex -> L.Text -> Bool #-}
myMatchTest :: Uncons text => Regex -> text -> Bool
myMatchTest :: Regex -> text -> Bool
myMatchTest = Regex -> text -> Bool
forall text. Uncons text => Regex -> text -> Bool
Tester.matchTest
instance RegexLike Regex L.Text where
matchOnce :: Regex -> Text -> Maybe MatchArray
matchOnce Regex
r Text
s = [MatchArray] -> Maybe MatchArray
forall a. [a] -> Maybe a
listToMaybe (Regex -> Text -> [MatchArray]
forall regex source.
RegexLike regex source =>
regex -> source -> [MatchArray]
matchAll Regex
r Text
s)
matchAll :: Regex -> Text -> [MatchArray]
matchAll Regex
r Text
s = Regex -> Position -> Char -> Text -> [MatchArray]
forall text.
Uncons text =>
Regex -> Position -> Char -> text -> [MatchArray]
execMatch Regex
r Position
0 Char
'\n' Text
s
matchCount :: Regex -> Text -> Position
matchCount Regex
r Text
s = [MatchArray] -> Position
forall (t :: * -> *) a. Foldable t => t a -> Position
length (Regex -> Text -> [MatchArray]
forall regex source.
RegexLike regex source =>
regex -> source -> [MatchArray]
matchAll Regex
r' Text
s)
where r' :: Regex
r' = Regex
r { regex_execOptions :: ExecOption
regex_execOptions = (Regex -> ExecOption
regex_execOptions Regex
r) {captureGroups :: Bool
captureGroups = Bool
False} }
matchTest :: Regex -> Text -> Bool
matchTest = Regex -> Text -> Bool
forall text. Uncons text => Regex -> text -> Bool
myMatchTest
matchOnceText :: Regex -> Text -> Maybe (Text, MatchText Text, Text)
matchOnceText Regex
regex Text
source =
(MatchArray -> (Text, MatchText Text, Text))
-> Maybe MatchArray -> Maybe (Text, MatchText Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ MatchArray
ma ->
let (Position
o,Position
l) = MatchArray
maMatchArray -> Position -> (Position, Position)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!Position
0
in (Position -> Text -> Text
forall source. Extract source => Position -> source -> source
before Position
o Text
source
,((Position, Position) -> (Text, (Position, Position)))
-> MatchArray -> MatchText Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ (Position, Position)
ol -> ((Position, Position) -> Text -> Text
forall source.
Extract source =>
(Position, Position) -> source -> source
extract (Position, Position)
ol Text
source,(Position, Position)
ol)) MatchArray
ma
,Position -> Text -> Text
forall source. Extract source => Position -> source -> source
after (Position
oPosition -> Position -> Position
forall a. Num a => a -> a -> a
+Position
l) Text
source))
(Regex -> Text -> Maybe MatchArray
forall regex source.
RegexLike regex source =>
regex -> source -> Maybe MatchArray
matchOnce Regex
regex Text
source)
matchAllText :: Regex -> Text -> [MatchText Text]
matchAllText Regex
regex Text
source =
let go :: Int -> L.Text -> [Array Int (Int, Int)] -> [Array Int (L.Text, (Int, Int))]
go :: Position -> Text -> [MatchArray] -> [MatchText Text]
go Position
i Text
_ [MatchArray]
_ | Position
i Position -> Bool -> Bool
`seq` Bool
False = [MatchText Text]
forall a. HasCallStack => a
undefined
go Position
_i Text
_t [] = []
go Position
i Text
t (MatchArray
x:[MatchArray]
xs) =
let (Position
off0,Position
len0) = MatchArray
xMatchArray -> Position -> (Position, Position)
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!Position
0
trans :: (Position, Position) -> (Text, (Position, Position))
trans pair :: (Position, Position)
pair@(Position
off,Position
len) = ((Position, Position) -> Text -> Text
forall source.
Extract source =>
(Position, Position) -> source -> source
extract (Position
offPosition -> Position -> Position
forall a. Num a => a -> a -> a
-Position
i,Position
len) Text
t,(Position, Position)
pair)
t' :: Text
t' = Position -> Text -> Text
forall source. Extract source => Position -> source -> source
after (Position
off0Position -> Position -> Position
forall a. Num a => a -> a -> a
+(Position
len0Position -> Position -> Position
forall a. Num a => a -> a -> a
-Position
i)) Text
t
in ((Position, Position) -> (Text, (Position, Position)))
-> MatchArray -> MatchText Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Position, Position) -> (Text, (Position, Position))
trans MatchArray
x MatchText Text -> [MatchText Text] -> [MatchText Text]
forall a. a -> [a] -> [a]
: Text -> [MatchText Text] -> [MatchText Text]
seq Text
t' (Position -> Text -> [MatchArray] -> [MatchText Text]
go (Position
off0Position -> Position -> Position
forall a. Num a => a -> a -> a
+Position
len0) Text
t' [MatchArray]
xs)
in Position -> Text -> [MatchArray] -> [MatchText Text]
go Position
0 Text
source (Regex -> Text -> [MatchArray]
forall regex source.
RegexLike regex source =>
regex -> source -> [MatchArray]
matchAll Regex
regex Text
source)
compile :: CompOption
-> ExecOption
-> L.Text
-> Either String Regex
compile :: CompOption -> ExecOption -> Text -> Either String Regex
compile CompOption
compOpt ExecOption
execOpt Text
txt =
case String -> Either ParseError (Pattern, (Position, DoPa))
parseRegex (Text -> String
L.unpack Text
txt) of
Left ParseError
err -> String -> Either String Regex
forall a b. a -> Either a b
Left (String
"parseRegex for Text.Regex.TDFA.Text.Lazy failed:"String -> String -> String
forall a. [a] -> [a] -> [a]
++ParseError -> String
forall a. Show a => a -> String
show ParseError
err)
Right (Pattern, (Position, DoPa))
pattern -> Regex -> Either String Regex
forall a b. b -> Either a b
Right ((Pattern, (Position, DoPa)) -> CompOption -> ExecOption -> Regex
patternToRegex (Pattern, (Position, DoPa))
pattern CompOption
compOpt ExecOption
execOpt)
execute :: Regex
-> L.Text
-> Either String (Maybe MatchArray)
execute :: Regex -> Text -> Either String (Maybe MatchArray)
execute Regex
r Text
txt = Maybe MatchArray -> Either String (Maybe MatchArray)
forall a b. b -> Either a b
Right (Regex -> Text -> Maybe MatchArray
forall regex source.
RegexLike regex source =>
regex -> source -> Maybe MatchArray
matchOnce Regex
r Text
txt)
regexec :: Regex
-> L.Text
-> Either String (Maybe (L.Text, L.Text, L.Text, [L.Text]))
regexec :: Regex -> Text -> Either String (Maybe (Text, Text, Text, [Text]))
regexec Regex
r Text
txt =
case Regex -> Text -> Maybe (Text, MatchText Text, Text)
forall regex source.
RegexLike regex source =>
regex -> source -> Maybe (source, MatchText source, source)
matchOnceText Regex
r Text
txt of
Maybe (Text, MatchText Text, Text)
Nothing -> Maybe (Text, Text, Text, [Text])
-> Either String (Maybe (Text, Text, Text, [Text]))
forall a b. b -> Either a b
Right (Maybe (Text, Text, Text, [Text])
forall a. Maybe a
Nothing)
Just (Text
pre,MatchText Text
mt,Text
post) ->
let main :: Text
main = (Text, (Position, Position)) -> Text
forall a b. (a, b) -> a
fst (MatchText Text
mtMatchText Text -> Position -> (Text, (Position, Position))
forall (a :: * -> * -> *) e i.
(IArray a e, Ix i) =>
a i e -> i -> e
!Position
0)
rest :: [Text]
rest = ((Text, (Position, Position)) -> Text)
-> [(Text, (Position, Position))] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text, (Position, Position)) -> Text
forall a b. (a, b) -> a
fst ([(Text, (Position, Position))] -> [(Text, (Position, Position))]
forall a. [a] -> [a]
tail (MatchText Text -> [(Text, (Position, Position))]
forall (a :: * -> * -> *) e i. (IArray a e, Ix i) => a i e -> [e]
elems MatchText Text
mt))
in Maybe (Text, Text, Text, [Text])
-> Either String (Maybe (Text, Text, Text, [Text]))
forall a b. b -> Either a b
Right ((Text, Text, Text, [Text]) -> Maybe (Text, Text, Text, [Text])
forall a. a -> Maybe a
Just (Text
pre,Text
main,Text
post,[Text]
rest))