haskell-lexer-1.1: A fully compliant Haskell 98 lexer.

Safe HaskellSafe
LanguageHaskell98

Language.Haskell.Lexer

Synopsis

Documentation

data Token Source #

Haskell token classifications:

Constructors

Varid

Variable

Conid

Constructor

Varsym

Variable operator

Consym

Constructor operator

Reservedid

Reserved keyword

Reservedop

Reserved operator

Specialid 
IntLit

Integral numeric literal

FloatLit

Fractional numeric literal

CharLit

Character literal

StringLit

String literal

QQuote

Quasi quote: [|text|stuff|]

Qvarid

Qualified variable

Qconid

Qualified constructor

Qvarsym

Qualified variable operator

Qconsym

Qualified constructor operator

Special 
Whitespace

White space

NestedCommentStart

Internal: causes a call to an external function

NestedComment

A nested comment ({- ... -})

LiterateComment

Not handled by the lexer

Commentstart

Dashes

Comment

The stuff after the dashes

ErrorToken 
GotEOF 
TheRest 
ModuleName 
ModuleAlias

recognized in a later pass

Layout

for implicit braces

Indent Int

<n>, to preceed first token on each line

Open Int

{n}, after let, where, do or of, if not followed by a "{"

Instances
Eq Token Source # 
Instance details

Defined in Language.Haskell.Lexer.Tokens

Methods

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

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

Ord Token Source # 
Instance details

Defined in Language.Haskell.Lexer.Tokens

Methods

compare :: Token -> Token -> Ordering #

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

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

(>) :: Token -> Token -> Bool #

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

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

Show Token Source # 
Instance details

Defined in Language.Haskell.Lexer.Tokens

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

lexerPass0 :: String -> [PosToken] Source #

Tokenize and add position information. Preserves white space, and does not insert extra tokens due to layout.

lexerPass0' :: Pos -> String -> [PosToken] Source #

Same as lexerPass0, except that it uses the given start position.

lexerPass1 :: String -> [PosToken] Source #

The function lexerPass1 handles the part of lexical analysis that can be done independently of the parser---the tokenization and the addition of the extra layout tokens <n> and {n}, as specified in section 9.3 of the revised Haskell 98 Report.

rmSpace :: [PosToken] -> [PosToken] Source #

Remove token that are not meaningful (e.g., white space and comments).

layoutPre :: [PosToken] -> [PosToken] Source #

This is an implementation of Haskell layout, as specified in section 9.3 of the revised Haskell 98 report. This preprocessor inserts the extra <n> and {n} tokens.

data Pos Source #

The posisiotn within a file.

Constructors

Pos 

Fields

Instances
Eq Pos Source # 
Instance details

Defined in Language.Haskell.Lexer.Position

Methods

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

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

Ord Pos Source # 
Instance details

Defined in Language.Haskell.Lexer.Position

Methods

compare :: Pos -> Pos -> Ordering #

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

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

(>) :: Pos -> Pos -> Bool #

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

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

Show Pos Source # 
Instance details

Defined in Language.Haskell.Lexer.Position

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

simpPos :: Pos -> (Int, Int) Source #

The line and column numbers of a position.

startPos :: Pos Source #

The first column is designated column 1, not 0.

nextPos :: Pos -> String -> Pos Source #

Advance position by a string.

nextPos1 :: Pos -> Char -> Pos Source #

Advance position by a single character.