Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data SearchOption
- makeSearchOptsM :: [SearchOption] -> String -> Either String SearchExp
- data SearchExp = SearchExp {
- seInput :: String
- seCompiled :: Regex
- seBackCompiled :: Regex
- seOptions :: [SearchOption]
- searchString :: SearchExp -> String
- searchRegex :: Direction -> SearchExp -> Regex
- emptySearch :: SearchExp
- emptyRegex :: Regex
- regexEscapeString :: String -> String
- reversePattern :: (Pattern, (t, DoPa)) -> (Pattern, (t, DoPa))
- newtype AllTextSubmatches (f :: Type -> Type) b = AllTextSubmatches {
- getAllTextSubmatches :: f b
- class Extract source => RegexLike regex source where
- matchAll :: regex -> source -> [MatchArray]
- matchOnceText :: regex -> source -> Maybe (source, MatchText source, source)
- data Regex
- data CompOption = CompOption {
- caseSensitive :: Bool
- multiline :: Bool
- rightAssoc :: Bool
- newSyntax :: Bool
- lastStarGreedy :: Bool
- makeRegex :: RegexMaker regex compOpt execOpt source => source -> regex
- makeRegexOptsM :: (RegexMaker regex compOpt execOpt source, MonadFail m) => compOpt -> execOpt -> source -> m regex
- defaultCompOpt :: RegexOptions regex compOpt execOpt => compOpt
- defaultExecOpt :: RegexOptions regex compOpt execOpt => execOpt
- (=~) :: (RegexMaker Regex CompOption ExecOption source, RegexContext Regex source1 target) => source1 -> source -> target
Documentation
data SearchOption Source #
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
Generic SearchOption Source # | |
Defined in Yi.Regex type Rep SearchOption :: Type -> Type # from :: SearchOption -> Rep SearchOption x # to :: Rep SearchOption x -> SearchOption # | |
Binary SearchOption Source # | |
Defined in Yi.Regex | |
Eq SearchOption Source # | |
Defined in Yi.Regex (==) :: SearchOption -> SearchOption -> Bool # (/=) :: SearchOption -> SearchOption -> Bool # | |
type Rep SearchOption Source # | |
Defined in Yi.Regex type Rep SearchOption = D1 ('MetaData "SearchOption" "Yi.Regex" "yi-language-0.19.1-48kBHo5CiHwKn5eCndJTLb" 'False) (C1 ('MetaCons "IgnoreCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoNewLine" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuoteRegex" 'PrefixI 'False) (U1 :: Type -> Type))) |
makeSearchOptsM :: [SearchOption] -> String -> Either String SearchExp Source #
SearchExp | |
|
searchString :: SearchExp -> String Source #
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.
newtype AllTextSubmatches (f :: Type -> Type) b #
Used in results of RegexContext
instances.
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
.
Conversely, 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.
Nothing
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.
The TDFA backend specific Regex
type, used by this module's RegexOptions
and RegexMaker
.
Instances
RegexOptions Regex CompOption ExecOption | |
Defined in Text.Regex.TDFA.Common defaultCompOpt :: CompOption # defaultExecOpt :: ExecOption # setExecOpts :: ExecOption -> Regex -> Regex # getExecOpts :: Regex -> ExecOption # |
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.
CompOption | |
|
Instances
Read CompOption | |
Defined in Text.Regex.TDFA.Common readsPrec :: Int -> ReadS CompOption # readList :: ReadS [CompOption] # readPrec :: ReadPrec CompOption # readListPrec :: ReadPrec [CompOption] # | |
Show CompOption | |
Defined in Text.Regex.TDFA.Common showsPrec :: Int -> CompOption -> ShowS # show :: CompOption -> String # showList :: [CompOption] -> ShowS # | |
RegexOptions Regex CompOption ExecOption | |
Defined in Text.Regex.TDFA.Common defaultCompOpt :: CompOption # defaultExecOpt :: ExecOption # setExecOpts :: ExecOption -> Regex -> Regex # getExecOpts :: Regex -> ExecOption # |
makeRegex :: RegexMaker regex compOpt execOpt source => source -> regex #
Use the defaultCompOpt
and defaultExecOpt
.
makeRegexOptsM :: (RegexMaker regex compOpt execOpt source, MonadFail m) => compOpt -> execOpt -> source -> m regex #
Specify your own options, reporting errors with fail
defaultCompOpt :: RegexOptions regex compOpt execOpt => compOpt #
Reasonable options (extended, caseSensitive, multiline regex).
defaultExecOpt :: RegexOptions regex compOpt execOpt => execOpt #
Reasonable options (extended, caseSensitive, multiline regex).
(=~) :: (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.