Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Regex
- = MatchAnyChar
- | MatchDynamic !Int
- | MatchChar (Char -> Bool)
- | MatchSome !Regex
- | MatchAlt !Regex !Regex
- | MatchConcat !Regex !Regex
- | MatchCapture !Int !Regex
- | MatchCaptured !Int
- | AssertWordBoundary
- | AssertBeginning
- | AssertEnd
- | AssertPositive !Direction !Regex
- | AssertNegative !Direction !Regex
- | Possessive !Regex
- | Lazy !Regex
- | Subroutine !Int
- | MatchNull
- data RE
- pattern RE :: ByteString -> Bool -> RE
- reCaseSensitive :: RE -> Bool
- reString :: RE -> ByteString
- compileRE :: RE -> Either String Regex
- compileRegex :: Bool -> ByteString -> Either String Regex
- matchRegex :: Regex -> ByteString -> Maybe (ByteString, IntMap (Int, Int))
- testRegex :: Bool -> String -> String -> Maybe (String, [(Int, String)])
- isWordChar :: Char -> Bool
Documentation
MatchAnyChar | |
MatchDynamic !Int | |
MatchChar (Char -> Bool) | |
MatchSome !Regex | |
MatchAlt !Regex !Regex | |
MatchConcat !Regex !Regex | |
MatchCapture !Int !Regex | |
MatchCaptured !Int | |
AssertWordBoundary | |
AssertBeginning | |
AssertEnd | |
AssertPositive !Direction !Regex | |
AssertNegative !Direction !Regex | |
Possessive !Regex | |
Lazy !Regex | |
Subroutine !Int | |
MatchNull |
A representation of a regular expression.
Instances
FromJSON RE Source # | |
Defined in Skylighting.Regex | |
ToJSON RE Source # | |
Data RE Source # | |
Defined in Skylighting.Regex gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RE -> c RE # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RE # dataTypeOf :: RE -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RE) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RE) # gmapT :: (forall b. Data b => b -> b) -> RE -> RE # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RE -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RE -> r # gmapQ :: (forall d. Data d => d -> u) -> RE -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RE -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RE -> m RE # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RE -> m RE # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RE -> m RE # | |
Read RE Source # | |
Show RE Source # | |
Binary RE Source # | |
Eq RE Source # | |
Ord RE Source # | |
reCaseSensitive :: RE -> Bool Source #
reString :: RE -> ByteString Source #
compileRegex :: Bool -> ByteString -> Either String Regex Source #
Compile a UTF-8 encoded ByteString as a Regex. If the first parameter is True, then the Regex will be case sensitive.
matchRegex :: Regex -> ByteString -> Maybe (ByteString, IntMap (Int, Int)) Source #
Match a Regex against a (presumed UTF-8 encoded) ByteString,
returning the matched text and a map of (offset, size)
pairs for captures. Note that all matches are from the
beginning of the string (a ^
anchor is implicit). Note
also that to avoid pathological performance in certain cases,
the matcher is limited to considering 2000 possible matches
at a time; when that threshold is reached, it discards
smaller matches. Hence certain regexes may incorrectly fail to
match: e.g. a*a{3000}$
on a string of 3000 a
s.
isWordChar :: Char -> Bool Source #