regex-base-0.72.0.2: Replaces/Enhances Text.RegexSource codeContentsIndex
Text.Regex.Base.RegexLike
Portabilitynon-portable (MPTC+FD)
Stabilityexperimental
Maintainerlibraries@haskell.org, textregexlazy@personal.mightyreason.com
Contents
Type aliases
Data types
Classes
Description

Classes and instances for Regex matching.

All the classes are declared here, and some common type aliases, and the MatchResult data type.

The only instances here are for Extract String and Extract ByteString. There are no data values. The RegexContext instances are in Text.Regex.Base.Context, except for ones which run afoul of a repeated variable (RegexContext regex a a), which are defined in each modules' String and ByteString modules.

Synopsis
type MatchOffset = Int
type MatchLength = Int
type MatchArray = Array Int (MatchOffset, MatchLength)
type MatchText source = Array Int (source, (MatchOffset, MatchLength))
data MatchResult a = MR {
mrBefore :: a
mrMatch :: a
mrAfter :: a
mrSubList :: [a]
mrSubs :: Array Int a
}
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
class Extract source => RegexLike regex source where
matchAll :: regex -> source -> [MatchArray]
matchOnce :: regex -> source -> Maybe MatchArray
matchCount :: regex -> source -> Int
matchTest :: regex -> source -> Bool
matchAllText :: regex -> source -> [MatchText source]
matchOnceText :: regex -> source -> Maybe (source, MatchText source, source)
class RegexLike regex source => RegexContext regex source target where
match :: regex -> source -> target
matchM :: Monad m => regex -> source -> m target
class Extract source where
before :: Int -> source -> source
after :: Int -> source -> source
empty :: source
extract :: (Int, Int) -> source -> source
Type aliases
type MatchOffset = IntSource
0 based index from start of source, or (-1) for unused
type MatchLength = IntSource
non-negative length of a match
type MatchArray = Array Int (MatchOffset, MatchLength)Source
0 based array, with 0th index indicating the full match. If the full match location is not available, represent as (0,0).
type MatchText source = Array Int (source, (MatchOffset, MatchLength))Source
Data types
data MatchResult a Source
This is the same as the type from JRegex.
Constructors
MR
mrBefore :: a
mrMatch :: a
mrAfter :: a
mrSubList :: [a]
mrSubs :: Array Int a
show/hide Instances
Classes
class RegexOptions regex compOpt execOpt | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt whereSource
Rather than carry them around spearately, the options for how to execute a regex are kept as part of the regex. There are two types of options. Those that can only be specified at compilation time and never changed are CompOpt. Those that can be changed later and affect how matching is performed are ExecOpt. The actually types for these depend on the backend.
Methods
blankCompOptSource
:: compOptno options set at all in the backend
blankExecOptSource
:: execOptno options set at all in the backend
defaultCompOptSource
:: compOptreasonable options (extended,caseSensitive,multiline regex)
defaultExecOptSource
:: execOptreasonable options (extended,caseSensitive,multiline regex)
setExecOpts :: execOpt -> regex -> regexSource
forget old flags and use new ones
getExecOpts :: regex -> execOptSource
retrieve the current flags
class RegexOptions regex compOpt execOpt => RegexMaker regex compOpt execOpt source | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt whereSource
RegexMaker captures the creation of the compiled regular expression from a source type and an option type. The makeRegex function has a default implementation that depends on makeRegexOpts and used defaultCompOpt and defaultExecOpt.
Methods
makeRegex :: source -> regexSource
make using the defaultCompOpt and defaultExecOpt
makeRegexOpts :: compOpt -> execOpt -> source -> regexSource
Specify your own options
class Extract source => RegexLike regex source whereSource

RegexLike is parametrized on a regular expression type and a source type to run the matching on.

There are default implementations: matchTest and matchOnceText using matchOnce; matchCount and matchAllText using matchAll. matchOnce uses matchOnceText and matchAll uses matchAllText. So a minimal complete instance need to provide (matchOnce or matchOnceText) and (matchAll or matchAllText).

Methods
matchAll :: regex -> source -> [MatchArray]Source
matchOnce :: regex -> source -> Maybe MatchArraySource
This can return an array of (offset,length) index pairs for the match and captured substrings.
matchCount :: regex -> source -> IntSource
matchTest :: regex -> source -> BoolSource
matchAllText :: regex -> source -> [MatchText source]Source
matchOnceText :: regex -> source -> Maybe (source, MatchText source, source)Source
This can return a tuple of three items: the source before the match, an array of the match and captured substrings (with their indices), and the source after the match.
class RegexLike regex source => RegexContext regex source target whereSource
RegexContext is the polymorphic interface to do matching
Methods
match :: regex -> source -> targetSource
matchM :: Monad m => regex -> source -> m targetSource
show/hide Instances
class Extract source whereSource
Extract allows for indexing operations on String or ByteString.
Methods
before :: Int -> source -> sourceSource
before is a renamed take
after :: Int -> source -> sourceSource
after is a renamed drop
empty :: sourceSource
For when there is no match, this can construct an empty data value
extract :: (Int, Int) -> source -> sourceSource
extract takes an offset and length and has a default implementation of extract (off,len) source = before len (after off source)
show/hide Instances
Produced by Haddock version 2.4.2