alex-tools-0.3.1: A set of functions for a common use case of Alex.

Safe HaskellNone
LanguageHaskell2010

AlexTools

Contents

Synopsis

Lexer Basics

initialInput Source #

Arguments

:: Text

Where the text came from

-> Text

The text to lex

-> Input 

Prepare the text for lexing.

data Input Source #

Information about the lexer's input.

Constructors

Input 

Fields

inputFile :: Input -> Text Source #

The file/thing for the current position.

data Lexeme t Source #

Constructors

Lexeme 

Instances

Eq t => Eq (Lexeme t) Source # 

Methods

(==) :: Lexeme t -> Lexeme t -> Bool #

(/=) :: Lexeme t -> Lexeme t -> Bool #

Show t => Show (Lexeme t) Source # 

Methods

showsPrec :: Int -> Lexeme t -> ShowS #

show :: Lexeme t -> String #

showList :: [Lexeme t] -> ShowS #

NFData t => NFData (Lexeme t) Source # 

Methods

rnf :: Lexeme t -> () #

HasRange (Lexeme t) Source # 

startPos Source #

Arguments

:: Text

Name of file/thing containing this

-> SourcePos 

prettySourcePos :: SourcePos -> String Source #

Pretty print the source position without the file name.

prettySourceRange :: SourceRange -> String Source #

Pretty print the range, without the file name

prettySourcePosLong :: SourcePos -> String Source #

Pretty print the source position, including the file name.

prettySourceRangeLong :: SourceRange -> String Source #

Pretty print the range, including the file name.

class HasRange t where Source #

Minimal complete definition

range

Methods

range :: t -> SourceRange Source #

(<->) :: (HasRange a, HasRange b) => a -> b -> SourceRange Source #

moveSourcePos :: Char -> SourcePos -> SourcePos Source #

Update a SourcePos for a particular matched character

Writing Lexer Actions

data Action s a Source #

An action to be taken when a regular expression matchers.

Instances

Monad (Action s) Source # 

Methods

(>>=) :: Action s a -> (a -> Action s b) -> Action s b #

(>>) :: Action s a -> Action s b -> Action s b #

return :: a -> Action s a #

fail :: String -> Action s a #

Functor (Action s) Source # 

Methods

fmap :: (a -> b) -> Action s a -> Action s b #

(<$) :: a -> Action s b -> Action s a #

Applicative (Action s) Source # 

Methods

pure :: a -> Action s a #

(<*>) :: Action s (a -> b) -> Action s a -> Action s b #

liftA2 :: (a -> b -> c) -> Action s a -> Action s b -> Action s c #

(*>) :: Action s a -> Action s b -> Action s b #

(<*) :: Action s a -> Action s b -> Action s a #

Lexemes

lexeme :: t -> Action s [Lexeme t] Source #

Use the token and the current match to construct a lexeme.

matchLength :: Action s Int Source #

The number of characters in the matching input.

matchRange :: Action s SourceRange Source #

Get the range for the matching input.

matchText :: Action s Text Source #

Get the text associated with the matched input.

Manipulating the lexer's state

getLexerState :: Action s s Source #

Acces the curent state of the lexer.

setLexerState :: s -> Action s () Source #

Change the state of the lexer.

Access to the lexer's input

startInput :: Action s Input Source #

Acces the input just before the regular expression started matching.

endInput :: Action s Input Source #

Acces the input just after the regular expression that matched.

Interface with Alex

makeLexer :: ExpQ Source #

Generate a function to use an Alex lexer. The expression is of type LexerConfig s t -> Input -> [Lexeme t]

data LexerConfig s t Source #

Lexer configuration.

Constructors

LexerConfig 

Fields

simpleLexer :: LexerConfig () t Source #

A lexer that uses no lexer-modes, and does not emit anything at the end of the file.

data Word8 :: * #

8-bit unsigned integer type

Instances

Bounded Word8

Since: 2.1

Enum Word8

Since: 2.1

Eq Word8

Since: 2.1

Methods

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

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

Integral Word8

Since: 2.1

Num Word8

Since: 2.1

Ord Word8

Since: 2.1

Methods

compare :: Word8 -> Word8 -> Ordering #

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

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

(>) :: Word8 -> Word8 -> Bool #

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

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8

Since: 2.1

Real Word8

Since: 2.1

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: 2.1

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: 2.1

Lift Word8 

Methods

lift :: Word8 -> Q Exp #

Bits Word8

Since: 2.1

FiniteBits Word8

Since: 4.6.0.0

NFData Word8 

Methods

rnf :: Word8 -> () #