Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
A usable regular expressions library on top of pcre-light.
Synopsis
- (=~) :: ConvertibleStrings a SBS => a -> Regex -> Bool
- (≈) :: ConvertibleStrings a SBS => a -> Regex -> Bool
- scan :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS) => Regex -> a -> [(a, [a])]
- scanO :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS) => Regex -> [PCREExecOption] -> a -> [(a, [a])]
- scanRanges :: ConvertibleStrings a SBS => Regex -> a -> [((Int, Int), [(Int, Int)])]
- scanRangesO :: ConvertibleStrings a SBS => Regex -> [PCREExecOption] -> a -> [((Int, Int), [(Int, Int)])]
- class RegexReplacement a
- sub :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement r) => Regex -> r -> a -> a
- subO :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement r) => Regex -> [PCREExecOption] -> r -> a -> a
- gsub :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement r) => Regex -> r -> a -> a
- gsubO :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement r) => Regex -> [PCREExecOption] -> r -> a -> a
- split :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS) => Regex -> a -> [a]
- splitO :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS) => Regex -> [PCREExecOption] -> a -> [a]
- re :: QuasiQuoter
- mkRegexQQ :: [PCREOption] -> QuasiQuoter
- escape :: (ConvertibleStrings a SBS, ConvertibleStrings SBS a) => a -> a
- data Regex
- data PCREOption
- compileM :: ByteString -> [PCREOption] -> Either String Regex
- rawMatch :: Regex -> SBS -> Int -> [PCREExecOption] -> Maybe [(Int, Int)]
- rawSub :: RegexReplacement r => Regex -> r -> SBS -> Int -> [PCREExecOption] -> Maybe (SBS, Int)
Matching
(=~) :: ConvertibleStrings a SBS => a -> Regex -> Bool Source #
Checks whether a string matches a regex.
>>>
"https://val.packett.cool" =~ [re|^http.*|]
True
(≈) :: ConvertibleStrings a SBS => a -> Regex -> Bool Source #
Same as =~.
Checks whether a string matches a regex.
>>>
"https://val.packett.cool" =~ [re|^http.*|]
True
scan :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS) => Regex -> a -> [(a, [a])] Source #
Searches the string for all matches of a given regex.
>>>
scan [re|\s*entry (\d+) (\w+)\s*&?|] (" entry 1 hello &entry 2 hi" :: String)
[(" entry 1 hello &",["1","hello"]),("entry 2 hi",["2","hi"])]
It is lazy! If you only need the first match, just apply head
(or
headMay
from the "safe" library) -- no extra work will be performed!
>>>
head $ scan [re|\s*entry (\d+) (\w+)\s*&?|] (" entry 1 hello &entry 2 hi" :: String)
(" entry 1 hello &",["1","hello"])
scanO :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS) => Regex -> [PCREExecOption] -> a -> [(a, [a])] Source #
Exactly like scan
, but passes runtime options to PCRE.
scanRanges :: ConvertibleStrings a SBS => Regex -> a -> [((Int, Int), [(Int, Int)])] Source #
scanRangesO :: ConvertibleStrings a SBS => Regex -> [PCREExecOption] -> a -> [((Int, Int), [(Int, Int)])] Source #
Exactly like scanRanges
, but passes runtime options to PCRE.
Replacement
class RegexReplacement a Source #
Class of types that can serve as the replacement argument in the
sub
family of functions.
performReplacement
Instances
ConvertibleStrings a SBS => RegexReplacement a Source # | A replacement string. |
Defined in Text.Regex.PCRE.Heavy performReplacement :: SBS -> [SBS] -> a -> SBS | |
(ConvertibleStrings SBS a, ConvertibleStrings a SBS) => RegexReplacement ([a] -> a) Source # | A function mapping the matched groups to a replacement string. |
Defined in Text.Regex.PCRE.Heavy performReplacement :: SBS -> [SBS] -> ([a] -> a) -> SBS | |
(ConvertibleStrings SBS a, ConvertibleStrings a SBS) => RegexReplacement (a -> [a] -> a) Source # | A function mapping the matched string and groups to a replacement string. |
Defined in Text.Regex.PCRE.Heavy performReplacement :: SBS -> [SBS] -> (a -> [a] -> a) -> SBS | |
(ConvertibleStrings SBS a, ConvertibleStrings a SBS) => RegexReplacement (a -> a) Source # | A function mapping the matched string to a replacement string. |
Defined in Text.Regex.PCRE.Heavy performReplacement :: SBS -> [SBS] -> (a -> a) -> SBS |
sub :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement r) => Regex -> r -> a -> a Source #
Replaces the first occurence of a given regex.
>>>
sub [re|thing|] "world" "Hello, thing thing" :: String
"Hello, world thing"
>>>
sub [re|a|] "b" "c" :: String
"c"
>>>
sub [re|bad|] "xxxbad" "this is bad, right?" :: String
"this is xxxbad, right?"
You can use functions! A function of ConvertibleStrings SBS gets the full match. A function of [ConvertibleStrings SBS] gets the groups. A function of ConvertibleStrings SBS → [ConvertibleStrings SBS] gets both.
>>>
sub [re|%(\d+)(\w+)|] (\(d:w:_) -> "{" ++ d ++ " of " ++ w ++ "}" :: String) "Hello, %20thing" :: String
"Hello, {20 of thing}"
subO :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement r) => Regex -> [PCREExecOption] -> r -> a -> a Source #
Exactly like sub
, but passes runtime options to PCRE.
gsub :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement r) => Regex -> r -> a -> a Source #
Replaces all occurences of a given regex.
See sub
for more documentation.
>>>
gsub [re|thing|] "world" "Hello, thing thing" :: String
"Hello, world world"
>>>
gsub [re||] "" "Hello, world" :: String
"Hello, world"
https://codeberg.org/valpackett/pcre-heavy/issues/2 >>> gsub [re|good|] "bad" "goodgoodgood" :: String "badbadbad"
>>>
gsub [re|bad|] "xxxbad" "this is bad, right? bad" :: String
"this is xxxbad, right? xxxbad"
>>>
gsub [re|a|] "" "aaa" :: String
""
gsubO :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS, RegexReplacement r) => Regex -> [PCREExecOption] -> r -> a -> a Source #
Exactly like gsub
, but passes runtime options to PCRE.
Splitting
split :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS) => Regex -> a -> [a] Source #
Splits the string using the given regex.
Is lazy.
>>>
split [re|%(begin|next|end)%|] ("%begin%hello%next%world%end%" :: String)
["","hello","world",""]
>>>
split [re|%(begin|next|end)%|] ("" :: String)
[""]
splitO :: (ConvertibleStrings SBS a, ConvertibleStrings a SBS) => Regex -> [PCREExecOption] -> a -> [a] Source #
Exactly like split
, but passes runtime options to PCRE.
QuasiQuoter
re :: QuasiQuoter Source #
A QuasiQuoter for regular expressions that does a compile time check.
mkRegexQQ :: [PCREOption] -> QuasiQuoter Source #
Returns a QuasiQuoter like re
, but with given PCRE options.
Building regexes
escape :: (ConvertibleStrings a SBS, ConvertibleStrings SBS a) => a -> a Source #
Escapes the regex metacharacters in a string. In other words, given a string, produces a regex that matches just that string (or case variations of that string, if case-insenstive matching is enabled).
>>>
("foo*bar"::String) =~ PCRE.compile (escape "foo*bar") []
True
Types and stuff from pcre-light
An abstract pointer to a compiled PCRE Regex structure The structure allocated by the PCRE library will be deallocated automatically by the Haskell storage manager.
data PCREOption #
A type for PCRE compile-time options. These are newtyped CInts,
which can be bitwise-or'd together, using (.|.)
Instances
compileM :: ByteString -> [PCREOption] -> Either String Regex #
Advanced raw stuff
rawMatch :: Regex -> SBS -> Int -> [PCREExecOption] -> Maybe [(Int, Int)] Source #
Does raw PCRE matching (you probably shouldn't use this directly).
>>>
rawMatch [re|\w{2}|] "a a ab abc ba" 0 []
Just [(4,6)]>>>
rawMatch [re|\w{2}|] "a a ab abc ba" 6 []
Just [(7,9)]>>>
rawMatch [re|(\w)(\w)|] "a a ab abc ba" 0 []
Just [(4,6),(4,5),(5,6)]
rawSub :: RegexReplacement r => Regex -> r -> SBS -> Int -> [PCREExecOption] -> Maybe (SBS, Int) Source #
Orphan instances
Lift PCREOption Source # | |
lift :: Quote m => PCREOption -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => PCREOption -> Code m PCREOption # |