Regexp substitution in fptools?

John Goerzen jgoerzen at complete.org
Wed Dec 8 14:15:32 EST 2004


Hi,

I have the following code in my MissingH tree.  I think it would make a
good addition to Text.Regex in fptools.  Is this the right place to ask?

-- John

{- | Replaces every occurance 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.

-}
subRe :: Regex                          -- ^ Search pattern
      -> String                         -- ^ Input string
      -> String                         -- ^ Replacement text
      -> String                         -- ^ Output string
subRe _ "" _ = ""
subRe regexp inp repl =
    let 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 = (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 ++ (subRe regexp trail repl)

{- | Splits a string based on a regular expression.  The regular expression
should identify one delimiter.
-}

splitRe :: Regex -> String -> [String]
splitRe _ [] = []
splitRe delim str =
    case matchRegexAll delim str of
       Nothing -> [str]
       Just (firstline, _, remainder, _) ->
           if remainder == ""
              then firstline : [] : []
              else firstline : splitRe delim remainder




More information about the Libraries mailing list