Safe Haskell | None |
---|---|
Language | Haskell2010 |
Text.Regex.PCRE
Description
The Text.Regex.PCRE 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.
Using the provided CompOption
and ExecOption
values and if
configUTF8
is True, then you might be able to send UTF8 encoded
ByteStrings to PCRE and get sensible results. This is currently
untested.
The regular expression can be provided as a ByteString
, but it will
be copied and a NUL byte appended to make a CString
unless such a
byte is already present. Thus the regular expression cannot contain
an explicit NUL byte. The search string is passed as a CStringLen
and may contain NUL bytes and does not need to end in a NUL
byte. ByteString
s are searched in place (via unsafeUseAsCStringLen).
A String
will be converted into a CString
or CStringLen
for
processing. Doing this repeatedly will be very inefficient.
The Text.Regex.PCRE.String, Text.Regex.PCRE.ByteString, and Text.Regex.PCRE.Wrap modules provides both the high level interface exported by this module and medium- and low-level interfaces that returns error using Either structures.
Synopsis
- getVersion_Text_Regex_PCRE :: 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
- unusedOffset :: MatchOffset
- getNumSubs :: Regex -> Int
- configUTF8 :: Bool
- getVersion :: Maybe String
- compBlank :: CompOption
- compAnchored :: CompOption
- compAutoCallout :: CompOption
- compCaseless :: CompOption
- compDollarEndOnly :: CompOption
- compDotAll :: CompOption
- compExtended :: CompOption
- compExtra :: CompOption
- compFirstLine :: CompOption
- compMultiline :: CompOption
- compNoAutoCapture :: CompOption
- compUngreedy :: CompOption
- compUTF8 :: CompOption
- compNoUTF8Check :: CompOption
- execBlank :: ExecOption
- execAnchored :: ExecOption
- execNotBOL :: ExecOption
- execNotEOL :: ExecOption
- execNotEmpty :: ExecOption
- execNoUTF8Check :: ExecOption
- execPartial :: ExecOption
Documentation
getVersion_Text_Regex_PCRE :: 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.PCRE.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.PCRE.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.PCRE.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.PCRE.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.PCRE.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 #
Constructors
CompOption CInt |
Instances
newtype ExecOption Source #
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 #
getNumSubs :: Regex -> Int Source #
configUTF8 :: Bool Source #
getVersion :: Maybe String Source #
Version string of PCRE library
NOTE: The Maybe
type is used for historic reasons; practically, getVersion
is never Nothing
.