| Copyright | (c) Niklas Broberg 2004-2009 (c) Michael Sloan 2013 | 
|---|---|
| License | BSD-style (see the file LICENSE.txt) | 
| Maintainer | Niklas Broberg, d00nibro@chalmers.se | 
| Stability | stable | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Language.Haskell.Exts.Parser
Contents
Description
Annotated parser for Haskell with extensions.
- class Parseable ast where
- data ParseMode = ParseMode {}
- defaultParseMode :: ParseMode
- data ParseResult a- = ParseOk a
- | ParseFailed SrcLoc String
 
- fromParseResult :: ParseResult a -> a
- parseModule :: String -> ParseResult (Module SrcSpanInfo)
- parseModuleWithMode :: ParseMode -> String -> ParseResult (Module SrcSpanInfo)
- parseModuleWithComments :: ParseMode -> String -> ParseResult (Module SrcSpanInfo, [Comment])
- parseExp :: String -> ParseResult (Exp SrcSpanInfo)
- parseExpWithMode :: ParseMode -> String -> ParseResult (Exp SrcSpanInfo)
- parseExpWithComments :: ParseMode -> String -> ParseResult (Exp SrcSpanInfo, [Comment])
- parseStmt :: String -> ParseResult (Stmt SrcSpanInfo)
- parseStmtWithMode :: ParseMode -> String -> ParseResult (Stmt SrcSpanInfo)
- parseStmtWithComments :: ParseMode -> String -> ParseResult (Stmt SrcSpanInfo, [Comment])
- parsePat :: String -> ParseResult (Pat SrcSpanInfo)
- parsePatWithMode :: ParseMode -> String -> ParseResult (Pat SrcSpanInfo)
- parsePatWithComments :: ParseMode -> String -> ParseResult (Pat SrcSpanInfo, [Comment])
- parseDecl :: String -> ParseResult (Decl SrcSpanInfo)
- parseDeclWithMode :: ParseMode -> String -> ParseResult (Decl SrcSpanInfo)
- parseDeclWithComments :: ParseMode -> String -> ParseResult (Decl SrcSpanInfo, [Comment])
- parseType :: String -> ParseResult (Type SrcSpanInfo)
- parseTypeWithMode :: ParseMode -> String -> ParseResult (Type SrcSpanInfo)
- parseTypeWithComments :: ParseMode -> String -> ParseResult (Type SrcSpanInfo, [Comment])
- parseImportDecl :: String -> ParseResult (ImportDecl SrcSpanInfo)
- parseImportDeclWithMode :: ParseMode -> String -> ParseResult (ImportDecl SrcSpanInfo)
- parseImportDeclWithComments :: ParseMode -> String -> ParseResult (ImportDecl SrcSpanInfo, [Comment])
- newtype NonGreedy a = NonGreedy {- unNonGreedy :: a
 
- data ListOf a = ListOf SrcSpanInfo [a]
- unListOf :: ListOf a -> [a]
- getTopPragmas :: String -> ParseResult [ModulePragma SrcSpanInfo]
- data PragmasAndModuleName l = PragmasAndModuleName l [ModulePragma l] (Maybe (ModuleName l))
- data PragmasAndModuleHead l = PragmasAndModuleHead l [ModulePragma l] (Maybe (ModuleHead l))
- data ModuleHeadAndImports l = ModuleHeadAndImports l [ModulePragma l] (Maybe (ModuleHead l)) [ImportDecl l]
General parsing
class Parseable ast where Source #
Class providing function for parsing at many different types.
Note that for convenience of implementation, the default methods have
   definitions equivalent to undefined.  The minimal definition is all of
   the visible methods.
Minimal complete definition
parser
Methods
parse :: String -> ParseResult ast Source #
Parse a string with default mode.
parseWithMode :: ParseMode -> String -> ParseResult ast Source #
Parse a string with an explicit ParseMode.
parseWithComments :: ParseMode -> String -> ParseResult (ast, [Comment]) Source #
Parse a string with an explicit ParseMode, returning all comments along
   with the AST.
Static parameters governing a parse.
   Note that the various parse functions in Language.Haskell.Exts.Parser
   never look at LANGUAGE pragmas, regardless of
   what the ignoreLanguagePragmas flag is set to.
   Only the various parseFile functions in Language.Haskell.Exts will
   act on it, when set to False.
Constructors
| ParseMode | |
| Fields 
 | |
defaultParseMode :: ParseMode Source #
Default parameters for a parse.
   The default is an unknown filename,
   no extensions (i.e. Haskell 98),
   don't ignore LANGUAGE pragmas, do ignore LINE pragmas,
   and be aware of fixities from the Prelude.
data ParseResult a Source #
The result of a parse.
Constructors
| ParseOk a | The parse succeeded, yielding a value. | 
| ParseFailed SrcLoc String | The parse failed at the specified source location, with an error message. | 
Instances
| Monad ParseResult Source # | |
| Functor ParseResult Source # | |
| Applicative ParseResult Source # | |
| Show a => Show (ParseResult a) Source # | |
| Monoid m => Monoid (ParseResult m) Source # | |
fromParseResult :: ParseResult a -> a Source #
Retrieve the result of a successful parse, throwing an error if the parse is actually not successful.
Parsing of specific AST elements
Modules
parseModule :: String -> ParseResult (Module SrcSpanInfo) Source #
Parse of a string, which should contain a complete Haskell module, using defaultParseMode.
parseModuleWithMode :: ParseMode -> String -> ParseResult (Module SrcSpanInfo) Source #
Parse of a string containing a complete Haskell module, using an explicit ParseMode.
parseModuleWithComments :: ParseMode -> String -> ParseResult (Module SrcSpanInfo, [Comment]) Source #
Parse of a string containing a complete Haskell module, using an explicit ParseMode, retaining comments.
Expressions
parseExp :: String -> ParseResult (Exp SrcSpanInfo) Source #
Parse of a string containing a Haskell expression, using defaultParseMode.
parseExpWithMode :: ParseMode -> String -> ParseResult (Exp SrcSpanInfo) Source #
Parse of a string containing a Haskell expression, using an explicit ParseMode.
parseExpWithComments :: ParseMode -> String -> ParseResult (Exp SrcSpanInfo, [Comment]) Source #
Parse of a string containing a complete Haskell module, using an explicit ParseMode, retaining comments.
Statements
parseStmt :: String -> ParseResult (Stmt SrcSpanInfo) Source #
Parse of a string containing a Haskell statement, using defaultParseMode.
parseStmtWithMode :: ParseMode -> String -> ParseResult (Stmt SrcSpanInfo) Source #
Parse of a string containing a Haskell type, using an explicit ParseMode.
parseStmtWithComments :: ParseMode -> String -> ParseResult (Stmt SrcSpanInfo, [Comment]) Source #
Parse of a string containing a complete Haskell module, using an explicit ParseMode, retaining comments.
Patterns
parsePat :: String -> ParseResult (Pat SrcSpanInfo) Source #
Parse of a string containing a Haskell pattern, using defaultParseMode.
parsePatWithMode :: ParseMode -> String -> ParseResult (Pat SrcSpanInfo) Source #
Parse of a string containing a Haskell pattern, using an explicit ParseMode.
parsePatWithComments :: ParseMode -> String -> ParseResult (Pat SrcSpanInfo, [Comment]) Source #
Parse of a string containing a complete Haskell module, using an explicit ParseMode, retaining comments.
Declarations
parseDecl :: String -> ParseResult (Decl SrcSpanInfo) Source #
Parse of a string containing a Haskell top-level declaration, using defaultParseMode.
parseDeclWithMode :: ParseMode -> String -> ParseResult (Decl SrcSpanInfo) Source #
Parse of a string containing a Haskell top-level declaration, using an explicit ParseMode.
parseDeclWithComments :: ParseMode -> String -> ParseResult (Decl SrcSpanInfo, [Comment]) Source #
Parse of a string containing a complete Haskell module, using an explicit ParseMode, retaining comments.
Types
parseType :: String -> ParseResult (Type SrcSpanInfo) Source #
Parse of a string containing a Haskell type, using defaultParseMode.
parseTypeWithMode :: ParseMode -> String -> ParseResult (Type SrcSpanInfo) Source #
Parse of a string containing a Haskell type, using an explicit ParseMode.
parseTypeWithComments :: ParseMode -> String -> ParseResult (Type SrcSpanInfo, [Comment]) Source #
Parse of a string containing a complete Haskell module, using an explicit ParseMode, retaining comments.
Imports
parseImportDecl :: String -> ParseResult (ImportDecl SrcSpanInfo) Source #
Parse of a string containing a Haskell statement, using defaultParseMode.
parseImportDeclWithMode :: ParseMode -> String -> ParseResult (ImportDecl SrcSpanInfo) Source #
Parse of a string containing a Haskell type, using an explicit ParseMode.
parseImportDeclWithComments :: ParseMode -> String -> ParseResult (ImportDecl SrcSpanInfo, [Comment]) Source #
Parse of a string containing a complete Haskell module, using an explicit ParseMode, retaining comments.
Non-greedy parsers
Instances of Parseable for NonGreedy a will only consume the input
   until a is fully parsed.  This means that parse errors that come later
   in the input will be ignored.  It's also more efficient, as it's fully lazy
   in the remainder of the input:
>>>parse (unlines ("module A where" : "main =" : repeat "blah")) :: ParseResult PragmasAndModuleHeadParseOk (NonGreedy {unNonGreedy = PragmasAndModuleHead [] (ModuleName "A",Nothing,Nothing)})
(this example uses the simplified AST)
Constructors
| NonGreedy | |
| Fields 
 | |
Instances
| Functor NonGreedy Source # | |
| Eq a => Eq (NonGreedy a) Source # | |
| Data a => Data (NonGreedy a) Source # | |
| Ord a => Ord (NonGreedy a) Source # | |
| Show a => Show (NonGreedy a) Source # | |
| Parseable (NonGreedy (ListOf (ModulePragma SrcSpanInfo))) Source # | |
| Parseable (NonGreedy (ModuleHeadAndImports SrcSpanInfo)) Source # | |
| Parseable (NonGreedy (PragmasAndModuleHead SrcSpanInfo)) Source # | |
| Parseable (NonGreedy (PragmasAndModuleName SrcSpanInfo)) Source # | |
ListOf a stores lists of the AST type a, along with a SrcSpanInfo,
   in order to provide Parseable instances for lists.  These instances are
   provided when the type is used as a list in the syntax, and the same
   delimiters are used in all of its usages. Some exceptions are made:
Constructors
| ListOf SrcSpanInfo [a] | 
Module head parsers
getTopPragmas :: String -> ParseResult [ModulePragma SrcSpanInfo] Source #
Non-greedy parse of a string starting with a series of top-level option pragmas.
data PragmasAndModuleName l Source #
Type intended to be used with Parseable, with instances that implement a
   non-greedy parse of the module name, including top-level pragmas.  This
   means that a parse error that comes after the module header won't be
   returned. If the Maybe value is Nothing, then this means that there was
   no module header.
Constructors
| PragmasAndModuleName l [ModulePragma l] (Maybe (ModuleName l)) | 
Instances
| Eq l => Eq (PragmasAndModuleName l) Source # | |
| Data l => Data (PragmasAndModuleName l) Source # | |
| Ord l => Ord (PragmasAndModuleName l) Source # | |
| Show l => Show (PragmasAndModuleName l) Source # | |
| Parseable (NonGreedy (PragmasAndModuleName SrcSpanInfo)) Source # | |
data PragmasAndModuleHead l Source #
Constructors
| PragmasAndModuleHead l [ModulePragma l] (Maybe (ModuleHead l)) | 
Instances
| Eq l => Eq (PragmasAndModuleHead l) Source # | |
| Data l => Data (PragmasAndModuleHead l) Source # | |
| Ord l => Ord (PragmasAndModuleHead l) Source # | |
| Show l => Show (PragmasAndModuleHead l) Source # | |
| Parseable (NonGreedy (PragmasAndModuleHead SrcSpanInfo)) Source # | |
data ModuleHeadAndImports l Source #
Constructors
| ModuleHeadAndImports l [ModulePragma l] (Maybe (ModuleHead l)) [ImportDecl l] | 
Instances
| Eq l => Eq (ModuleHeadAndImports l) Source # | |
| Data l => Data (ModuleHeadAndImports l) Source # | |
| Ord l => Ord (ModuleHeadAndImports l) Source # | |
| Show l => Show (ModuleHeadAndImports l) Source # | |
| Parseable (NonGreedy (ModuleHeadAndImports SrcSpanInfo)) Source # | |