yi-language-0.18.0: Collection of language-related Yi libraries.

Safe HaskellNone
LanguageHaskell2010

Yi.Regex

Synopsis

Documentation

data SearchOption Source #

Constructors

IgnoreCase

Compile for matching that ignores char case

NoNewLine

Compile for newline-insensitive matching

QuoteRegex

Treat the input not as a regex but as a literal string to search for.

Instances
Eq SearchOption Source # 
Instance details

Defined in Yi.Regex

Generic SearchOption Source # 
Instance details

Defined in Yi.Regex

Associated Types

type Rep SearchOption :: * -> * #

Binary SearchOption Source # 
Instance details

Defined in Yi.Regex

type Rep SearchOption Source # 
Instance details

Defined in Yi.Regex

type Rep SearchOption = D1 (MetaData "SearchOption" "Yi.Regex" "yi-language-0.18.0-1FEc2siMQfF3fsxTbsKtHE" False) (C1 (MetaCons "IgnoreCase" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "NoNewLine" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "QuoteRegex" PrefixI False) (U1 :: * -> *)))

data SearchExp Source #

Instances
Binary SearchExp Source # 
Instance details

Defined in Yi.Regex

emptyRegex :: Regex Source #

The regular expression that matches nothing.

regexEscapeString :: String -> String Source #

Return an escaped (for parseRegex use) version of the string.

reversePattern :: (Pattern, (t, DoPa)) -> (Pattern, (t, DoPa)) Source #

Reverse a pattern. Note that the submatches will be reversed as well.

defaultCompOpt #

Arguments

:: RegexOptions regex compOpt execOpt 
=> compOpt

reasonable options (extended,caseSensitive,multiline regex)

defaultExecOpt #

Arguments

:: RegexOptions regex compOpt execOpt 
=> execOpt

reasonable options (extended,caseSensitive,multiline regex)

makeRegex :: RegexMaker regex compOpt execOpt source => source -> regex #

make using the defaultCompOpt and defaultExecOpt

makeRegexOptsM :: (RegexMaker regex compOpt execOpt source, Monad m) => compOpt -> execOpt -> source -> m regex #

Specify your own options, reporting errors with fail

class Extract source => RegexLike regex source where #

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.

Methods

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

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.

matchOnceText :: regex -> source -> Maybe (source, MatchText 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.

newtype AllTextSubmatches (f :: * -> *) b #

Used in results of RegexContext instances

Constructors

AllTextSubmatches 

Fields

(=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target #

This is the pure functional matching operator. If the target cannot be produced then some empty result will be returned. If there is an error in processing, then error will be called.

data CompOption #

Control whether the pattern is multiline or case-sensitive like Text.Regex and whether to capture the subgroups (\1, \2, etc). Controls enabling extra anchor syntax.

Constructors

CompOption 

Fields

  • caseSensitive :: Bool

    True in blankCompOpt and defaultCompOpt

  • multiline :: Bool

    False in blankCompOpt, True in defaultCompOpt. Compile for newline-sensitive matching. "By default, newline is a completely ordinary character with no special meaning in either REs or strings. With this flag, inverted bracket expressions and . never match newline, a ^ anchor matches the null string after any newline in the string in addition to its normal function, and the $ anchor matches the null string before any newline in the string in addition to its normal function."

  • rightAssoc :: Bool

    True (and therefore Right associative) in blankCompOpt and defaultCompOpt

  • newSyntax :: Bool

    False in blankCompOpt, True in defaultCompOpt. Add the extended non-POSIX syntax described in Text.Regex.TDFA haddock documentation.

  • lastStarGreedy :: Bool

    False by default. This is POSIX correct but it takes space and is slower. Setting this to true will improve performance, and should be done if you plan to set the captureGroups execoption to False.

data Regex #

The TDFA backend specific Regex type, used by this module's RegexOptions and RegexMaker