regex-tdfa-quasiquoter-0.2.1.0: Quasi-quoter for TDFA (extended POSIX) regular expressions.

Safe HaskellNone
LanguageHaskell2010

Text.Regex.TDFA.QuasiQuoter.Internal

Contents

Description

Internal definitions for Text.Regex.TDFA.QuasiQuoter. Expect these definitions to change.

Synopsis

Documentation

data Flag Source #

A flag indicates whether a particular option should be True ("on") or False ("off") when compiling a regular expression string.

Refer to CompOption and ExecOption for the meanings of each flag.

Instances

Eq Flag Source # 

Methods

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

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

Ord Flag Source # 

Methods

compare :: Flag -> Flag -> Ordering #

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

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

(>) :: Flag -> Flag -> Bool #

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

max :: Flag -> Flag -> Flag #

min :: Flag -> Flag -> Flag #

Show Flag Source # 

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

data Options Source #

Options to use when compiling a regular expression string.

Refer to CompOption and ExecOption for the meanings of each option.

unescape :: String -> String Source #

Replaces escape sequences with their respective characters. Any sequence not listed will be left as-is.

Sequence  | Character
----------+--------------------
\\        | \
\n        | Newline
\r        | Carriage return
\t        | Horizontal tab
\f        | Form feed
\v        | Vertical tab
\xFFFF    | Code point (in hex)
|~]       | |]
\|~]      | |~]

Note that if you are reading the source file and not the generated Haddock documentation that the backslashes have been doubled up. This is also why the table is incorrectly formatted in source.

compilePattern :: String -> Either String (Pattern, (GroupIndex, DoPa)) Source #

The AST for the regular expression string. If there is a parse error a corresponding error string is returned.

defaultOptions :: Options Source #

The default options used when compiling a regular expression string.

Refer to CompOption and ExecOption for the meanings of each option.

optionsToTDFAOptions :: Options -> (CompOption, ExecOption) Source #

Converts this module's representation of regular expression string compiler options to that of Text.Regex.TDFA's.

applyFlag :: Flag -> Options -> Options Source #

Overrides the option indicated by the flag.

flagsChars :: [(Char, Flag)] Source #

A relation of flags and characters. Each flag is related with one character and that character is unique. Not all characters are related to a flag.

charToFlag :: Char -> Maybe Flag Source #

The flag related to the character (by flagsChars), if any.

flagToChar :: Flag -> Char Source #

The character related to the flag (by flagsChars).

negateFlag :: Flag -> Flag Source #

The flag which indicates the opposite option. That is, if the flag indicates an option to be True ("on") then the negated flag indicates the same option to be False ("off") and vice versa.

parseFlags :: String -> Either String [Flag] Source #

The set of flags related to the set of characters using the relation flagsChars.

  • No character may occur twice.
  • If a character is present the character related to the negated flag must not be.
  • All characters must be related to a flag.

If one of these conditions are not met then a corresponding error message is returned instead.

switch :: Either a b -> Either b a Source #

The switch of Left and Right for an Either value.

flagStringToOptions :: String -> Either String Options Source #

Apply all flags to the default options. See parseFlags and applyFlag.

Orphan instances

Data Pattern Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pattern -> c Pattern #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pattern #

toConstr :: Pattern -> Constr #

dataTypeOf :: Pattern -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Pattern) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pattern) #

gmapT :: (forall b. Data b => b -> b) -> Pattern -> Pattern #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pattern -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pattern -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pattern -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pattern -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pattern -> m Pattern #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pattern -> m Pattern #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pattern -> m Pattern #

Data PatternSet Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatternSet -> c PatternSet #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PatternSet #

toConstr :: PatternSet -> Constr #

dataTypeOf :: PatternSet -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PatternSet) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PatternSet) #

gmapT :: (forall b. Data b => b -> b) -> PatternSet -> PatternSet #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatternSet -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatternSet -> r #

gmapQ :: (forall d. Data d => d -> u) -> PatternSet -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatternSet -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatternSet -> m PatternSet #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatternSet -> m PatternSet #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatternSet -> m PatternSet #

Data PatternSetCharacterClass Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatternSetCharacterClass -> c PatternSetCharacterClass #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PatternSetCharacterClass #

toConstr :: PatternSetCharacterClass -> Constr #

dataTypeOf :: PatternSetCharacterClass -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PatternSetCharacterClass) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PatternSetCharacterClass) #

gmapT :: (forall b. Data b => b -> b) -> PatternSetCharacterClass -> PatternSetCharacterClass #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatternSetCharacterClass -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatternSetCharacterClass -> r #

gmapQ :: (forall d. Data d => d -> u) -> PatternSetCharacterClass -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatternSetCharacterClass -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatternSetCharacterClass -> m PatternSetCharacterClass #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatternSetCharacterClass -> m PatternSetCharacterClass #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatternSetCharacterClass -> m PatternSetCharacterClass #

Data PatternSetCollatingElement Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatternSetCollatingElement -> c PatternSetCollatingElement #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PatternSetCollatingElement #

toConstr :: PatternSetCollatingElement -> Constr #

dataTypeOf :: PatternSetCollatingElement -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PatternSetCollatingElement) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PatternSetCollatingElement) #

gmapT :: (forall b. Data b => b -> b) -> PatternSetCollatingElement -> PatternSetCollatingElement #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatternSetCollatingElement -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatternSetCollatingElement -> r #

gmapQ :: (forall d. Data d => d -> u) -> PatternSetCollatingElement -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatternSetCollatingElement -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatternSetCollatingElement -> m PatternSetCollatingElement #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatternSetCollatingElement -> m PatternSetCollatingElement #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatternSetCollatingElement -> m PatternSetCollatingElement #

Data PatternSetEquivalenceClass Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatternSetEquivalenceClass -> c PatternSetEquivalenceClass #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PatternSetEquivalenceClass #

toConstr :: PatternSetEquivalenceClass -> Constr #

dataTypeOf :: PatternSetEquivalenceClass -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PatternSetEquivalenceClass) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PatternSetEquivalenceClass) #

gmapT :: (forall b. Data b => b -> b) -> PatternSetEquivalenceClass -> PatternSetEquivalenceClass #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatternSetEquivalenceClass -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatternSetEquivalenceClass -> r #

gmapQ :: (forall d. Data d => d -> u) -> PatternSetEquivalenceClass -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PatternSetEquivalenceClass -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatternSetEquivalenceClass -> m PatternSetEquivalenceClass #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatternSetEquivalenceClass -> m PatternSetEquivalenceClass #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatternSetEquivalenceClass -> m PatternSetEquivalenceClass #

Data DoPa Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DoPa -> c DoPa #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DoPa #

toConstr :: DoPa -> Constr #

dataTypeOf :: DoPa -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DoPa) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DoPa) #

gmapT :: (forall b. Data b => b -> b) -> DoPa -> DoPa #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DoPa -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DoPa -> r #

gmapQ :: (forall d. Data d => d -> u) -> DoPa -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DoPa -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DoPa -> m DoPa #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DoPa -> m DoPa #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DoPa -> m DoPa #

Data CompOption Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompOption -> c CompOption #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompOption #

toConstr :: CompOption -> Constr #

dataTypeOf :: CompOption -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CompOption) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompOption) #

gmapT :: (forall b. Data b => b -> b) -> CompOption -> CompOption #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompOption -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompOption -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompOption -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompOption -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompOption -> m CompOption #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompOption -> m CompOption #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompOption -> m CompOption #

Data ExecOption Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExecOption -> c ExecOption #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExecOption #

toConstr :: ExecOption -> Constr #

dataTypeOf :: ExecOption -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ExecOption) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExecOption) #

gmapT :: (forall b. Data b => b -> b) -> ExecOption -> ExecOption #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExecOption -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExecOption -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExecOption -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExecOption -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExecOption -> m ExecOption #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExecOption -> m ExecOption #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExecOption -> m ExecOption #