[Haskell-beginners] wrapping text in a multiline string

Rico Moorman rico.moorman at gmail.com
Wed Jun 6 22:08:27 CEST 2012


Thank you for this important detail.

Following the advice in this thread I tried to rewrite the function in
terms of the lower-level interface instead of using =~~

-- qualified import to avoid clashes in main program
import qualified Text.Regex.PCRE as RE

regexReplace' :: String -> (String -> String) -> String -> String
regexReplace' regex replace text = go text
    where
        regex' :: RE.Regex
        regex' = RE.makeRegexOpts RE.defaultCompOpt RE.defaultExecOpt regex
        replace' :: RE.MatchText String -> String
        replace' = undefined
        go text = case RE.matchOnceText regex' text of
            Just (before, match, after) ->
                before ++ replace' match ++ go after
            _ -> text

Did you mean something like this? (besides that the replace' function
still has to be filled in)

If this is correct ... I am still a little lost though. I cannot come
up with a way of matching the actual String out of the MatchText
returned by matchOnceText ...
http://hackage.haskell.org/packages/archive/regex-base/latest/doc/html/Text-Regex-Base-RegexLike.html#v:matchOnceText

If I should structure the entire function differently, I would be very
grateful to receive some pointers how.

Best regards,

rico

On Wed, Jun 6, 2012 at 7:50 PM, Chaddaï Fouché <chaddai.fouche at gmail.com> wrote:
> On Wed, Jun 6, 2012 at 10:39 AM, Rico Moorman <rico.moorman at gmail.com> wrote:
>> Now I am wondering how I would integrate this in the replacement
>> function or how to rewrite it properly.
>>
>> Looking at the type signature of =~~ (with my limited knowledge) it
>> seems that I would have to "use" RegexMaker adding up the CompOptions
>> needed?
>>
>> (=~~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext
>> Regex source1 target, Monad m) => source1 -> source -> m target
>
> What's non-obvious and trip a lot of people when they try to use
> regexes in Haskell is that most regex libraries use the same
> interface, which is specified in the regex-base and consists of
> several typeclasses that offers a very high degree of flexibility.
> =~and =~~ are only the simplified front-ends to this and are pretty
> inadequate for advanced usages (for instance compile and use multiple
> time the same regex, you should really avoid =~ in this case, or
> additional regex compilation options). To see the basic interface,
> look at Text.Regex.Base.RegexLike :
> http://hackage.haskell.org/packages/archive/regex-base/latest/doc/html/Text-Regex-Base-RegexLike.html
> .
> In particular, what you want to do should be done with makeRegexOpts
> and match (or matchM), note that the available compilation and
> execution options can vary depending on the regex library you use and
> for regex-pcre, they're documented there :
> http://hackage.haskell.org/packages/archive/regex-pcre/latest/doc/html/Text-Regex-PCRE-Wrap.html#g:4
>
> --
> Jedaï



More information about the Beginners mailing list