regex-tdfa-1.2.3.1: Replaces/Enhances Text.Regex

Safe HaskellNone
LanguageHaskell98

Text.Regex.TDFA

Description

The Text.Regex.TDFA module provides a backend for regular expressions. It provides instances for the classes defined and documented in Text.Regex.Base and re-exported by this module. If you import this along with other backends then you should do so with qualified imports (with renaming for convenience).

This regex-tdfa package implements, correctly, POSIX extended regular expressions. It is highly unlikely that the regex-posix package on your operating system is correct, see http://www.haskell.org/haskellwiki/Regex_Posix for examples of your OS's bugs.

This package does provide captured parenthesized subexpressions.

Depending on the text being searched this package supports Unicode. The [Char] and (Seq Char) text types support Unicode. The ByteString and ByteString.Lazy text types only support ASCII. It is possible to support utf8 encoded ByteString.Lazy by using regex-tdfa and regex-tdfa-utf8 packages together (required the utf8-string package).

As of version 1.1.1 the following GNU extensions are recognized, all anchors:

  • \` at beginning of entire text
  • \' at end of entire text
  • \< at beginning of word
  • \> at end of word
  • \b at either beginning or end of word
  • \B at neither beginning nor end of word

The above are controlled by the newSyntax Bool in CompOption.

Where the "word" boundaries means between characters that are and are not in the [:word:] character class which contains [a-zA-Z0-9_]. Note that \< and \b may match before the entire text and \> and \b may match at the end of the entire text.

There is no locale support, so collating elements like [.ch.] are simply ignored and equivalence classes like [=a=] are converted to just [a]. The character classes like [:alnum:] are supported over ASCII only, valid classes are alnum, digit, punct, alpha, graph, space, blank, lower, upper, cntrl, print, xdigit, word.

This package does not provide "basic" regular expressions. This package does not provide back references inside regular expressions.

The package does not provide Perl style regular expressions. Please look at the regex-pcre and pcre-light packages instead.

Synopsis

Documentation

(=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target Source #

This is the pure functional matching operator. If the target cannot be produced then some empty result will be returned. If there is an error in processing, then error will be called.

(=~~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target, Monad m) => source1 -> source -> m target Source #

This is the monadic matching operator. If a single match fails, then fail will be called.

data Regex Source #

The TDFA backend specific Regex type, used by this module's RegexOptions and RegexMaker

Instances
RegexLike Regex String Source # 
Instance details

Defined in Text.Regex.TDFA.String

RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.TDFA.ByteString.Lazy

RegexLike Regex ByteString Source # 
Instance details

Defined in Text.Regex.TDFA.ByteString

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

RegexContext Regex String String Source # 
Instance details

Defined in Text.Regex.TDFA.String

Methods

match :: Regex -> String -> String #

matchM :: Monad m => Regex -> String -> m String #

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.TDFA.ByteString.Lazy

RegexContext Regex ByteString ByteString Source # 
Instance details

Defined in Text.Regex.TDFA.ByteString

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.TDFA.String

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.TDFA.ByteString.Lazy

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.TDFA.ByteString

RegexMaker Regex CompOption ExecOption (Seq Char) Source # 
Instance details

Defined in Text.Regex.TDFA.Sequence

RegexLike Regex (Seq Char) Source # 
Instance details

Defined in Text.Regex.TDFA.Sequence

RegexContext Regex (Seq Char) (Seq Char) Source # 
Instance details

Defined in Text.Regex.TDFA.Sequence

Methods

match :: Regex -> Seq Char -> Seq Char #

matchM :: Monad m => Regex -> Seq Char -> m (Seq Char) #

data ExecOption Source #

Constructors

ExecOption 

Fields

Instances
Read ExecOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Show ExecOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.TDFA.String

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.TDFA.ByteString.Lazy

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.TDFA.ByteString

RegexMaker Regex CompOption ExecOption (Seq Char) Source # 
Instance details

Defined in Text.Regex.TDFA.Sequence

data CompOption Source #

Control whether the pattern is multiline or case-sensitive like Text.Regex and whether to capture the subgroups (\1, \2, etc). Controls enabling extra anchor syntax.

Constructors

CompOption 

Fields

  • caseSensitive :: Bool

    True in blankCompOpt and defaultCompOpt

  • multiline :: Bool

    False in blankCompOpt, True in defaultCompOpt. Compile for newline-sensitive matching. "By default, newline is a completely ordinary character with no special meaning in either REs or strings. With this flag, inverted bracket expressions and . never match newline, a ^ anchor matches the null string after any newline in the string in addition to its normal function, and the $ anchor matches the null string before any newline in the string in addition to its normal function."

  • rightAssoc :: Bool

    True (and therefore Right associative) in blankCompOpt and defaultCompOpt

  • newSyntax :: Bool

    False in blankCompOpt, True in defaultCompOpt. Add the extended non-POSIX syntax described in Text.Regex.TDFA haddock documentation.

  • lastStarGreedy :: Bool

    False by default. This is POSIX correct but it takes space and is slower. Setting this to true will improve performance, and should be done if you plan to set the captureGroups execoption to False.

Instances
Read CompOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

Show CompOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

RegexOptions Regex CompOption ExecOption Source # 
Instance details

Defined in Text.Regex.TDFA.Common

RegexMaker Regex CompOption ExecOption String Source # 
Instance details

Defined in Text.Regex.TDFA.String

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.TDFA.ByteString.Lazy

RegexMaker Regex CompOption ExecOption ByteString Source # 
Instance details

Defined in Text.Regex.TDFA.ByteString

RegexMaker Regex CompOption ExecOption (Seq Char) Source # 
Instance details

Defined in Text.Regex.TDFA.Sequence