skylighting-core-0.10.5.1: syntax highlighting library
Safe HaskellNone
LanguageHaskell2010

Skylighting.Regex

Synopsis

Documentation

data RE Source #

A representation of a regular expression.

Constructors

RE 

Instances

Instances details
Eq RE Source # 
Instance details

Defined in Skylighting.Regex

Methods

(==) :: RE -> RE -> Bool #

(/=) :: RE -> RE -> Bool #

Data RE Source # 
Instance details

Defined in Skylighting.Regex

Methods

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 #

toConstr :: RE -> Constr #

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 #

Ord RE Source # 
Instance details

Defined in Skylighting.Regex

Methods

compare :: RE -> RE -> Ordering #

(<) :: RE -> RE -> Bool #

(<=) :: RE -> RE -> Bool #

(>) :: RE -> RE -> Bool #

(>=) :: RE -> RE -> Bool #

max :: RE -> RE -> RE #

min :: RE -> RE -> RE #

Read RE Source # 
Instance details

Defined in Skylighting.Regex

Show RE Source # 
Instance details

Defined in Skylighting.Regex

Methods

showsPrec :: Int -> RE -> ShowS #

show :: RE -> String #

showList :: [RE] -> ShowS #

Generic RE Source # 
Instance details

Defined in Skylighting.Regex

Associated Types

type Rep RE :: Type -> Type #

Methods

from :: RE -> Rep RE x #

to :: Rep RE x -> RE #

ToJSON RE Source # 
Instance details

Defined in Skylighting.Regex

FromJSON RE Source # 
Instance details

Defined in Skylighting.Regex

Binary RE Source # 
Instance details

Defined in Skylighting.Regex

Methods

put :: RE -> Put #

get :: Get RE #

putList :: [RE] -> Put #

type Rep RE Source # 
Instance details

Defined in Skylighting.Regex

type Rep RE = D1 ('MetaData "RE" "Skylighting.Regex" "skylighting-core-0.10.5.1-AFpz2V9yu8Z6VUCstianHd" 'False) (C1 ('MetaCons "RE" 'PrefixI 'True) (S1 ('MetaSel ('Just "reString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "reCaseSensitive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

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 as.