| Copyright | Copyright (c) 2007-2008 Don Stewart | 
|---|---|
| License | BSD3 | 
| Maintainer | Don Stewart <dons@galois.com> | 
| Stability | experimental | 
| Portability | H98 + CPP | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Text.Regex.PCRE.Light
Contents
Description
Synopsis
- data Regex
- compile :: ByteString -> [PCREOption] -> Regex
- compileM :: ByteString -> [PCREOption] -> Either String Regex
- match :: Regex -> ByteString -> [PCREExecOption] -> Maybe [ByteString]
- captureCount :: Regex -> Int
- captureNames :: Regex -> [(ByteString, Int)]
- data PCREOption
- anchored :: PCREOption
- auto_callout :: PCREOption
- caseless :: PCREOption
- dollar_endonly :: PCREOption
- dotall :: PCREOption
- dupnames :: PCREOption
- extended :: PCREOption
- extra :: PCREOption
- firstline :: PCREOption
- multiline :: PCREOption
- newline_cr :: PCREOption
- newline_crlf :: PCREOption
- newline_lf :: PCREOption
- no_auto_capture :: PCREOption
- ungreedy :: PCREOption
- utf8 :: PCREOption
- no_utf8_check :: PCREOption
- data PCREExecOption
- exec_anchored :: PCREExecOption
- exec_newline_cr :: PCREExecOption
- exec_newline_crlf :: PCREExecOption
- exec_newline_lf :: PCREExecOption
- exec_notbol :: PCREExecOption
- exec_noteol :: PCREExecOption
- exec_notempty :: PCREExecOption
- exec_no_utf8_check :: PCREExecOption
- exec_partial :: PCREExecOption
The abstract PCRE Regex type
An abstract pointer to a compiled PCRE Regex structure The structure allocated by the PCRE library will be deallocated automatically by the Haskell storage manager.
ByteString interface
compile :: ByteString -> [PCREOption] -> Regex Source #
Compile a perl-compatible regular expression stored in a strict bytestring.
An example
let r = compile (pack "^(b+|a){1,2}?bc") []Or using GHC's -XOverloadedStrings flag, and importing Data.ByteString.Char8, we can avoid the pack:
let r = compile "^(b+|a){1,2}?bc" []If the regular expression is invalid, an exception is thrown.
 If this is unsuitable, compileM is availlable, which returns failure
 in a monad.
To do case insentive matching,
compile "^(b+|a){1,2}?bc" [caseless]Other flags are documented below.
The resulting abstract regular expression can be passed to match
 for matching against a subject string.
The arguments are:
- pat: A ByteString containing the regular expression to be compiled.
- flags, optional bit flags. If- Nothingis provided, defaults are used.
Valid compile-time flags are:
- anchored- Force pattern anchoring
- auto_callout- Compile automatic callouts
- bsr_anycrlf- \R matches only CR, LF, or CRLF
- bsr_unicode- \R matches all Unicode line endings
- caseless- Do caseless matching
- dollar_endonly-- $not to match newline at end
- dotall- matches anything including NL
- dupnames- Allow duplicate names for subpatterns
- extended- Ignore whitespace and # comments
- extra- PCRE extra features (not much use currently)
- firstline- Force matching to be before newline
- multiline-- ^and- $match newlines within data
- newline_any- Recognize any Unicode newline sequence
- newline_anycrlf- Recognize CR, LF, and CRLF as newline sequences
- newline_cr- Set CR as the newline sequence
- newline_crlf- Set CRLF as the newline sequence
- newline_lf- Set LF as the newline sequence
- no_auto_capture- Disable numbered capturing parentheses (named ones available)
- ungreedy- Invert greediness of quantifiers
- utf8- Run in UTF-8 mode
- no_utf8_check- Do not check the pattern for UTF-8 validity
The regex is allocated via malloc on the C side, and will be deallocated by the runtime when the Haskell value representing it goes out of scope.
See 'man pcreapi for more details.
Caveats: patterns with embedded nulls, such as "0*" seem to be mishandled, as this won't currently match the subject "000".
compileM :: ByteString -> [PCREOption] -> Either String Regex Source #
match :: Regex -> ByteString -> [PCREExecOption] -> Maybe [ByteString] Source #
Matches a compiled regular expression against a given subject string,
 using a matching algorithm that is similar to Perl's. If the subject
 string doesn't match the regular expression, Nothing is returned,
 otherwise the portion of the string that matched is returned, along
 with any captured subpatterns.
The arguments are:
- regex, a PCRE regular expression value produced by compile
- subject, the subject string to match against
- options, an optional set of exec-time flags to exec.
Available runtime options are:
- exec_anchored- Match only at the first position
- exec_newline_any- Recognize any Unicode newline sequence
- exec_newline_anycrlf- Recognize CR, LF, and CRLF as newline sequences
- exec_newline_cr- Set CR as the newline sequence
- exec_newline_crlf- Set CRLF as the newline sequence
- exec_newline_lf- Set LF as the newline sequence
- exec_notbol- Subject is not the beginning of a line
- exec_noteol- Subject is not the end of a line
- exec_notempty- An empty string is not a valid match
- exec_no_utf8_check- Do not check the subject for UTF-8
- exec_partial- Return PCRE_ERROR_PARTIAL for a partial match
The result value, and any captured subpatterns, are returned. If the regex is invalid, or the subject string is empty, Nothing is returned.
captureCount :: Regex -> Int Source #
Returns the number of captures in a Regex. Correctly ignores non-capturing groups
 like (?:abc).
>>>captureCount (compile "(?<one>abc) (def) (?:non-captured) (?<three>ghi)" [])3
captureNames :: Regex -> [(ByteString, Int)] Source #
Returns the names and numbers of all named subpatterns in the regular expression. Groups are zero-indexed. Unnamed groups are counted, but don't appear in the result list.
>>>captureNames (compile "(?<one>abc) (def) (?<three>ghi)")[("one", 0), ("three", 2)]
Regex types and constructors externally visible
PCRE compile-time bit flags
data PCREOption Source #
A type for PCRE compile-time options. These are newtyped CInts, which can be bitwise-or'd together, using '(Data.Bits..|.)'
Instances
| Eq PCREOption Source # | |
| Defined in Text.Regex.PCRE.Light.Base | |
| Ord PCREOption Source # | |
| Defined in Text.Regex.PCRE.Light.Base Methods compare :: PCREOption -> PCREOption -> Ordering # (<) :: PCREOption -> PCREOption -> Bool # (<=) :: PCREOption -> PCREOption -> Bool # (>) :: PCREOption -> PCREOption -> Bool # (>=) :: PCREOption -> PCREOption -> Bool # max :: PCREOption -> PCREOption -> PCREOption # min :: PCREOption -> PCREOption -> PCREOption # | |
| Read PCREOption Source # | |
| Defined in Text.Regex.PCRE.Light.Base Methods readsPrec :: Int -> ReadS PCREOption # readList :: ReadS [PCREOption] # readPrec :: ReadPrec PCREOption # readListPrec :: ReadPrec [PCREOption] # | |
| Show PCREOption Source # | |
| Defined in Text.Regex.PCRE.Light.Base Methods showsPrec :: Int -> PCREOption -> ShowS # show :: PCREOption -> String # showList :: [PCREOption] -> ShowS # | |
anchored :: PCREOption Source #
If this bit is set, the pattern is forced to be anchored, that is, it is constrained to match only at the first matching point in the string that is being searched (the subject string). This effect can also be achieved by appropriate constructs in the pattern itself, which is the only way to do it in Perl.
auto_callout :: PCREOption Source #
If this bit is set, "compile" automatically inserts callout items, all with number 255, before each pattern item. For discussion of the callout facility, see the man pcrecallout documentation
caseless :: PCREOption Source #
bsr_anycrlf and bsr_unicode
These options (which are mutually exclusive) control what the \R escape sequence matches. The choice is either to match only CR, LF, or CRLF, or to match any Unicode new- line sequence. The default is specified when PCRE is built. It can be overridden from within the pattern, or by setting an option when a compiled pattern is matched.
bsr_anycrlf :: PCREOption bsr_anycrlf = PCREOption bsr_anycrlf_cint
bsr_unicode. See bse_anycrlf
bsr_unicode :: PCREOption bsr_unicode = PCREOption bsr_unicode_cint
If this bit is set, letters in the pattern match both upper and lower case letters. It is equivalent to Perl's /i option, and it can be changed within a pattern by a (?i) option setting. In UTF-8 mode, PCRE always understands the concept of case for characters whose values are less than 128, so caseless matching is always possible. For characters with higher values, the concept of case is supported if PCRE is compiled with Unicode property sup- port, but not otherwise. If you want to use caseless matching for characters 128 and above, you must ensure that PCRE is compiled with Unicode property support as well as with UTF-8 support.
dollar_endonly :: PCREOption Source #
If this bit is set, a dollar metacharacter in the pattern matches only at
 the end of the subject string. Without this option, a dollar also matches
 immediately before a newline at the end of the string (but not before any other
 newlines). The dollar_endonly option is ignored if multiline
 is set.  There is no equivalent to this option in Perl, and no way to set it
 within a pattern.
dotall :: PCREOption Source #
If this bit is set, a dot metacharater in the pattern matches all characters, including those that indicate newline. Without it, a dot does not match when the current position is at a newline. This option is equivalent to Perl's /s option, and it can be changed within a pattern by a (?s) option setting. A negative class such as [^a] always matches newline characters, independent of the setting of this option.
dupnames :: PCREOption Source #
If this bit is set, names used to identify capturing subpatterns need not be unique. This can be helpful for certain types of pattern when it is known that only one instance of the named subpattern can ever be matched. There are more details of named subpatterns in the man pcreapi documentation.
extended :: PCREOption Source #
If this bit is set, whitespace data characters in the pattern are totally ignored except when escaped or inside a character class. Whitespace does not include the VT character (code 11). In addition, characters between an unescaped # outside a character class and the next newline, inclusive, are also ignored. This is equivalent to Perl's /x option, and it can be changed within a pattern by a (?x) option setting.
This option makes it possible to include comments inside complicated patterns. Note, however, that this applies only to data characters. Whitespace characters may never appear within special character sequences in a pattern, for example within the sequence (?( which introduces a conditional subpattern.
extra :: PCREOption Source #
This option was invented in order to turn on additional functionality of PCRE that is incompatible with Perl, but it is currently of very little use. When set, any backslash in a pattern that is followed by a letter that has no special meaning causes an error, thus reserving these combinations for future expansion. By default, as in Perl, a backslash followed by a letter with no special meaning is treated as a literal. (Perl can, however, be persuaded to give a warning for this.) There are at present no other features controlled by this option. It can also be set by a (?X) option setting within a pattern.
firstline :: PCREOption Source #
If this option is set, an unanchored pattern is required to match before or at the first newline in the subject string, though the matched text may continue over the newline.
multiline :: PCREOption Source #
By default, PCRE treats the subject string as consisting of a single line
 of characters (even if it actually contains newlines). The start of line
 metacharacter (^) matches only at the start of the string, while the end of line
  metacharacter ($) matches only at the end of the string, or before a
 terminating newline (unless dollar_endonly is set). This is the same
 as Perl.
When multiline it is set, the start of line and end of line
 constructs match immediately following or immediately before internal newlines
 in the subject string, respectively, as well as at the very start and end. This
 is equivalent to Perl's /m option, and it can be changed within a pattern by a
 (?m) option setting. If there are no newlines in a subject string, or no occur-
 rences of ^ or $ in a pattern, setting PCRE_MULTILINE has no effect.
newline_cr :: PCREOption Source #
newline_cr', newline_lf, newline_crlf,
 newline_anycrlf, newline_any
These options override the default newline definition that
 was chosen when PCRE was built. Setting the first or the
 second specifies that a newline is indicated by a single
 character (CR or LF, respectively). Setting newline_crlf specifies
 that a newline is indicated by the two-character CRLF sequence.
 Setting newline_anycrlf
 specifies that any of the three preceding sequences should
 be recognized. Setting newline_any specifies that any
 Unicode newline sequence should be recognized. The Unicode
 newline sequences are the three just mentioned, plus the
 single characters VT (vertical tab, U+000B), FF (formfeed,
 U+000C), NEL (next line, U+0085), LS (line separator,
 U+2028), and PS (paragraph separator, U+2029). The last
 two are recognized only in UTF-8 mode.
The newline setting in the options word uses three bits
 that are treated as a number, giving eight possibilities.
 Currently only six are used (default plus the five values
 above). This means that if you set more than one newline
 option, the combination may or may not be sensible. For
 example, newline_cr with newline_lf is equivalent to
 newline_crlf, but other combinations may yield unused numbers and
 cause an error.
The only time that a line break is specially recognized
 when compiling a pattern is if extended is set, and
 an unescaped # outside a character class is encountered.
 This indicates a comment that lasts until after the next
 line break sequence. In other circumstances, line break
 sequences are treated as literal data, except that in
 extended mode, both CR and LF are treated as whitespace characters
 and are therefore ignored.  -- 
The newline option that is set at compile time becomes the
 default that is used for exec but it can be overridden.
newline_any :: PCREOption newline_any = PCREOption newline_any_cint
newline_anycrlf, see newline_any
 newline_anycrlf    :: PCREOption
 newline_anycrlf    = PCREOption newline_anycrlf_cint
newline_cr, see newline_any
newline_crlf :: PCREOption Source #
newline_crlf, see newline_any
newline_lf :: PCREOption Source #
newline_lf, see newline_any
no_auto_capture :: PCREOption Source #
If this option is set, it disables the use of numbered capturing parentheses in the pattern. Any opening paren- thesis that is not followed by ? behaves as if it were followed by ?: but named parentheses can still be used for capturing (and they acquire numbers in the usual way). There is no equivalent of this option in Perl.
ungreedy :: PCREOption Source #
This option inverts the greediness of the quantifiers so that they are not greedy by default, but become greedy if followed by ?. It is not compatible with Perl. It can also be set by a (?U) option setting within the pattern.
utf8 :: PCREOption Source #
This option causes PCRE to regard both the pattern and the subject as strings of UTF-8 characters instead of single-byte character strings. However, it is available only when PCRE is built to include UTF-8 support. If not, the use of this option provokes an error. Details of how this option changes the behaviour of PCRE are given in the section on UTF-8 support in the main pcre page.
no_utf8_check :: PCREOption Source #
When PCRE_UTF8 is set, the validity of the pattern as a
 UTF-8 string is automatically checked. There is a discussion 
 about the validity of UTF-8 strings in the main pcre
 page. If an invalid UTF-8 sequence of bytes is found,
 compile() returns an error. If you already know that
 your pattern is valid, and you want to skip this check for
 performance reasons, you can set the no_utf8_check
 option. When it is set, the effect of passing an invalid
 UTF-8 string as a pattern is undefined. It may cause your
 program to crash. Note that this option can also be passed
 to exec, to suppress the UTF-8 validity checking of subject strings.
PCRE exec-time bit flags
data PCREExecOption Source #
Instances
| Eq PCREExecOption Source # | |
| Defined in Text.Regex.PCRE.Light.Base Methods (==) :: PCREExecOption -> PCREExecOption -> Bool # (/=) :: PCREExecOption -> PCREExecOption -> Bool # | |
| Ord PCREExecOption Source # | |
| Defined in Text.Regex.PCRE.Light.Base Methods compare :: PCREExecOption -> PCREExecOption -> Ordering # (<) :: PCREExecOption -> PCREExecOption -> Bool # (<=) :: PCREExecOption -> PCREExecOption -> Bool # (>) :: PCREExecOption -> PCREExecOption -> Bool # (>=) :: PCREExecOption -> PCREExecOption -> Bool # max :: PCREExecOption -> PCREExecOption -> PCREExecOption # min :: PCREExecOption -> PCREExecOption -> PCREExecOption # | |
| Read PCREExecOption Source # | |
| Defined in Text.Regex.PCRE.Light.Base Methods readsPrec :: Int -> ReadS PCREExecOption # readList :: ReadS [PCREExecOption] # | |
| Show PCREExecOption Source # | |
| Defined in Text.Regex.PCRE.Light.Base Methods showsPrec :: Int -> PCREExecOption -> ShowS # show :: PCREExecOption -> String # showList :: [PCREExecOption] -> ShowS # | |
exec_newline_cr :: PCREExecOption Source #
newline_cr, newline_lf,
 newline_crlf, newline_anycrlf, newline_any
These options override the newline definition that was
 chosen or defaulted when the pattern was compiled. For
 details, see the description of compile above. Dur-
 ing matching, the newline choice affects the behaviour of
 the dot, circumflex, and dollar metacharacters. It may
 also alter the way the match position is advanced after a
 match failure for an unanchored pattern.
When newline_crlf, newline_anycrlf, or newline_any
 is set, and a match attempt for an unanchored
 pattern fails when the current position is at a CRLF
 sequence, and the pattern contains no explicit matches for
 CR or LF characters, the match position is advanced by two
 characters instead of one, in other words, to after the
 CRLF.
The above rule is a compromise that makes the most common
 cases work as expected. For example, if the pattern is .+A
 (and the dotall option is not set), it does not match
 the string \r\nA because, after failing at the start, it
 skips both the CR and the LF before retrying. However, the
 pattern [\r\n]A does match that string, because it contains
 an explicit CR or LF reference, and so advances only
 by one character after the first failure.
An explicit match for CR of LF is either a literal appear- ance of one of those characters, or one of the \r or \n escape sequences. Implicit matches such as [^X] do not count, nor does \s (which includes CR and LF in the char- acters that it matches).
Notwithstanding the above, anomalous effects may still occur when CRLF is a valid newline sequence and explicit \r or \n escapes appear in the pattern.
exec_newline_any :: PCREExecOption exec_newline_any = PCREExecOption exec_newline_any_cint
exec_newline_anycrlf, see exec_newline_any
 exec_newline_anycrlf       :: PCREExecOption
 exec_newline_anycrlf       = PCREExecOption exec_newline_anycrlf_cint
exec_newline_cr, see exec_newline_any
exec_newline_crlf :: PCREExecOption Source #
exec_newline_crlf, see exec_newline_any
exec_newline_lf :: PCREExecOption Source #
exec_newline_lf, see exec_newline_any
exec_notbol :: PCREExecOption Source #
PCRE_NOTBOL
This option specifies that first character of the subject
 string is not the beginning of a line, so the circumflex
 metacharacter should not match before it. Setting this
 without multiline (at compile time) causes circumflex
 never to match. This option affects only the behaviour of
 the circumflex metacharacter. It does not affect \A.
exec_noteol :: PCREExecOption Source #
noteol
This option specifies that the end of the subject string
 is not the end of a line, so the dollar metacharacter
 should not match it nor (except in multiline mode) a newline
 immediately before it. Setting this without multiline 
 (at compile time) causes dollar never to match.
 This option affects only the behaviour of the dollar
 metacharacter. It does not affect \Z or \z.
exec_notempty :: PCREExecOption Source #
PCRE_NOTEMPTY
An empty string is not considered to be a valid match if this option is set. If there are alternatives in the pattern, they are tried. If all the alternatives match the empty string, the entire match fails. For example, if the pattern
a?b?
is applied to a string not beginning with a or b, it
 matches the empty string at the start of the subject. With
 notempty set, this match is not valid, so 'PCRE
 searches further into the string for occurrences of a or
 b.
Perl has no direct equivalent of notempty, but it
 does make a special case of a pattern match of the empty
 string within its split() function, and when using the /g
 modifier. It is possible to emulate Perl's behaviour after
 matching a null string by first trying the match again at
 the same offset with PCRE_NOTEMPTY and PCRE_ANCHORED, and
 then if that fails by advancing the starting offset (see
 below) and trying an ordinary match again. There is some
 code that demonstrates how to do this in the pcredemo.c
 sample program.
exec_no_utf8_check :: PCREExecOption Source #
When utf8 is set at compile time, the validity of the
 subject as a UTF-8 string is automatically checked when
 exec() is subsequently called. The value of
 startoffset is also checked to ensure that it points to
 the start of a UTF-8 character. There is a discussion
 about the validity of UTF-8 strings in the section on
 UTF-8 support in the main pcre page. If an invalid UTF-8
 sequence of bytes is found, exec() returns the error
 error_badutf8. If startoffset contains an invalid
 value, error_badutf8_offset is returned.
If you already know that your subject is valid, and you
 want to skip these checks for performance reasons, you can
 set the no_utf8_check option when calling
 exec. You might want to do this for the second and
 subsequent calls to exec() if you are making repeated
 calls to find all the matches in a single subject string.
 However, you should be sure that the value of startoffset
 points to the start of a UTF-8 character. When
 no_utf8_check is set, the effect of passing an
 invalid UTF-8 string as a subject, or a value of startoff-
 set that does not point to the start of a UTF-8 character,
 is undefined. Your program may crash.
exec_partial :: PCREExecOption Source #
partial
This option turns on the partial matching feature. If the
 subject string fails to match the pattern, but at some
 point during the matching process the end of the subject
 was reached (that is, the subject partially matches the
 pattern and the failure to match occurred only because
 there were not enough subject characters), exec
 returns error_partial instead of error_nomatch.
 When partial is used, there are restrictions on what
 may appear in the pattern. These are discussed in the
 pcrepartial documentation.