[Haskell-cafe] Named captures in regex-pcre?

Roman Cheplyaka roma at ro-che.info
Sat Jan 28 23:53:54 CET 2012


* Ilya Portnov <portnov at iportnov.ru> [2012-01-29 01:26:29+0500]
> Hi haskell-cafe.
> 
> Is there a way to get named captures from regex using regex-pcre (or
> maybe other PCRE-package)? For example, I want to write something
> like
> 
> let result = "ab 12 cd" =~ "ab (?P<number>\d+) cd" :: SomeCrypticType
> 
> and then have namedCaptures result == [("number", "12")].
> 
> I do not see somewhat similar in regex-pcre documentation. It parses
> such regexs fine, and captures work, but i do not see way to get
> _named_ captures.

Try the regex-applicative package.

    {-# LANGUAGE OverloadedStrings #-}
    import Text.Regex.Applicative
    import Data.Char

    main = print $
        "ab 12 cd" =~ "ab " *> some (psym isDigit) <* " cd"

You can combine several captures into, say, a record using the
Applicative instance and thus emulate named captures semantics.

-- 
Roman I. Cheplyaka :: http://ro-che.info/



More information about the Haskell-Cafe mailing list