{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
module Text.Regex (
Regex,
mkRegex,
mkRegexWithOpts,
matchRegex,
matchRegexAll,
subRegex,
splitRegex
) where
import Data.Array((!))
import Data.Bits((.|.))
import Text.Regex.Base(RegexMaker(makeRegexOpts),defaultExecOpt,RegexLike(matchAll,matchAllText),RegexContext(matchM),MatchText)
import Text.Regex.Posix(Regex,compNewline,compIgnoreCase,compExtended)
mkRegex :: String -> Regex
mkRegex :: String -> Regex
mkRegex String
s = CompOption -> ExecOption -> String -> Regex
forall regex compOpt execOpt source.
RegexMaker regex compOpt execOpt source =>
compOpt -> execOpt -> source -> regex
makeRegexOpts CompOption
opt ExecOption
forall regex compOpt execOpt.
RegexOptions regex compOpt execOpt =>
execOpt
defaultExecOpt String
s
where opt :: CompOption
opt = CompOption
compExtended CompOption -> CompOption -> CompOption
forall a. Bits a => a -> a -> a
.|. CompOption
compNewline
mkRegexWithOpts
:: String
-> Bool
-> Bool
-> Regex
mkRegexWithOpts :: String -> Bool -> Bool -> Regex
mkRegexWithOpts String
s Bool
single_line Bool
case_sensitive
= let opt :: CompOption
opt = (if Bool
single_line then (CompOption
compNewline CompOption -> CompOption -> CompOption
forall a. Bits a => a -> a -> a
.|.) else CompOption -> CompOption
forall a. a -> a
id) (CompOption -> CompOption)
-> (CompOption -> CompOption) -> CompOption -> CompOption
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(if Bool
case_sensitive then CompOption -> CompOption
forall a. a -> a
id else (CompOption
compIgnoreCase CompOption -> CompOption -> CompOption
forall a. Bits a => a -> a -> a
.|.)) (CompOption -> CompOption) -> CompOption -> CompOption
forall a b. (a -> b) -> a -> b
$
CompOption
compExtended
in CompOption -> ExecOption -> String -> Regex
forall regex compOpt execOpt source.
RegexMaker regex compOpt execOpt source =>
compOpt -> execOpt -> source -> regex
makeRegexOpts CompOption
opt ExecOption
forall regex compOpt execOpt.
RegexOptions regex compOpt execOpt =>
execOpt
defaultExecOpt String
s
matchRegex
:: Regex
-> String
-> Maybe [String]
matchRegex :: Regex -> String -> Maybe [String]
matchRegex Regex
p String
str = ((String, String, String, [String]) -> [String])
-> Maybe (String, String, String, [String]) -> Maybe [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(String
_,String
_,String
_,[String]
str) -> [String]
str) (Regex -> String -> Maybe (String, String, String, [String])
matchRegexAll Regex
p String
str)
matchRegexAll
:: Regex
-> String
-> Maybe ( String, String, String, [String] )
matchRegexAll :: Regex -> String -> Maybe (String, String, String, [String])
matchRegexAll Regex
p String
str = Regex -> String -> Maybe (String, String, String, [String])
forall regex source target (m :: * -> *).
(RegexContext regex source target, MonadFail m) =>
regex -> source -> m target
matchM Regex
p String
str
subRegex :: Regex
-> String
-> String
-> String
subRegex :: Regex -> String -> String -> String
subRegex Regex
_ String
"" String
_ = String
""
subRegex Regex
regexp String
inp String
repl =
let compile :: Int
-> String
-> [(String, (Int, Int))]
-> Array i (String, b)
-> String
-> String
compile Int
_i String
str [] = \ Array i (String, b)
_m -> (String
strString -> String -> String
forall a. [a] -> [a] -> [a]
++)
compile Int
i String
str ((String
"\\",(Int
off,Int
len)):[(String, (Int, Int))]
rest) =
let i' :: Int
i' = Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len
pre :: String
pre = Int -> String -> String
forall a. Int -> [a] -> [a]
take (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) String
str
str' :: String
str' = Int -> String -> String
forall a. Int -> [a] -> [a]
drop (Int
i'Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) String
str
in if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str' then \ Array i (String, b)
_m -> (String
pre String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
'\\'Char -> String -> String
forall a. a -> [a] -> [a]
:)
else \ Array i (String, b)
m -> (String
pre String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
:) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> String
-> [(String, (Int, Int))]
-> Array i (String, b)
-> String
-> String
compile Int
i' String
str' [(String, (Int, Int))]
rest Array i (String, b)
m
compile Int
i String
str ((String
xstr,(Int
off,Int
len)):[(String, (Int, Int))]
rest) =
let i' :: Int
i' = Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len
pre :: String
pre = Int -> String -> String
forall a. Int -> [a] -> [a]
take (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) String
str
str' :: String
str' = Int -> String -> String
forall a. Int -> [a] -> [a]
drop (Int
i'Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) String
str
x :: i
x = String -> i
forall a. Read a => String -> a
read String
xstr
in if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str' then \ Array i (String, b)
m -> (String
pre String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, b) -> String
forall a b. (a, b) -> a
fst (Array i (String, b)
m Array i (String, b) -> i -> (String, b)
forall i e. Ix i => Array i e -> i -> e
! i
x) String -> String -> String
forall a. [a] -> [a] -> [a]
++)
else \ Array i (String, b)
m -> (String
pre String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, b) -> String
forall a b. (a, b) -> a
fst (Array i (String, b)
m Array i (String, b) -> i -> (String, b)
forall i e. Ix i => Array i e -> i -> e
! i
x) String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> String
-> [(String, (Int, Int))]
-> Array i (String, b)
-> String
-> String
compile Int
i' String
str' [(String, (Int, Int))]
rest Array i (String, b)
m
compiled :: MatchText String -> String -> String
compiled :: MatchText String -> String -> String
compiled = Int
-> String
-> [(String, (Int, Int))]
-> MatchText String
-> String
-> String
forall i b.
(Ix i, Read i) =>
Int
-> String
-> [(String, (Int, Int))]
-> Array i (String, b)
-> String
-> String
compile Int
0 String
repl [(String, (Int, Int))]
findrefs where
bre :: Regex
bre = String -> Regex
mkRegex String
"\\\\(\\\\|[0-9]+)"
findrefs :: [(String, (Int, Int))]
findrefs = (MatchText String -> (String, (Int, Int)))
-> [MatchText String] -> [(String, (Int, Int))]
forall a b. (a -> b) -> [a] -> [b]
map (\MatchText String
m -> ((String, (Int, Int)) -> String
forall a b. (a, b) -> a
fst (MatchText String
m MatchText String -> Int -> (String, (Int, Int))
forall i e. Ix i => Array i e -> i -> e
! Int
1), (String, (Int, Int)) -> (Int, Int)
forall a b. (a, b) -> b
snd (MatchText String
m MatchText String -> Int -> (String, (Int, Int))
forall i e. Ix i => Array i e -> i -> e
! Int
0))) (Regex -> String -> [MatchText String]
forall regex source.
RegexLike regex source =>
regex -> source -> [MatchText source]
matchAllText Regex
bre String
repl)
go :: Int -> String -> [MatchText String] -> String
go Int
_i String
str [] = String
str
go Int
i String
str (MatchText String
m:[MatchText String]
ms) =
let (String
_, (Int
off, Int
len)) = MatchText String
m MatchText String -> Int -> (String, (Int, Int))
forall i e. Ix i => Array i e -> i -> e
! Int
0
i' :: Int
i' = Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len
pre :: String
pre = Int -> String -> String
forall a. Int -> [a] -> [a]
take (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) String
str
str' :: String
str' = Int -> String -> String
forall a. Int -> [a] -> [a]
drop (Int
i'Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) String
str
in if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str' then String
pre String -> String -> String
forall a. [a] -> [a] -> [a]
++ (MatchText String -> String -> String
compiled MatchText String
m String
"")
else String
pre String -> String -> String
forall a. [a] -> [a] -> [a]
++ (MatchText String -> String -> String
compiled MatchText String
m (Int -> String -> [MatchText String] -> String
go Int
i' String
str' [MatchText String]
ms))
in Int -> String -> [MatchText String] -> String
go Int
0 String
inp (Regex -> String -> [MatchText String]
forall regex source.
RegexLike regex source =>
regex -> source -> [MatchText source]
matchAllText Regex
regexp String
inp)
splitRegex :: Regex -> String -> [String]
splitRegex :: Regex -> String -> [String]
splitRegex Regex
_ [] = []
splitRegex Regex
delim String
strIn =
let matches :: [(Int, Int)]
matches = (Array Int (Int, Int) -> (Int, Int))
-> [Array Int (Int, Int)] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map (Array Int (Int, Int) -> Int -> (Int, Int)
forall i e. Ix i => Array i e -> i -> e
! Int
0) (Regex -> String -> [Array Int (Int, Int)]
forall regex source.
RegexLike regex source =>
regex -> source -> [Array Int (Int, Int)]
matchAll Regex
delim String
strIn)
go :: Int -> String -> [(Int, Int)] -> [String]
go Int
_i String
str [] = String
str String -> [String] -> [String]
forall a. a -> [a] -> [a]
: []
go Int
i String
str ((Int
off,Int
len):[(Int, Int)]
rest) =
let i' :: Int
i' = Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len
firstline :: String
firstline = Int -> String -> String
forall a. Int -> [a] -> [a]
take (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) String
str
remainder :: String
remainder = Int -> String -> String
forall a. Int -> [a] -> [a]
drop (Int
i'Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i) String
str
in Int -> [String] -> [String]
seq Int
i' ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$
if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
remainder then [String
firstline,String
""]
else String
firstline String -> [String] -> [String]
forall a. a -> [a] -> [a]
: Int -> String -> [(Int, Int)] -> [String]
go Int
i' String
remainder [(Int, Int)]
rest
in Int -> String -> [(Int, Int)] -> [String]
go Int
0 String
strIn [(Int, Int)]
matches