Copyright | (c) Niklas Broberg 2004-2009 |
---|---|
License | BSD-style (see the file LICENSE.txt) |
Maintainer | Niklas Broberg, d00nibro@chalmers.se |
Stability | stable |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
An umbrella module for the various functionality of the package. Also provides some convenient functionality for dealing directly with source files.
Synopsis
- module Language.Haskell.Exts.Syntax
- module Language.Haskell.Exts.Build
- data Token
- = 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
- | OpenArrowBracket
- | CloseArrowBracket
- | 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
- lexTokenStream :: String -> ParseResult [Loc Token]
- lexTokenStreamWithMode :: ParseMode -> String -> ParseResult [Loc Token]
- module Language.Haskell.Exts.Pretty
- module Language.Haskell.Exts.Fixity
- module Language.Haskell.Exts.ExactPrint
- module Language.Haskell.Exts.SrcLoc
- module Language.Haskell.Exts.Comments
- module Language.Haskell.Exts.Extension
- module Language.Haskell.Exts.Parser
- parseFile :: FilePath -> IO (ParseResult (Module SrcSpanInfo))
- parseFileWithMode :: ParseMode -> FilePath -> IO (ParseResult (Module SrcSpanInfo))
- parseFileWithExts :: [Extension] -> FilePath -> IO (ParseResult (Module SrcSpanInfo))
- parseFileWithComments :: ParseMode -> FilePath -> IO (ParseResult (Module SrcSpanInfo, [Comment]))
- parseFileWithCommentsAndPragmas :: ParseMode -> FilePath -> IO (ParseResult (Module SrcSpanInfo, [Comment], [UnknownPragma]))
- parseFileContents :: String -> ParseResult (Module SrcSpanInfo)
- parseFileContentsWithMode :: ParseMode -> String -> ParseResult (Module SrcSpanInfo)
- parseFileContentsWithExts :: [Extension] -> String -> ParseResult (Module SrcSpanInfo)
- parseFileContentsWithComments :: ParseMode -> String -> ParseResult (Module SrcSpanInfo, [Comment])
- readExtensions :: String -> Maybe (Maybe Language, [Extension])
Re-exported modules
module Language.Haskell.Exts.Syntax
module Language.Haskell.Exts.Build
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.
module Language.Haskell.Exts.Pretty
module Language.Haskell.Exts.Fixity
module Language.Haskell.Exts.SrcLoc
module Language.Haskell.Exts.Parser
Parsing of Haskell source files
parseFile :: FilePath -> IO (ParseResult (Module SrcSpanInfo)) Source #
Parse a source file on disk, using the default parse mode.
parseFileWithMode :: ParseMode -> FilePath -> IO (ParseResult (Module SrcSpanInfo)) Source #
Parse a source file on disk, supplying a custom parse mode.
parseFileWithExts :: [Extension] -> FilePath -> IO (ParseResult (Module SrcSpanInfo)) Source #
Parse a source file on disk, with an extra set of extensions to know about on top of what the file itself declares.
parseFileWithComments :: ParseMode -> FilePath -> IO (ParseResult (Module SrcSpanInfo, [Comment])) Source #
parseFileWithCommentsAndPragmas :: ParseMode -> FilePath -> IO (ParseResult (Module SrcSpanInfo, [Comment], [UnknownPragma])) Source #
Parse a source file on disk, supplying a custom parse mode, and retaining comments as well as unknown pragmas.
parseFileContents :: String -> ParseResult (Module SrcSpanInfo) Source #
Parse a source file from a string using the default parse mode.
parseFileContentsWithMode :: ParseMode -> String -> ParseResult (Module SrcSpanInfo) Source #
Parse a source file from a string using a custom parse mode.
parseFileContentsWithExts :: [Extension] -> String -> ParseResult (Module SrcSpanInfo) Source #
Parse a source file from a string, with an extra set of extensions to know about on top of what the file itself declares.
parseFileContentsWithComments :: ParseMode -> String -> ParseResult (Module SrcSpanInfo, [Comment]) Source #