
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. WBR, Ilya Portnov.

On Sat, Jan 28, 2012 at 15:26, Ilya Portnov
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
regex-pcre is constrained by the common Haskell regex API (used by all the regex-* packages), which doesn't support named captures. Unfortunately, it doesn't look like pcre-light will return the kind of capture alist you want either; it uses the basic pcre_exec() function and doesn't appear to provide an API for pcre_get_named_substring() etc. dons doesn't seem to be very active any more (sandbagged by job?), so pcre-light (which looks to be the obvious place for it given that Text.Regex.PCRE.Base already provides a partial raw API) is likely open to adoption; you could add the named capture API to T.R.P.Base and possibly develop a more Haskell-like API later. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

* Ilya Portnov
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/
participants (3)
-
Brandon Allbery
-
Ilya Portnov
-
Roman Cheplyaka