haskell-src-exts-1.22.0: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer

Copyright(c) The GHC Team 1997-2000
(c) Niklas Broberg 2004-2012
LicenseBSD-style (see the file LICENSE.txt)
MaintainerNiklas Broberg, niklas.broberg@chalmers.se
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Language.Haskell.Exts.Lexer

Description

Lexer for Haskell with extensions.

Synopsis

Documentation

lexTokenStream :: String -> ParseResult [Loc Token] Source #

Lex a string into a list of Haskell 2010 source tokens.

lexTokenStreamWithMode :: ParseMode -> String -> ParseResult [Loc Token] Source #

Lex a string into a list of Haskell source tokens, using an explicit mode.

data Token Source #

Constructors

VarId String 
LabelVarId String 
QVarId (String, String) 
IDupVarId String 
ILinVarId String 
ConId String 
QConId (String, String) 
DVarId [String] 
VarSym String 
ConSym String 
QVarSym (String, String) 
QConSym (String, String) 
IntTok (Integer, String) 
FloatTok (Rational, String) 
Character (Char, String) 
StringTok (String, String) 
IntTokHash (Integer, String) 
WordTokHash (Integer, String) 
FloatTokHash (Rational, String) 
DoubleTokHash (Rational, String) 
CharacterHash (Char, String) 
StringHash (String, String) 
LeftParen 
RightParen 
LeftHashParen 
RightHashParen 
SemiColon 
LeftCurly 
RightCurly 
VRightCurly 
LeftSquare 
RightSquare 
ParArrayLeftSquare 
ParArrayRightSquare 
Comma 
Underscore 
BackQuote 
Dot 
DotDot 
Colon 
QuoteColon 
DoubleColon 
Equals 
Backslash 
Bar 
LeftArrow 
RightArrow 
At 
TApp 
Tilde 
DoubleArrow 
Minus 
Exclamation 
Star 
LeftArrowTail 
RightArrowTail 
LeftDblArrowTail 
RightDblArrowTail 
THExpQuote 
THTExpQuote 
THPatQuote 
THDecQuote 
THTypQuote 
THCloseQuote 
THTCloseQuote

]

THIdEscape String

|]

THParenEscape 
THTIdEscape String 
THTParenEscape 
THVarQuote 
THTyQuote 
THQuasiQuote (String, String) 
RPGuardOpen 
RPGuardClose 
RPCAt

)

XCodeTagOpen 
XCodeTagClose 
XStdTagOpen 
XStdTagClose 
XCloseTagOpen 
XEmptyTagClose 
XChildTagOpen 
XPCDATA String 
XRPatOpen 
XRPatClose 
PragmaEnd 
RULES 
INLINE Bool 
INLINE_CONLIKE 
SPECIALISE 
SPECIALISE_INLINE Bool 
SOURCE 
DEPRECATED 
WARNING 
SCC 
GENERATED 
CORE 
UNPACK 
NOUNPACK 
OPTIONS (Maybe String, String) 
LANGUAGE 
ANN 
MINIMAL 
NO_OVERLAP 
OVERLAP 
OVERLAPPING 
OVERLAPPABLE 
OVERLAPS 
INCOHERENT 
COMPLETE 
KW_As 
KW_By 
KW_Case 
KW_Class 
KW_Data 
KW_Default 
KW_Deriving 
KW_Do 
KW_MDo 
KW_Else 
KW_Family 
KW_Forall 
KW_Group 
KW_Hiding 
KW_If 
KW_Import 
KW_In 
KW_Infix 
KW_InfixL 
KW_InfixR 
KW_Instance 
KW_Let 
KW_Module 
KW_NewType 
KW_Of 
KW_Proc 
KW_Rec 
KW_Role 
KW_Then 
KW_Type 
KW_Using 
KW_Where 
KW_Qualified 
KW_Pattern 
KW_Stock 
KW_Anyclass 
KW_Via 
KW_Foreign 
KW_Export 
KW_Safe 
KW_Unsafe 
KW_Threadsafe 
KW_Interruptible 
KW_StdCall 
KW_CCall 
KW_CPlusPlus 
KW_DotNet 
KW_Jvm 
KW_Js 
KW_JavaScript 
KW_CApi 
EOF 
Instances
Eq Token Source # 
Instance details

Defined in Language.Haskell.Exts.InternalLexer

Methods

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

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

Show Token Source # 
Instance details

Defined in Language.Haskell.Exts.InternalLexer

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

data Loc a Source #

An entity located in the source.

Constructors

Loc 

Fields

Instances
Eq a => Eq (Loc a) Source # 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Methods

(==) :: Loc a -> Loc a -> Bool #

(/=) :: Loc a -> Loc a -> Bool #

Ord a => Ord (Loc a) Source # 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Methods

compare :: Loc a -> Loc a -> Ordering #

(<) :: Loc a -> Loc a -> Bool #

(<=) :: Loc a -> Loc a -> Bool #

(>) :: Loc a -> Loc a -> Bool #

(>=) :: Loc a -> Loc a -> Bool #

max :: Loc a -> Loc a -> Loc a #

min :: Loc a -> Loc a -> Loc a #

Show a => Show (Loc a) Source # 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Methods

showsPrec :: Int -> Loc a -> ShowS #

show :: Loc a -> String #

showList :: [Loc a] -> ShowS #

Generic (Loc a) Source # 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep (Loc a) :: Type -> Type #

Methods

from :: Loc a -> Rep (Loc a) x #

to :: Rep (Loc a) x -> Loc a #

type Rep (Loc a) Source # 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

type Rep (Loc a) = D1 (MetaData "Loc" "Language.Haskell.Exts.SrcLoc" "haskell-src-exts-1.22.0-5tSwDhjCyZb5AQf9d2FsEo" False) (C1 (MetaCons "Loc" PrefixI True) (S1 (MetaSel (Just "loc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SrcSpan) :*: S1 (MetaSel (Just "unLoc") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))