regex-0.2.0.2: Toolkit for regex-base

Copyright(C) 2016-17 Chris Dornan
LicenseBSD3 (see the LICENSE file)
MaintainerChris Dornan <chris.dornan@irisconnect.com>
StabilityRFC
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.RE

Contents

Description

 

Synopsis

Tutorial

We have a regex tutorial at http://tutorial.regex.uk. These API docs are mainly for reference.

How to use this library

This module won't provide any operators to match a regular expression against text as it merely provides the toolkit for working with the output of the match operators. You probably won't import it directly but import one of the modules that provides the match operators, which will in tuen re-export this module.

The module that you choose to import will depend upon two factors:

  • Which flavour of regular expression do you want to use? If you want Posix flavour REs then you want the TDFA modules, otherwise its PCRE for Perl-style REs.
  • What type of text do you want to match: (slow) Strings, ByteString, ByteString.Lazy, Text, Text.Lazy or the anachronistic Seq Char or indeed a good old-fashioned polymorphic operators?

While we aim to provide all combinations of these choices, some of them are currently not available. We have:

The Match Operators

The traditional =~ and =~~ operators are exported by the regex, but we recommend that you use the two new operators, especially if you are not familiar with the old operators. We have:

  • txt ?=~ re searches for a single match yielding a value of type Match a where a is the type of the text you are searching.
  • txt *=~ re searches for all non-overlapping matches in txt, returning a value of type Matches a.

See the sections below for more information on these Matches and Match result types.

Matches, Match, Capture Types and Functions

data Matches a Source #

the result type to use when every match is needed, not just the first match of the RE against the source

Constructors

Matches 

Fields

Instances

Functor Matches Source # 

Methods

fmap :: (a -> b) -> Matches a -> Matches b #

(<$) :: a -> Matches b -> Matches a #

(RegexContext regex source [MatchText source], RegexLike regex source) => RegexContext regex source (Matches source) Source #

for matching all REs against the source text

Methods

match :: regex -> source -> Matches source #

matchM :: Monad m => regex -> source -> m (Matches source) #

Eq a => Eq (Matches a) Source # 

Methods

(==) :: Matches a -> Matches a -> Bool #

(/=) :: Matches a -> Matches a -> Bool #

Show a => Show (Matches a) Source # 

Methods

showsPrec :: Int -> Matches a -> ShowS #

show :: Matches a -> String #

showList :: [Matches a] -> ShowS #

data Match a Source #

the result of matching a RE to a text once, listing the text that was matched and the named captures in the RE and all of the substrings matched, with the text captured by the whole RE; a complete failure to match will be represented with an empty array (with bounds (0,-1))

Constructors

Match 

Fields

Instances

Functor Match Source # 

Methods

fmap :: (a -> b) -> Match a -> Match b #

(<$) :: a -> Match b -> Match a #

(RegexContext regex source (AllTextSubmatches (Array Int) (source, (Int, Int))), RegexLike regex source) => RegexContext regex source (Match source) Source #

for matching just the first RE against the source text

Methods

match :: regex -> source -> Match source #

matchM :: Monad m => regex -> source -> m (Match source) #

Eq a => Eq (Match a) Source # 

Methods

(==) :: Match a -> Match a -> Bool #

(/=) :: Match a -> Match a -> Bool #

Show a => Show (Match a) Source # 

Methods

showsPrec :: Int -> Match a -> ShowS #

show :: Match a -> String #

showList :: [Match a] -> ShowS #

data Capture a Source #

the matching of a single sub-expression against part of the source text

Constructors

Capture 

Fields

  • captureSource :: !a

    the whole text that was searched

  • capturedText :: !a

    the text that was matched

  • captureOffset :: !Int

    the number of characters preceding the match with -1 used if no text was captured by the RE (not even the empty string)

  • captureLength :: !Int

    the number of chacter in the captured sub-string

Instances

Functor Capture Source # 

Methods

fmap :: (a -> b) -> Capture a -> Capture b #

(<$) :: a -> Capture b -> Capture a #

Eq a => Eq (Capture a) Source # 

Methods

(==) :: Capture a -> Capture a -> Bool #

(/=) :: Capture a -> Capture a -> Bool #

Show a => Show (Capture a) Source # 

Methods

showsPrec :: Int -> Capture a -> ShowS #

show :: Capture a -> String #

showList :: [Capture a] -> ShowS #

noMatch :: a -> Match a Source #

Construct a Match that does not match anything.

Matches functions

anyMatches :: Matches a -> Bool Source #

tests whether the RE matched the source text at all

countMatches :: Matches a -> Int Source #

count the matches

matches :: Matches a -> [a] Source #

mainCaptures :: Matches a -> [Capture a] Source #

extract the main capture from each match

Match functions

matched :: Match a -> Bool Source #

tests whether the RE matched the source text at all

matchedText :: Match a -> Maybe a Source #

tests whether the RE matched the source text at all

matchCapture :: Match a -> Maybe (Capture a) Source #

the top-level capture if the source text matched the RE, Nothing otherwise

matchCaptures :: Match a -> Maybe (Capture a, [Capture a]) Source #

the top-level capture and the sub captures if the text matched the RE, Nothing otherwise

(!$$) :: Match a -> CaptureID -> a infixl 9 Source #

an alternative for captureText

captureText :: CaptureID -> Match a -> a Source #

look up the text of the nth capture, 0 being the match of the whole RE against the source text, 1, the first bracketed sub-expression to be matched and so on

(!$$?) :: Match a -> CaptureID -> Maybe a Source #

an alternative for captureTextMaybe

captureTextMaybe :: CaptureID -> Match a -> Maybe a Source #

look up the text of the nth capture (0 being the match of the whole), returning Nothing if the Match doesn't contain the capture

(!$) :: Match a -> CaptureID -> Capture a infixl 9 Source #

an alternative for capture

capture :: CaptureID -> Match a -> Capture a Source #

look up the nth capture, 0 being the match of the whole RE against the source text, 1, the first bracketed sub-expression to be matched and so on

(!$?) :: Match a -> CaptureID -> Maybe (Capture a) Source #

an alternative for capture captureMaybe

captureMaybe :: CaptureID -> Match a -> Maybe (Capture a) Source #

look up the nth capture, 0 being the match of the whole RE against the source text, 1, the first bracketed sub-expression to be matched and so on, returning Nothing if there is no such capture, or if the capture failed to capture anything (being in a failed alternate)

Capture functions

hasCaptured :: Capture a -> Bool Source #

test if the capture has matched any text

capturePrefix :: Extract a => Capture a -> a Source #

returns the text preceding the match

captureSuffix :: Extract a => Capture a -> a Source #

returns the text after the match

IsRegex

class Replace s => IsRegex re s where Source #

Minimal complete definition

matchOnce, matchMany, regexSource

Methods

matchOnce :: re -> s -> Match s Source #

matchMany :: re -> s -> Matches s Source #

regexSource :: re -> String Source #

Options

data Mode Source #

Constructors

Simple 
Block 

Instances

Bounded Mode Source # 
Enum Mode Source # 

Methods

succ :: Mode -> Mode #

pred :: Mode -> Mode #

toEnum :: Int -> Mode #

fromEnum :: Mode -> Int #

enumFrom :: Mode -> [Mode] #

enumFromThen :: Mode -> Mode -> [Mode] #

enumFromTo :: Mode -> Mode -> [Mode] #

enumFromThenTo :: Mode -> Mode -> Mode -> [Mode] #

Eq Mode Source # 

Methods

(==) :: Mode -> Mode -> Bool #

(/=) :: Mode -> Mode -> Bool #

Ord Mode Source # 

Methods

compare :: Mode -> Mode -> Ordering #

(<) :: Mode -> Mode -> Bool #

(<=) :: Mode -> Mode -> Bool #

(>) :: Mode -> Mode -> Bool #

(>=) :: Mode -> Mode -> Bool #

max :: Mode -> Mode -> Mode #

min :: Mode -> Mode -> Mode #

Show Mode Source # 

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

data SimpleRegexOptions Source #

Instances

Bounded SimpleRegexOptions Source # 
Enum SimpleRegexOptions Source # 
Eq SimpleRegexOptions Source # 
Ord SimpleRegexOptions Source # 
Show SimpleRegexOptions Source # 
Lift SimpleRegexOptions Source # 

CaptureID

newtype CaptureOrdinal Source #

Constructors

CaptureOrdinal 

Instances

Enum CaptureOrdinal Source # 
Eq CaptureOrdinal Source # 
Num CaptureOrdinal Source # 
Ord CaptureOrdinal Source # 
Show CaptureOrdinal Source # 
Ix CaptureOrdinal Source # 

Edit

data Edits m re s Source #

Constructors

Select [(re, Edit m s)] 
Pipe [(re, Edit m s)] 

data Edit m s Source #

Constructors

EDIT_tpl s 
EDIT_phi (Phi s) 
EDIT_fun Context (LineNo -> Match s -> Location -> Capture s -> m (Maybe s)) 
EDIT_gen (LineNo -> Matches s -> m (LineEdit s)) 

data LineEdit s Source #

Constructors

NoEdit 
ReplaceWith s 
Delete 

Instances

Show s => Show (LineEdit s) Source # 

Methods

showsPrec :: Int -> LineEdit s -> ShowS #

show :: LineEdit s -> String #

showList :: [LineEdit s] -> ShowS #

applyEdits :: (IsRegex re s, Monad m, Functor m) => LineNo -> Edits m re s -> s -> m s Source #

applyEdit :: (IsRegex re s, Monad m, Functor m) => (s -> s) -> LineNo -> re -> Edit m s -> s -> m (Maybe s) Source #

applyLineEdit :: Monoid s => (s -> s) -> LineEdit s -> Maybe s Source #

LineNo

Parsers

Replace

class (Extract a, Monoid a) => Replace a where Source #

Replace provides the missing methods needed to replace the matched text; length_ is the minimum implementation

Minimal complete definition

length_, pack_, unpack_, parse_tpl

Methods

length_ :: a -> Int Source #

length function for a

pack_ :: String -> a Source #

inject String into a

unpack_ :: a -> String Source #

project a onto a String

textify :: a -> Text Source #

inject into Text

detextify :: Text -> a Source #

project Text onto a

appendNewline :: a -> a Source #

append a newline

subst :: (a -> a) -> Capture a -> a Source #

apply a substitution function to a Capture

parse_tpl :: a -> Match a -> Location -> Capture a -> Maybe a Source #

convert a template containing $0, $1, etc., in the first argument, into a phi replacement function for use with replaceAllCaptures' and replaceCaptures'

Instances

Replace ByteString Source # 
Replace ByteString Source # 
Replace Text Source # 
Replace Text Source # 
Replace [Char] Source # 
Replace (Seq Char) Source # 

data Replace_ a Source #

a selction of the Replace methods can be encapsulated with Replace_ for the higher-order replacement functions

Constructors

Replace_ 

Fields

replace_ :: Replace a => Replace_ a Source #

replace_ encapsulates Replace_ a from a Replace a context

data Phi a Source #

Phi specifies the substitution function for procesing the substrings captured by the regular expression.

Constructors

Phi 

Fields

  • _phi_context :: Context

    the context for applying the substitution

  • _phi_phi :: Location -> a -> a

    the substitution function takes the location and the text to be replaced and returns the replacement text to be substituted

data Context Source #

Context specifies which contexts the substitutions should be applied

Constructors

TOP

substitutions should be applied to the top-level only, the text that matched the whole RE

SUB

substitutions should only be applied to the text captured by bracketed sub-REs

ALL

the substitution function should be applied to all captures, the top level and the sub-expression captures

Instances

data Location Source #

the Location information passed into the substitution function specifies which sub-expression is being substituted

Constructors

Location 

Fields

  • _loc_match :: Int

    the zero-based, i-th string to be matched, when matching all strings, zero when only the first string is being matched

  • _loc_capture :: CaptureOrdinal

    0, when matching the top-level string matched by the whole RE, 1 for the top-most, left-most redex captured by bracketed sub-REs, etc.

isTopLocation :: Location -> Bool Source #

True iff the location references a complete match (i.e., not a bracketed capture)

replace :: Replace a => Match a -> a -> a Source #

replaceAll :: Replace a => a -> Matches a -> a Source #

replace all with a template, $0 for whole text, $1 for first capture, etc.

replaceAllCaptures :: Replace a => Phi a -> Matches a -> a Source #

substitutes the PHI substitutions through the Matches

replaceAllCaptures' :: Replace a => Context -> (Match a -> Location -> Capture a -> Maybe a) -> Matches a -> a Source #

substitutes using a function that takes the full Match context and returns the same replacement text as the _phi_phi context.

replaceAllCaptures_ :: Extract a => Replace_ a -> Context -> (Match a -> Location -> Capture a -> Maybe a) -> Matches a -> a Source #

replaceAllCaptures_ is like like replaceAllCaptures' but takes the Replace methods through the Replace_ argument

replaceAllCapturesM :: (Extract a, Monad m) => Replace_ a -> Context -> (Match a -> Location -> Capture a -> m (Maybe a)) -> Matches a -> m a Source #

replaceAllCapturesM is just a monadically generalised version of replaceAllCaptures_

replaceCaptures :: Replace a => Phi a -> Match a -> a Source #

substitutes the PHI substitutions through the Match

replaceCaptures' :: Replace a => Context -> (Match a -> Location -> Capture a -> Maybe a) -> Match a -> a Source #

substitutes using a function that takes the full Match context and returns the same replacement text as the _phi_phi context.

replaceCaptures_ :: Extract a => Replace_ a -> Context -> (Match a -> Location -> Capture a -> Maybe a) -> Match a -> a Source #

replaceCaptures_ is like replaceCaptures' but takes the Replace methods through the Replace_ argument

replaceCapturesM :: (Monad m, Extract a) => Replace_ a -> Context -> (Match a -> Location -> Capture a -> m (Maybe a)) -> Match a -> m a Source #

replaceCapturesM is just a monadically generalised version of replaceCaptures_

expandMacros :: (r -> String) -> Mode -> Macros r -> String -> String Source #

expand all of the @{..} macros in the RE in the argument String according to the Macros argument, preprocessing the RE String according to the Mode argument (used internally)

expandMacros' :: (MacroID -> Maybe String) -> String -> String Source #

expand the @{..} macos in the argument string using the given function

Tools

Grep

data Line Source #

Constructors

Line 

Instances

grep :: IsRegex re ByteString => re -> FilePath -> IO () Source #

type GrepScript re s t = [(re, LineNo -> Matches s -> Maybe t)] Source #

grepScript :: IsRegex re s => GrepScript re s t -> [s] -> [t] Source #

Lex

alex :: IsRegex re s => [(re, Match s -> Maybe t)] -> t -> s -> [t] Source #

alex' :: Replace s => (re -> s -> Match s) -> [(re, Match s -> Maybe t)] -> t -> s -> [t] Source #

Sed