tlex-th-0.4.2.0: TemplateHaskell plugin for Tlex
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Lexer.Tlex.Plugin.TH

Documentation

class (Enum unit, Monad m) => TlexContext mark unit (m :: Type -> Type) | m -> mark, m -> unit where #

Methods

tlexGetInputPart :: m (Maybe unit) #

Get a unit of current position from input, and move to next position.

tlexGetMark :: m mark #

Get a mark of current position.

data TlexResult mark action #

Constructors

TlexEndOfInput

No more inputs.

TlexNotAccepted

Some inputs are available, but not accepted.

TlexAccepted mark action

Accepted with a end position and an action.

Instances

Instances details
(Show mark, Show action) => Show (TlexResult mark action) 
Instance details

Defined in Language.Lexer.Tlex.Runner

Methods

showsPrec :: Int -> TlexResult mark action -> ShowS #

show :: TlexResult mark action -> String #

showList :: [TlexResult mark action] -> ShowS #

(Eq mark, Eq action) => Eq (TlexResult mark action) 
Instance details

Defined in Language.Lexer.Tlex.Runner

Methods

(==) :: TlexResult mark action -> TlexResult mark action -> Bool #

(/=) :: TlexResult mark action -> TlexResult mark action -> Bool #

data Runner (unit :: k) action #

Constructors

Runner 

Fields

Instances

Instances details
Functor (Runner unit) 
Instance details

Defined in Language.Lexer.Tlex.Runner

Methods

fmap :: (a -> b) -> Runner unit a -> Runner unit b #

(<$) :: a -> Runner unit b -> Runner unit a #

runRunner :: (Enum state, TlexContext mark unit m) => Runner unit action -> state -> m (TlexResult mark action) #

buildTHScanner :: forall e s a. Enum e => Bounded e => Type -> Type -> Type -> THScannerBuilder s e a () -> THScanner e Source #

buildTHScannerWithReify :: forall s a e. Enum e => Bounded e => Typeable e => Typeable s => Typeable a => THScannerBuilder s e a () -> Q (THScanner e) Source #

thLexRule :: Enum e => Enum s => [s] -> Pattern e -> Code Q a -> THScannerBuilder s e a () Source #