haskell-src-exts-1.16.0.1: 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 HaskellNone
LanguageHaskell98

Language.Haskell.Exts.Parser

Contents

Description

Parser for Haskell with extensions.

Synopsis

General parsing

class Parseable ast where Source

Class to reuse the parse function at many different types.

Methods

parse :: String -> ParseResult ast Source

Parse a string with default mode.

parseWithMode :: ParseMode -> String -> ParseResult ast Source

Parse a string with an explicit mode.

parseWithComments :: ParseMode -> String -> ParseResult (ast, [Comment]) Source

Parse a string with an explicit mode, returning all comments along the AST

Instances

data ParseMode Source

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

parseFilename :: String

original name of the file being parsed

baseLanguage :: Language

base language (e.g. Haskell98, Haskell2010)

extensions :: [Extension]

list of extensions enabled for parsing

ignoreLanguagePragmas :: Bool

if True, the parser won't care about further extensions in LANGUAGE pragmas in source files

ignoreLinePragmas :: Bool

if True, the parser won't read line position information from LINE pragmas in source files

fixities :: Maybe [Fixity]

list of fixities to be aware of

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.

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 Source

Parse of a string, which should contain a complete Haskell module.

parseModuleWithMode :: ParseMode -> String -> ParseResult Module Source

Parse of a string containing a complete Haskell module, using an explicit mode.

parseModuleWithComments :: ParseMode -> String -> ParseResult (Module, [Comment]) Source

Parse of a string containing a complete Haskell module, using an explicit mode, retaining comments.

Expressions

parseExp :: String -> ParseResult Exp Source

Parse of a string containing a Haskell expression.

parseExpWithMode :: ParseMode -> String -> ParseResult Exp Source

Parse of a string containing a Haskell expression, using an explicit mode.

parseExpWithComments :: ParseMode -> String -> ParseResult (Exp, [Comment]) Source

Parse of a string containing a complete Haskell module, using an explicit mode, retaining comments.

Statements

parseStmt :: String -> ParseResult Stmt Source

Parse of a string containing a Haskell type.

parseStmtWithMode :: ParseMode -> String -> ParseResult Stmt Source

Parse of a string containing a Haskell type, using an explicit mode.

parseStmtWithComments :: ParseMode -> String -> ParseResult (Stmt, [Comment]) Source

Parse of a string containing a complete Haskell module, using an explicit mode, retaining comments.

Patterns

parsePat :: String -> ParseResult Pat Source

Parse of a string containing a Haskell pattern.

parsePatWithMode :: ParseMode -> String -> ParseResult Pat Source

Parse of a string containing a Haskell pattern, using an explicit mode.

parsePatWithComments :: ParseMode -> String -> ParseResult (Pat, [Comment]) Source

Parse of a string containing a complete Haskell module, using an explicit mode, retaining comments.

Declarations

parseDecl :: String -> ParseResult Decl Source

Parse of a string containing a Haskell top-level declaration.

parseDeclWithMode :: ParseMode -> String -> ParseResult Decl Source

Parse of a string containing a Haskell top-level declaration, using an explicit mode.

parseDeclWithComments :: ParseMode -> String -> ParseResult (Decl, [Comment]) Source

Parse of a string containing a complete Haskell module, using an explicit mode, retaining comments.

Types

parseType :: String -> ParseResult Type Source

Parse of a string containing a Haskell type.

parseTypeWithMode :: ParseMode -> String -> ParseResult Type Source

Parse of a string containing a Haskell type, using an explicit mode.

parseTypeWithComments :: ParseMode -> String -> ParseResult (Type, [Comment]) Source

Parse of a string containing a complete Haskell module, using an explicit mode, retaining comments.

Option pragmas