| Copyright | (c) Chris Kuklewicz 2006 |
|---|---|
| License | BSD-3-Clause |
| Maintainer | Andreas Abel |
| Stability | stable |
| Portability | non-portable (regex-base needs MPTC+FD) |
| Safe Haskell | None |
| Language | Haskell2010 |
Text.Regex.Posix
Description
Module that provides the Regex backend that wraps the C POSIX.2 regex api. This is the backend being used by the regex-compat package to replace Text.Regex.
The Text.Regex.Posix module provides a backend for regular expressions. If you import this along with other backends, then you should do so with qualified imports, perhaps renamed for convenience.
If the =~ and =~~ functions are too high level, you can use the
compile, regexec, and execute functions from importing either
Text.Regex.Posix.String or Text.Regex.Posix.ByteString. If you
want to use a low-level CString interface to the library,
then import Text.Regex.Posix.Wrap and use the wrap* functions.
This module is only efficient with ByteString only
if it is null terminated, i.e. (Bytestring.last bs)==0. Otherwise the
library must make a temporary copy of the ByteString
and append the NUL byte.
A String will be converted into a CString for processing.
Doing this repeatedly will be very inefficient.
Note that the posix library works with single byte characters, and does not understand Unicode. If you need Unicode support you will have to use a different backend.
When offsets are reported for subexpression captures, a subexpression
that did not match anything (as opposed to matching an empty string)
will have its offset set to the unusedRegOffset value, which is (-1).
Benchmarking shows the default regex library on many platforms is very
inefficient. You might increase performace by an order of magnitude
by obtaining libpcre and regex-pcre
or libtre and regex-tre. If you
do not need the captured substrings then you can also get great
performance from regex-dfa. If you do need the capture substrings
then you may be able to use regex-parsec to improve performance.
Synopsis
- getVersion_Text_Regex_Posix :: Version
- class Extract source where
- class Extract source => RegexLike regex source where
- matchOnce :: regex -> source -> Maybe MatchArray
- matchAll :: regex -> source -> [MatchArray]
- matchCount :: regex -> source -> Int
- matchTest :: regex -> source -> Bool
- matchAllText :: regex -> source -> [MatchText source]
- matchOnceText :: regex -> source -> Maybe (source, MatchText source, source)
- class RegexOptions regex compOpt execOpt | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt where
- blankCompOpt :: compOpt
- blankExecOpt :: execOpt
- defaultCompOpt :: compOpt
- defaultExecOpt :: execOpt
- setExecOpts :: execOpt -> regex -> regex
- getExecOpts :: regex -> execOpt
- class RegexOptions regex compOpt execOpt => RegexMaker regex compOpt execOpt source | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt where
- makeRegex :: source -> regex
- makeRegexOpts :: compOpt -> execOpt -> source -> regex
- makeRegexM :: MonadFail m => source -> m regex
- makeRegexOptsM :: MonadFail m => compOpt -> execOpt -> source -> m regex
- class RegexLike regex source => RegexContext regex source target where
- type MatchArray = Array Int (MatchOffset, MatchLength)
- type MatchOffset = Int
- type MatchLength = Int
- newtype AllMatches (f :: Type -> Type) b = AllMatches {
- getAllMatches :: f b
- newtype AllSubmatches (f :: Type -> Type) b = AllSubmatches {
- getAllSubmatches :: f b
- newtype AllTextMatches (f :: Type -> Type) b = AllTextMatches {
- getAllTextMatches :: f b
- newtype AllTextSubmatches (f :: Type -> Type) b = AllTextSubmatches {
- getAllTextSubmatches :: f b
- data MatchResult a = MR {}
- type MatchText source = Array Int (source, (MatchOffset, MatchLength))
- getVersion_Text_Regex_Base :: Version
- data Regex
- newtype CompOption = CompOption CInt
- newtype ExecOption = ExecOption CInt
- (=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target
- (=~~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target, MonadFail m) => source1 -> source -> m target
- unusedRegOffset :: RegOffset
- compBlank :: CompOption
- compExtended :: CompOption
- compIgnoreCase :: CompOption
- compNoSub :: CompOption
- compNewline :: CompOption
- execBlank :: ExecOption
- execNotBOL :: ExecOption
- execNotEOL :: ExecOption
Documentation
getVersion_Text_Regex_Posix :: Version Source #
class Extract source => RegexLike regex source where #
Minimal complete definition
Nothing
Methods
matchOnce :: regex -> source -> Maybe MatchArray #
matchAll :: regex -> source -> [MatchArray] #
matchCount :: regex -> source -> Int #
matchTest :: regex -> source -> Bool #
matchAllText :: regex -> source -> [MatchText source] #
matchOnceText :: regex -> source -> Maybe (source, MatchText source, source) #
Instances
| RegexLike Regex ByteString Source # | |
Defined in Text.Regex.Posix.ByteString Methods matchOnce :: Regex -> ByteString -> Maybe MatchArray # matchAll :: Regex -> ByteString -> [MatchArray] # matchCount :: Regex -> ByteString -> Int # matchTest :: Regex -> ByteString -> Bool # matchAllText :: Regex -> ByteString -> [MatchText ByteString] # matchOnceText :: Regex -> ByteString -> Maybe (ByteString, MatchText ByteString, ByteString) # | |
| RegexLike Regex ByteString Source # | |
Defined in Text.Regex.Posix.ByteString.Lazy Methods matchOnce :: Regex -> ByteString -> Maybe MatchArray # matchAll :: Regex -> ByteString -> [MatchArray] # matchCount :: Regex -> ByteString -> Int # matchTest :: Regex -> ByteString -> Bool # matchAllText :: Regex -> ByteString -> [MatchText ByteString] # matchOnceText :: Regex -> ByteString -> Maybe (ByteString, MatchText ByteString, ByteString) # | |
| RegexLike Regex String Source # | |
Defined in Text.Regex.Posix.String Methods matchOnce :: Regex -> String -> Maybe MatchArray # matchAll :: Regex -> String -> [MatchArray] # matchCount :: Regex -> String -> Int # matchTest :: Regex -> String -> Bool # matchAllText :: Regex -> String -> [MatchText String] # matchOnceText :: Regex -> String -> Maybe (String, MatchText String, String) # | |
| RegexLike Regex (Seq Char) Source # | |
Defined in Text.Regex.Posix.Sequence Methods matchOnce :: Regex -> Seq Char -> Maybe MatchArray # matchAll :: Regex -> Seq Char -> [MatchArray] # matchCount :: Regex -> Seq Char -> Int # matchTest :: Regex -> Seq Char -> Bool # matchAllText :: Regex -> Seq Char -> [MatchText (Seq Char)] # matchOnceText :: Regex -> Seq Char -> Maybe (Seq Char, MatchText (Seq Char), Seq Char) # | |
class RegexOptions regex compOpt execOpt | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt where #
Methods
blankCompOpt :: compOpt #
blankExecOpt :: execOpt #
defaultCompOpt :: compOpt #
defaultExecOpt :: execOpt #
setExecOpts :: execOpt -> regex -> regex #
getExecOpts :: regex -> execOpt #
Instances
| RegexOptions Regex CompOption ExecOption Source # | |
Defined in Text.Regex.Posix.Wrap Methods defaultCompOpt :: CompOption # defaultExecOpt :: ExecOption # setExecOpts :: ExecOption -> Regex -> Regex # getExecOpts :: Regex -> ExecOption # | |
class RegexOptions regex compOpt execOpt => RegexMaker regex compOpt execOpt source | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt where #
Minimal complete definition
Nothing
Methods
makeRegex :: source -> regex #
makeRegexOpts :: compOpt -> execOpt -> source -> regex #
makeRegexM :: MonadFail m => source -> m regex #
makeRegexOptsM :: MonadFail m => compOpt -> execOpt -> source -> m regex #
Instances
class RegexLike regex source => RegexContext regex source target where #
Instances
| RegexContext Regex ByteString ByteString Source # | |
| RegexContext Regex ByteString ByteString Source # | |
| RegexContext Regex String String Source # | |
| RegexContext Regex (Seq Char) (Seq Char) Source # | |
type MatchArray = Array Int (MatchOffset, MatchLength) #
type MatchOffset = Int #
type MatchLength = Int #
newtype AllMatches (f :: Type -> Type) b #
Constructors
| AllMatches | |
Fields
| |
newtype AllSubmatches (f :: Type -> Type) b #
Constructors
| AllSubmatches | |
Fields
| |
newtype AllTextMatches (f :: Type -> Type) b #
Constructors
| AllTextMatches | |
Fields
| |
newtype AllTextSubmatches (f :: Type -> Type) b #
Constructors
| AllTextSubmatches | |
Fields
| |
data MatchResult a #
type MatchText source = Array Int (source, (MatchOffset, MatchLength)) #
getVersion_Text_Regex_Base :: Version #
Wrap, for =~ and =~~, types and constants
A compiled regular expression.
Instances
newtype CompOption Source #
A bitmapped CInt containing options for compilation of regular
expressions. Option values (and their man 3 regcomp names) are
compBlankwhich is a completely zero value for all the flags. This is also theblankCompOptvalue.compExtended(REG_EXTENDED) which can be set to use extended instead of basic regular expressions. This is set in thedefaultCompOptvalue.compNewline(REG_NEWLINE) turns on newline sensitivity: The dot (.) and inverted set[^ ]never match newline, and ^ and $ anchors do match after and before newlines. This is set in thedefaultCompOptvalue.compIgnoreCase(REG_ICASE) which can be set to match ignoring upper and lower distinctions.compNoSub(REG_NOSUB) which turns off all information from matching except whether a match exists.
Constructors
| CompOption CInt |
Instances
newtype ExecOption Source #
A bitmapped CInt containing options for execution of compiled
regular expressions. Option values (and their man 3 regexec names) are
execBlankwhich is a complete zero value for all the flags. This is theblankExecOptvalue.execNotBOL(REG_NOTBOL) can be set to prevent ^ from matching at the start of the input.execNotEOL(REG_NOTEOL) can be set to prevent $ from matching at the end of the input (before the terminating NUL).
Constructors
| ExecOption CInt |
Instances
(=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target Source #
(=~~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target, MonadFail m) => source1 -> source -> m target Source #
compBlank :: CompOption Source #
A completely zero value for all the flags.
This is also the blankCompOpt value.
execBlank :: ExecOption Source #
A completely zero value for all the flags.
This is also the blankExecOpt value.