regex-compat-0.95.2.1/0000755000000000000000000000000007346545000012532 5ustar0000000000000000regex-compat-0.95.2.1/ChangeLog.md0000644000000000000000000000044107346545000014702 0ustar0000000000000000See also http://pvp.haskell.org/faq ## 0.95.2.1 - Allow `base-4.15` (GHC 9.0) - Workaround for `{-# LANGUAGE Haskell2010 #-}` parser regression introduced in GHC 9.0 - Optimization flag `-O2` has been removed ## 0.95.2.0 - Declare `Text.Regex` module `Trustworthy` under SafeHaskell regex-compat-0.95.2.1/LICENSE0000644000000000000000000000274407346545000013546 0ustar0000000000000000This modile is under this "3 clause" BSD license: Copyright (c) 2007, Christopher Kuklewicz All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * The names of the contributors may not be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. regex-compat-0.95.2.1/Setup.hs0000644000000000000000000000005607346545000014167 0ustar0000000000000000import Distribution.Simple main = defaultMain regex-compat-0.95.2.1/Text/0000755000000000000000000000000007346545000013456 5ustar0000000000000000regex-compat-0.95.2.1/Text/Regex.hs0000644000000000000000000001673407346545000015077 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-name-shadowing #-} ----------------------------------------------------------------------------- -- | -- Module : Text.Regex -- Copyright : (c) Chris Kuklewicz 2006, derived from (c) The University of Glasgow 2001 -- License : BSD-style (see the file LICENSE) -- -- Maintainer : hvr@gnu.org -- Stability : experimental -- Portability : non-portable (regex-base needs MPTC+FD) -- -- Regular expression matching. Uses the POSIX regular expression -- interface in "Text.Regex.Posix". -- --------------------------------------------------------------------------- -- -- Modified by Chris Kuklewicz to be a thin layer over the regex-posix -- package, and moved into a regex-compat package. -- module Text.Regex ( -- * Regular expressions 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) -- | Makes a regular expression with the default options (multi-line, -- case-sensitive). The syntax of regular expressions is -- otherwise that of @egrep@ (i.e. POSIX \"extended\" regular -- expressions). mkRegex :: String -> Regex mkRegex s = makeRegexOpts opt defaultExecOpt s where opt = compExtended .|. compNewline -- | Makes a regular expression, where the multi-line and -- case-sensitive options can be changed from the default settings. mkRegexWithOpts :: String -- ^ The regular expression to compile. -> Bool -- ^ 'True' iff @\'^\'@ and @\'$\'@ match the beginning and -- end of individual lines respectively, and @\'.\'@ does /not/ -- match the newline character. -> Bool -- ^ 'True' iff matching is case-sensitive. -> Regex -- ^ Returns: the compiled regular expression. mkRegexWithOpts s single_line case_sensitive = let opt = (if single_line then (compNewline .|.) else id) . (if case_sensitive then id else (compIgnoreCase .|.)) $ compExtended in makeRegexOpts opt defaultExecOpt s -- | Match a regular expression against a string. matchRegex :: Regex -- ^ The regular expression. -> String -- ^ The string to match against. -> Maybe [String] -- ^ Returns: @'Just' strs@ if the match succeeded -- (and @strs@ is the list of subexpression matches), -- or 'Nothing' otherwise. matchRegex p str = fmap (\(_,_,_,str) -> str) (matchRegexAll p str) -- | Match a regular expression against a string, returning more information -- about the match. matchRegexAll :: Regex -- ^ The regular expression. -> String -- ^ The string to match against. -> Maybe ( String, String, String, [String] ) -- ^ Returns: 'Nothing' if the match failed, or: -- -- > Just ( everything before match, -- > portion matched, -- > everything after the match, -- > subexpression matches ) matchRegexAll p str = matchM p str {- | Replaces every occurrence of the given regexp with the replacement string. In the replacement string, @\"\\1\"@ refers to the first substring; @\"\\2\"@ to the second, etc; and @\"\\0\"@ to the entire match. @\"\\\\\\\\\"@ will insert a literal backslash. This does not advance if the regex matches an empty string. This misfeature is here to match the behavior of the original @Text.Regex@ API. -} subRegex :: Regex -- ^ Search pattern -> String -- ^ Input string -> String -- ^ Replacement text -> String -- ^ Output string subRegex _ "" _ = "" subRegex regexp inp repl = 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 regexp inp) {- | Splits a string based on a regular expression. The regular expression should identify one delimiter. This does not advance and produces an infinite list of @[]@ if the regex matches an empty string. This misfeature is here to match the behavior of the original @Text.Regex@ API. -} splitRegex :: Regex -> String -> [String] splitRegex _ [] = [] splitRegex delim strIn = let matches = map (! 0) (matchAll delim strIn) go _i str [] = str : [] go i str ((off,len):rest) = let i' = off+len firstline = take (off-i) str remainder = drop (i'-i) str in seq i' $ if null remainder then [firstline,""] else firstline : go i' remainder rest in go 0 strIn matches {- -- These are the older versions which failed on (correct answer:) -- let r = mkRegex "^(.)" in subRegex2 r "abc\ndef" "|\\1" -- "|abc\n|def" subRegex :: Regex -- ^ Search pattern -> String -- ^ Input string -> String -- ^ Replacement text -> String -- ^ Output string subRegex _ "" _ = "" subRegex regexp inp repl = let -- bre matches a backslash then capture either a backslash or some digits bre = mkRegex "\\\\(\\\\|[0-9]+)" lookup _ [] _ = [] lookup [] _ _ = [] lookup match repl groups = case matchRegexAll bre repl of Nothing -> repl Just (lead, _, trail, bgroups) -> let newval = if (head bgroups) == "\\" then "\\" else let index :: Int index = (read (head bgroups)) - 1 in if index == -1 then match else groups !! index in lead ++ newval ++ lookup match trail groups in case matchRegexAll regexp inp of Nothing -> inp Just (lead, match, trail, groups) -> lead ++ lookup match repl groups ++ (subRegex regexp trail repl) splitRegex :: Regex -> String -> [String] splitRegex _ [] = [] splitRegex delim strIn = loop strIn where loop str = case matchOnceText delim str of Nothing -> [str] Just (firstline, _, remainder) -> if null remainder then [firstline,""] else firstline : loop remainder -} regex-compat-0.95.2.1/regex-compat.cabal0000644000000000000000000000327607346545000016121 0ustar0000000000000000cabal-version: 1.12 name: regex-compat version: 0.95.2.1 build-type: Simple license: BSD3 license-file: LICENSE copyright: Copyright (c) 2006, Christopher Kuklewicz author: Christopher Kuklewicz maintainer: Herbert Valerio Riedel , Andreas Abel homepage: https://wiki.haskell.org/Regular_expressions bug-reports: https://github.com/hvr/regex-compat/issues synopsis: Replaces/enhances "Text.Regex" category: Text description: One module compat layer over to replace "Text.Regex". . See also for more information. extra-source-files: ChangeLog.md tested-with: -- Haskell CI: GHC == 7.0.4 GHC == 7.2.2 GHC == 7.4.2 GHC == 7.6.3 GHC == 7.8.4 GHC == 7.10.3 GHC == 8.0.2 GHC == 8.2.2 GHC == 8.4.4 GHC == 8.6.5 GHC == 8.8.4 GHC == 8.10.3 -- manually (AA, 2021-02-17): -- GHC == 8.10.4 -- GHC == 9.0.1 source-repository head type: git location: https://github.com/hvr/regex-compat.git source-repository this type: git location: https://github.com/hvr/regex-compat.git tag: v0.95.2.1 library exposed-modules: Text.Regex build-depends: base >= 4.3 && < 4.16 , regex-base == 0.94.* , regex-posix == 0.96.* , array >= 0.3 && < 0.6 default-language: Haskell2010 default-extensions: MultiParamTypeClasses, FunctionalDependencies if impl(ghc >= 7.2) default-extensions: Trustworthy ghc-options: -Wall