Skip to content
Snippets Groups Projects
Commit 5a8d7926 authored by Francesco Gazzetta's avatar Francesco Gazzetta
Browse files

Include fixed subRegex from regex-compat-tdfa

Upstream looks unmaintained, and we only use a single function anyway.
The package did not build with ghc 9, so we include a fixed version of
that function.
parent 3f496852
No related branches found
No related tags found
No related merge requests found
......@@ -67,8 +67,9 @@ library
, filepath ^>= 1.3.0.1 || ^>= 1.4.0.0
, optparse-applicative ^>= 0.14.3.0 || ^>=0.15.1.0 || ^>=0.16.0.0
, process ^>= 1.1.0.2 || ^>= 1.2.0.0 || ^>= 1.4.2.0 || ^>= 1.6.1.0
, regex-compat-tdfa ^>= 0.95.1.4
, regex-base ^>= 0.94.0.1
, regex-tdfa ^>= 1.2.3.1 || ^>=1.3.1.0
, array ^>= 0.4.0.1 || ^>= 0.5.0.0
, temporary ^>= 1.3
, text ^>= 1.2.3.1
, transformers ^>= 0.3.0.0 || ^>= 0.4.2.0 || ^>= 0.5.2.0
......
......@@ -11,9 +11,11 @@ import Distribution.Pretty
import Distribution.Package
import Distribution.System
import qualified Data.Foldable as F
import Text.Regex.Base
import Text.Regex.TDFA
import Data.Array ((!))
import Text.Regex
import qualified Data.Foldable as F
normalizeOutput :: NormalizerEnv -> String -> String
normalizeOutput nenv =
......@@ -80,6 +82,41 @@ posixSpecialChars = ".^$*+?()[{\\|"
posixRegexEscape :: String -> String
posixRegexEscape = concatMap (\c -> if c `elem` posixSpecialChars then ['\\', c] else [c])
-- From regex-compat-tdfa by Christopher Kuklewicz and shelarcy, BSD-3-Clause
-------------------------
resub :: String {- search -} -> String {- replace -} -> String {- input -} -> String
resub search replace s =
subRegex (mkRegex search) s replace
resub _ _ "" = ""
resub regexp repl inp =
let compile _i str [] = \ _m -> (str ++)
compile i str (("\\", (off, len)) : rest) =
let i' = off + len
pre = take (off - i) str
str' = drop (i' - i) str
in if null str' then \ _m -> (pre ++) . ('\\' :)
else \ m -> (pre ++) . ('\\' :) . compile i' str' rest m
compile i str ((xstr, (off, len)) : rest) =
let i' = off + len
pre = take (off - i) str
str' = drop (i' - i) str
x = read xstr
in if null str' then \ m -> (pre++) . (fst (m ! x) ++)
else \ m -> (pre ++) . (fst (m ! x) ++) . compile i' str' rest m
compiled :: MatchText String -> String -> String
compiled = compile 0 repl findrefs where
-- bre matches a backslash then capture either a backslash or some digits
bre = mkRegex "\\\\(\\\\|[0-9]+)"
findrefs = map (\m -> (fst (m ! 1), snd (m ! 0))) (matchAllText bre repl)
go _i str [] = str
go i str (m : ms) =
let (_, (off, len)) = m ! 0
i' = off + len
pre = take (off - i) str
str' = drop (i' - i) str
in if null str' then pre ++ compiled m ""
else pre ++ compiled m (go i' str' ms)
in go 0 inp (matchAllText (mkRegex regexp) inp)
mkRegex :: String -> Regex
mkRegex s = makeRegexOpts opt defaultExecOpt s
where opt = defaultCompOpt { newSyntax = True, multiline = True }
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment