regex-base-0.94.0.0: Common "Text.Regex.*" API for Regex matching

Copyright(c) Chris Kuklewicz 2006
LicenseBSD-3-Clause
Maintainerhvr@gnu.org
Stabilityexperimental
Portabilitynon-portable (MPTC+FD)
Safe HaskellSafe
LanguageHaskell2010

Text.Regex.Base.RegexLike

Contents

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, Extract ByteString, and Extract Text. 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 aliases

type MatchOffset = Int Source #

0 based index from start of source, or (-1) for unused

type MatchLength = Int Source #

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 

Fields

Instances
RegexLike a b => RegexContext a b (MatchResult b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> MatchResult b Source #

matchM :: MonadFail m => a -> b -> m (MatchResult b) Source #

Classes

class RegexOptions regex compOpt execOpt | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt where Source #

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

blankCompOpt Source #

Arguments

:: compOpt

no options set at all in the backend

blankExecOpt Source #

Arguments

:: execOpt

no options set at all in the backend

defaultCompOpt Source #

Arguments

:: compOpt

reasonable options (extended,caseSensitive,multiline regex)

defaultExecOpt Source #

Arguments

:: execOpt

reasonable options (extended,caseSensitive,multiline regex)

setExecOpts :: execOpt -> regex -> regex Source #

forget old flags and use new ones

getExecOpts :: regex -> execOpt Source #

retrieve the current flags

class RegexOptions regex compOpt execOpt => RegexMaker regex compOpt execOpt source | regex -> compOpt execOpt, compOpt -> regex execOpt, execOpt -> regex compOpt where Source #

RegexMaker captures the creation of the compiled regular expression from a source type and an option type. makeRegexM and makeRegexM report parse error using MonadError, usually (Either String regex).

The makeRegex function has a default implementation that depends on makeRegexOpts and used defaultCompOpt and defaultExecOpt. Similarly for makeRegexM and makeRegexOptsM.

There are also default implementaions for makeRegexOpts and makeRegexOptsM in terms of each other. So a minimal instance definition needs to only define one of these, hopefully makeRegexOptsM.

Minimal complete definition

Nothing

Methods

makeRegex :: source -> regex Source #

make using the defaultCompOpt and defaultExecOpt

makeRegexOpts :: compOpt -> execOpt -> source -> regex Source #

Specify your own options

makeRegexM :: MonadFail m => source -> m regex Source #

make using the defaultCompOpt and defaultExecOpt, reporting errors with fail

makeRegexOptsM :: MonadFail m => compOpt -> execOpt -> source -> m regex Source #

Specify your own options, reporting errors with fail

class Extract source => RegexLike regex source where Source #

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

There are default implementations: matchTest and matchOnceText use matchOnce; matchCount and matchAllText use matchAll. matchOnce uses matchOnceText and matchAll uses matchAllText. So a minimal complete instance need to provide at least (matchOnce or matchOnceText) and (matchAll or matchAllText). Additional definitions are often provided where they will increase efficiency.

[ c | let notVowel = makeRegex "[^aeiou]" :: Regex, c <- ['a'..'z'], matchTest notVowel [c]  ]

"bcdfghjklmnpqrstvwxyz"

The strictness of these functions is instance dependent.

Minimal complete definition

Nothing

Methods

matchOnce :: regex -> source -> Maybe MatchArray Source #

This returns the first match in the source (it checks the whole source, not just at the start). This returns an array of (offset,length) index pairs for the match and captured substrings. The offset is 0-based. A (-1) for an offset means a failure to match. The lower bound of the array is 0, and the 0th element is the (offset,length) for the whole match.

matchAll :: regex -> source -> [MatchArray] Source #

matchAll returns a list of matches. The matches are in order and do not overlap. If any match succeeds but has 0 length then this will be the last match in the list.

matchCount :: regex -> source -> Int Source #

matchCount returns the number of non-overlapping matches returned by matchAll.

matchTest :: regex -> source -> Bool Source #

matchTest return True if there is a match somewhere in the source (it checks the whole source not just at the start).

matchAllText :: regex -> source -> [MatchText source] Source #

This is matchAll with the actual subsections of the source instead of just the (offset,length) information.

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 where Source #

RegexContext is the polymorphic interface to do matching. Since target is polymorphic you may need to suply the type explicitly in contexts where it cannot be inferred.

The monadic matchM version uses fail to report when the regex has no match in source. Two examples:

Here the contest Bool is inferred:

[ c | let notVowel = makeRegex "[^aeiou]" :: Regex, c <- ['a'..'z'], match notVowel [c]  ]

"bcdfghjklmnpqrstvwxyz"

Here the context '[String]' must be supplied:

let notVowel = (makeRegex "[^aeiou]" :: Regex )
in do { c <- ['a'..'z'] ; matchM notVowel [c] } :: [String]

["b","c","d","f","g","h","j","k","l","m","n","p","q","r","s","t","v","w","x","y","z"]

Methods

match :: regex -> source -> target Source #

matchM :: MonadFail m => regex -> source -> m target Source #

Instances
RegexLike a b => RegexContext a b MatchArray Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> MatchArray Source #

matchM :: MonadFail m => a -> b -> m MatchArray Source #

RegexLike a b => RegexContext a b Int Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> Int Source #

matchM :: MonadFail m => a -> b -> m Int Source #

RegexLike a b => RegexContext a b () Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> () Source #

matchM :: MonadFail m => a -> b -> m () Source #

RegexLike a b => RegexContext a b Bool Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> Bool Source #

matchM :: MonadFail m => a -> b -> m Bool Source #

RegexLike a b => RegexContext a b [[b]] Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> [[b]] Source #

matchM :: MonadFail m => a -> b -> m [[b]] Source #

RegexLike a b => RegexContext a b [MatchText b] Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> [MatchText b] Source #

matchM :: MonadFail m => a -> b -> m [MatchText b] Source #

RegexLike a b => RegexContext a b [MatchArray] Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> [MatchArray] Source #

matchM :: MonadFail m => a -> b -> m [MatchArray] Source #

RegexLike a b => RegexContext a b (MatchResult b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> MatchResult b Source #

matchM :: MonadFail m => a -> b -> m (MatchResult b) Source #

RegexLike a b => RegexContext a b (AllTextMatches (Array Int) (Array Int b)) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches (Array Int) (Array Int b) Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches (Array Int) (Array Int b)) Source #

RegexLike a b => RegexContext a b (AllTextMatches [] (Array Int b)) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches [] (Array Int b) Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches [] (Array Int b)) Source #

RegexLike a b => RegexContext a b (AllTextMatches (Array Int) [b]) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches (Array Int) [b] Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches (Array Int) [b]) Source #

RegexLike a b => RegexContext a b (AllTextMatches (Array Int) b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches (Array Int) b Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches (Array Int) b) Source #

RegexLike a b => RegexContext a b (AllTextMatches [] b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches [] b Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches [] b) Source #

RegexLike a b => RegexContext a b (AllTextMatches (Array Int) (MatchText b)) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches (Array Int) (MatchText b) Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches (Array Int) (MatchText b)) Source #

RegexLike a b => RegexContext a b (AllMatches (Array Int) MatchArray) Source # 
Instance details

Defined in Text.Regex.Base.Context

RegexLike a b => RegexContext a b (AllMatches (Array Int) (MatchOffset, MatchLength)) Source # 
Instance details

Defined in Text.Regex.Base.Context

RegexLike a b => RegexContext a b (AllMatches [] (MatchOffset, MatchLength)) Source # 
Instance details

Defined in Text.Regex.Base.Context

RegexLike a b => RegexContext a b (AllTextSubmatches (Array Int) b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextSubmatches (Array Int) b Source #

matchM :: MonadFail m => a -> b -> m (AllTextSubmatches (Array Int) b) Source #

RegexLike a b => RegexContext a b (AllTextSubmatches [] b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextSubmatches [] b Source #

matchM :: MonadFail m => a -> b -> m (AllTextSubmatches [] b) Source #

RegexLike a b => RegexContext a b (AllTextSubmatches [] (b, (MatchOffset, MatchLength))) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextSubmatches [] (b, (MatchOffset, MatchLength)) Source #

matchM :: MonadFail m => a -> b -> m (AllTextSubmatches [] (b, (MatchOffset, MatchLength))) Source #

RegexLike a b => RegexContext a b (AllTextSubmatches (Array Int) (b, (MatchOffset, MatchLength))) Source # 
Instance details

Defined in Text.Regex.Base.Context

RegexLike a b => RegexContext a b (AllSubmatches [] (MatchOffset, MatchLength)) Source # 
Instance details

Defined in Text.Regex.Base.Context

RegexLike a b => RegexContext a b (MatchOffset, MatchLength) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> (MatchOffset, MatchLength) Source #

matchM :: MonadFail m => a -> b -> m (MatchOffset, MatchLength) Source #

RegexLike a b => RegexContext a b (b, b, b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> (b, b, b) Source #

matchM :: MonadFail m => a -> b -> m (b, b, b) Source #

RegexLike a b => RegexContext a b (b, MatchText b, b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> (b, MatchText b, b) Source #

matchM :: MonadFail m => a -> b -> m (b, MatchText b, b) Source #

RegexLike a b => RegexContext a b (b, b, b, [b]) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> (b, b, b, [b]) Source #

matchM :: MonadFail m => a -> b -> m (b, b, b, [b]) Source #

class Extract source where Source #

Extract allows for indexing operations on String or ByteString.

Minimal complete definition

before, after, empty

Methods

before :: Int -> source -> source Source #

before is a renamed "take"

after :: Int -> source -> source Source #

after is a renamed "drop"

empty :: source Source #

For when there is no match, this can construct an empty data value

extract :: (Int, Int) -> source -> source Source #

extract takes an offset and length and has a default implementation of extract (off,len) source = before len (after off source)

Instances
Extract String Source # 
Instance details

Defined in Text.Regex.Base.RegexLike

Extract ByteString Source # 
Instance details

Defined in Text.Regex.Base.RegexLike

Extract ByteString Source # 
Instance details

Defined in Text.Regex.Base.RegexLike

Extract Text Source #

Since: 0.94.0.0

Instance details

Defined in Text.Regex.Base.RegexLike

Extract Text Source #

Since: 0.94.0.0

Instance details

Defined in Text.Regex.Base.RegexLike

Extract (Seq a) Source # 
Instance details

Defined in Text.Regex.Base.RegexLike

Methods

before :: Int -> Seq a -> Seq a Source #

after :: Int -> Seq a -> Seq a Source #

empty :: Seq a Source #

extract :: (Int, Int) -> Seq a -> Seq a Source #

newtype AllSubmatches f b Source #

Used in results of RegexContext instances

Constructors

AllSubmatches 

Fields

Instances
RegexLike a b => RegexContext a b (AllSubmatches [] (MatchOffset, MatchLength)) Source # 
Instance details

Defined in Text.Regex.Base.Context

newtype AllTextSubmatches f b Source #

Used in results of RegexContext instances

Constructors

AllTextSubmatches 

Fields

Instances
RegexLike a b => RegexContext a b (AllTextSubmatches (Array Int) b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextSubmatches (Array Int) b Source #

matchM :: MonadFail m => a -> b -> m (AllTextSubmatches (Array Int) b) Source #

RegexLike a b => RegexContext a b (AllTextSubmatches [] b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextSubmatches [] b Source #

matchM :: MonadFail m => a -> b -> m (AllTextSubmatches [] b) Source #

RegexLike a b => RegexContext a b (AllTextSubmatches [] (b, (MatchOffset, MatchLength))) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextSubmatches [] (b, (MatchOffset, MatchLength)) Source #

matchM :: MonadFail m => a -> b -> m (AllTextSubmatches [] (b, (MatchOffset, MatchLength))) Source #

RegexLike a b => RegexContext a b (AllTextSubmatches (Array Int) (b, (MatchOffset, MatchLength))) Source # 
Instance details

Defined in Text.Regex.Base.Context

newtype AllMatches f b Source #

Used in results of RegexContext instances

Constructors

AllMatches 

Fields

newtype AllTextMatches f b Source #

Used in results of RegexContext instances

Constructors

AllTextMatches 

Fields

Instances
RegexLike a b => RegexContext a b (AllTextMatches (Array Int) (Array Int b)) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches (Array Int) (Array Int b) Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches (Array Int) (Array Int b)) Source #

RegexLike a b => RegexContext a b (AllTextMatches [] (Array Int b)) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches [] (Array Int b) Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches [] (Array Int b)) Source #

RegexLike a b => RegexContext a b (AllTextMatches (Array Int) [b]) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches (Array Int) [b] Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches (Array Int) [b]) Source #

RegexLike a b => RegexContext a b (AllTextMatches (Array Int) b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches (Array Int) b Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches (Array Int) b) Source #

RegexLike a b => RegexContext a b (AllTextMatches [] b) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches [] b Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches [] b) Source #

RegexLike a b => RegexContext a b (AllTextMatches (Array Int) (MatchText b)) Source # 
Instance details

Defined in Text.Regex.Base.Context

Methods

match :: a -> b -> AllTextMatches (Array Int) (MatchText b) Source #

matchM :: MonadFail m => a -> b -> m (AllTextMatches (Array Int) (MatchText b)) Source #