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

Copyright(c) Niklas Broberg 2004-2009 (c) Michael Sloan 2013
LicenseBSD-style (see the file LICENSE.txt)
MaintainerNiklas Broberg, d00nibro@chalmers.se
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Language.Haskell.Exts.Parser

Contents

Description

Annotated parser for Haskell with extensions.

Synopsis

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.

Instances

Parseable (NonGreedy (ListOf (ModulePragma SrcSpanInfo))) Source # 
Parseable (NonGreedy (ModuleHeadAndImports SrcSpanInfo)) Source # 
Parseable (NonGreedy (PragmasAndModuleHead SrcSpanInfo)) Source # 
Parseable (NonGreedy (PragmasAndModuleName SrcSpanInfo)) Source # 

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

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 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

newtype NonGreedy a Source #

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 PragmasAndModuleHead
ParseOk (NonGreedy {unNonGreedy = PragmasAndModuleHead [] (ModuleName "A",Nothing,Nothing)})

(this example uses the simplified AST)

Constructors

NonGreedy 

Fields

Instances

Functor NonGreedy Source # 

Methods

fmap :: (a -> b) -> NonGreedy a -> NonGreedy b #

(<$) :: a -> NonGreedy b -> NonGreedy a #

Eq a => Eq (NonGreedy a) Source # 

Methods

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

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

Data a => Data (NonGreedy a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonGreedy a -> c (NonGreedy a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonGreedy a) #

toConstr :: NonGreedy a -> Constr #

dataTypeOf :: NonGreedy a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (NonGreedy a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonGreedy a)) #

gmapT :: (forall b. Data b => b -> b) -> NonGreedy a -> NonGreedy a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonGreedy a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonGreedy a -> r #

gmapQ :: (forall d. Data d => d -> u) -> NonGreedy a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NonGreedy a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonGreedy a -> m (NonGreedy a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonGreedy a -> m (NonGreedy a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonGreedy a -> m (NonGreedy a) #

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 # 

data ListOf a 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] 

Instances

Functor ListOf Source # 

Methods

fmap :: (a -> b) -> ListOf a -> ListOf b #

(<$) :: a -> ListOf b -> ListOf a #

Eq a => Eq (ListOf a) Source # 

Methods

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

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

Data a => Data (ListOf a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ListOf a -> c (ListOf a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ListOf a) #

toConstr :: ListOf a -> Constr #

dataTypeOf :: ListOf a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ListOf a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ListOf a)) #

gmapT :: (forall b. Data b => b -> b) -> ListOf a -> ListOf a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ListOf a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ListOf a -> r #

gmapQ :: (forall d. Data d => d -> u) -> ListOf a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ListOf a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ListOf a -> m (ListOf a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ListOf a -> m (ListOf a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListOf a -> m (ListOf a) #

Ord a => Ord (ListOf a) Source # 

Methods

compare :: ListOf a -> ListOf a -> Ordering #

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

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

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

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

max :: ListOf a -> ListOf a -> ListOf a #

min :: ListOf a -> ListOf a -> ListOf a #

Show a => Show (ListOf a) Source # 

Methods

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

show :: ListOf a -> String #

showList :: [ListOf a] -> ShowS #

Parseable (NonGreedy (ListOf (ModulePragma SrcSpanInfo))) Source # 

unListOf :: ListOf a -> [a] Source #

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.

Instances

Eq l => Eq (PragmasAndModuleName l) Source # 
Data l => Data (PragmasAndModuleName l) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PragmasAndModuleName l -> c (PragmasAndModuleName l) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PragmasAndModuleName l) #

toConstr :: PragmasAndModuleName l -> Constr #

dataTypeOf :: PragmasAndModuleName l -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (PragmasAndModuleName l)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PragmasAndModuleName l)) #

gmapT :: (forall b. Data b => b -> b) -> PragmasAndModuleName l -> PragmasAndModuleName l #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PragmasAndModuleName l -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PragmasAndModuleName l -> r #

gmapQ :: (forall d. Data d => d -> u) -> PragmasAndModuleName l -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PragmasAndModuleName l -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PragmasAndModuleName l -> m (PragmasAndModuleName l) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PragmasAndModuleName l -> m (PragmasAndModuleName l) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PragmasAndModuleName l -> m (PragmasAndModuleName l) #

Ord l => Ord (PragmasAndModuleName l) Source # 
Show l => Show (PragmasAndModuleName l) Source # 
Parseable (NonGreedy (PragmasAndModuleName SrcSpanInfo)) Source # 

data PragmasAndModuleHead l Source #

Instances

Eq l => Eq (PragmasAndModuleHead l) Source # 
Data l => Data (PragmasAndModuleHead l) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PragmasAndModuleHead l -> c (PragmasAndModuleHead l) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (PragmasAndModuleHead l) #

toConstr :: PragmasAndModuleHead l -> Constr #

dataTypeOf :: PragmasAndModuleHead l -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (PragmasAndModuleHead l)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (PragmasAndModuleHead l)) #

gmapT :: (forall b. Data b => b -> b) -> PragmasAndModuleHead l -> PragmasAndModuleHead l #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PragmasAndModuleHead l -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PragmasAndModuleHead l -> r #

gmapQ :: (forall d. Data d => d -> u) -> PragmasAndModuleHead l -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PragmasAndModuleHead l -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PragmasAndModuleHead l -> m (PragmasAndModuleHead l) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PragmasAndModuleHead l -> m (PragmasAndModuleHead l) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PragmasAndModuleHead l -> m (PragmasAndModuleHead l) #

Ord l => Ord (PragmasAndModuleHead l) Source # 
Show l => Show (PragmasAndModuleHead l) Source # 
Parseable (NonGreedy (PragmasAndModuleHead SrcSpanInfo)) Source # 

data ModuleHeadAndImports l Source #

Instances

Eq l => Eq (ModuleHeadAndImports l) Source # 
Data l => Data (ModuleHeadAndImports l) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleHeadAndImports l -> c (ModuleHeadAndImports l) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ModuleHeadAndImports l) #

toConstr :: ModuleHeadAndImports l -> Constr #

dataTypeOf :: ModuleHeadAndImports l -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ModuleHeadAndImports l)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ModuleHeadAndImports l)) #

gmapT :: (forall b. Data b => b -> b) -> ModuleHeadAndImports l -> ModuleHeadAndImports l #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleHeadAndImports l -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleHeadAndImports l -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleHeadAndImports l -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleHeadAndImports l -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleHeadAndImports l -> m (ModuleHeadAndImports l) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleHeadAndImports l -> m (ModuleHeadAndImports l) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleHeadAndImports l -> m (ModuleHeadAndImports l) #

Ord l => Ord (ModuleHeadAndImports l) Source # 
Show l => Show (ModuleHeadAndImports l) Source # 
Parseable (NonGreedy (ModuleHeadAndImports SrcSpanInfo)) Source # 

Orphan instances

Parseable (Stmt SrcSpanInfo) Source # 
Parseable (Pat SrcSpanInfo) Source # 
Parseable (Exp SrcSpanInfo) Source # 
Parseable (Type SrcSpanInfo) Source # 
Parseable (Decl SrcSpanInfo) Source # 
Parseable (ImportDecl SrcSpanInfo) Source # 
Parseable (Module SrcSpanInfo) Source #