Safe Haskell | None |
---|---|
Language | Haskell2010 |
Text.Regex.PCRE.Heavy
Description
A usable regular expressions library on top of pcre-light.
- (=~) :: (Stringable a, RegexResult b) => a -> Regex -> b
- scan :: Stringable a => Regex -> a -> [[a]]
- scanO :: Stringable a => Regex -> [PCREExecOption] -> a -> [[a]]
- sub :: (Stringable a, RegexReplacement r) => Regex -> r -> a -> a
- subO :: (Stringable a, RegexReplacement r) => Regex -> [PCREExecOption] -> r -> a -> a
- gsub :: (Stringable a, RegexReplacement r) => Regex -> r -> a -> a
- gsubO :: (Stringable a, RegexReplacement r) => Regex -> [PCREExecOption] -> r -> a -> a
- re :: QuasiQuoter
- mkRegexQQ :: [PCREOption] -> QuasiQuoter
- data Regex :: *
- data PCREOption :: *
- rawMatch :: Regex -> ByteString -> Int -> [PCREExecOption] -> Maybe [(Int, Int)]
- rawSub :: RegexReplacement r => Regex -> r -> ByteString -> Int -> [PCREExecOption] -> Maybe (ByteString, Int)
Matching
(=~) :: (Stringable a, RegexResult b) => a -> Regex -> b Source
Matches a string with a regex.
You can cast the result to Bool or Maybe [Stringable]
Maybe [Stringable] only represents the first match and its groups.
Use scan
to find all matches.
Note: if casts to bool automatically.
>>>
:set -XQuasiQuotes
>>>
"https://unrelenting.technology" =~ [re|^http.*|] :: Bool
True>>>
"https://unrelenting.technology" =~ [re|^https?://([^\.]+)\..*|] :: Maybe [String]
Just ["https://unrelenting.technology","unrelenting"]>>>
if "https://unrelenting.technology" =~ [re|^http.*|] then "YEP" else "NOPE"
"YEP"
scan :: Stringable a => Regex -> 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"
[[" entry 1 hello &","1","hello"],["entry 2 hi","2","hi"]]
scanO :: Stringable a => Regex -> [PCREExecOption] -> a -> [[a]] Source
Exactly like scan
, but passes runtime options to PCRE.
Replacement
sub :: (Stringable a, 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"
You can use functions! A function of Stringable gets the full match. A function of [Stringable] gets the groups. A function of Stringable -> [Stringable] gets both.
>>>
sub [re|%(\d+)(\w+)|] (\(d:w:_) -> "{" ++ d ++ " of " ++ w ++ "}" :: String) "Hello, %20thing" :: String
"Hello, {20 of thing}"
subO :: (Stringable a, RegexReplacement r) => Regex -> [PCREExecOption] -> r -> a -> a Source
Exactly like sub
, but passes runtime options to PCRE.
gsub :: (Stringable a, 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"
gsubO :: (Stringable a, RegexReplacement r) => Regex -> [PCREExecOption] -> r -> a -> a Source
Exactly like gsub
, 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.
Types from pcre-light
data Regex :: *
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 '(Data.Bits..|.)'
Instances
Advanced raw stuff
rawMatch :: Regex -> ByteString -> Int -> [PCREExecOption] -> Maybe [(Int, Int)] Source
Does raw PCRE matching (you probably shouldn't use this directly).
>>>
:set -XOverloadedStrings
>>>
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 -> ByteString -> Int -> [PCREExecOption] -> Maybe (ByteString, Int) Source