{-# LANGUAGE CPP, DeriveDataTypeable, FlexibleInstances, DeriveFunctor #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Language.Haskell.Exts.Parser
(
Parseable(parse, parseWithMode, parseWithComments)
, ParseMode(..), defaultParseMode, ParseResult(..), fromParseResult
, parseModule, parseModuleWithMode, parseModuleWithComments
, parseExp, parseExpWithMode, parseExpWithComments
, parseStmt, parseStmtWithMode, parseStmtWithComments
, parsePat, parsePatWithMode, parsePatWithComments
, parseDecl, parseDeclWithMode, parseDeclWithComments
, parseType, parseTypeWithMode, parseTypeWithComments
, parseImportDecl, parseImportDeclWithMode, parseImportDeclWithComments
, NonGreedy(..)
, ListOf(..), unListOf
, getTopPragmas
, PragmasAndModuleName(..)
, PragmasAndModuleHead(..)
, ModuleHeadAndImports(..)
) where
import Data.Data hiding (Fixity)
import Language.Haskell.Exts.Fixity
import Language.Haskell.Exts.Syntax
import Language.Haskell.Exts.Comments
import Language.Haskell.Exts.InternalParser
import Language.Haskell.Exts.ParseMonad
import Language.Haskell.Exts.SrcLoc
instance Parseable (Decl SrcSpanInfo) where parser = normalParser mparseDecl
instance Parseable (Exp SrcSpanInfo) where parser = normalParser mparseExp
instance Parseable (Module SrcSpanInfo) where parser = normalParser mparseModule
instance Parseable (Pat SrcSpanInfo) where parser = normalParser mparsePat
instance Parseable (Stmt SrcSpanInfo) where parser = normalParser mparseStmt
instance Parseable (Type SrcSpanInfo) where parser = normalParserNoFixity mparseType
instance Parseable (ImportDecl SrcSpanInfo) where parser = normalParserNoFixity mparseImportDecl
normalParser :: AppFixity a => P (a SrcSpanInfo) -> Maybe [Fixity] -> P (a SrcSpanInfo)
normalParser p Nothing = p
normalParser p (Just fixs) = p >>= \ast -> applyFixities fixs ast `atSrcLoc` noLoc
normalParserNoFixity :: P (a SrcSpanInfo) -> Maybe [Fixity] -> P (a SrcSpanInfo)
normalParserNoFixity p _ = p
parseModule :: String -> ParseResult (Module SrcSpanInfo)
parseModule = parse
parseModuleWithMode :: ParseMode -> String -> ParseResult (Module SrcSpanInfo)
parseModuleWithMode = parseWithMode
parseModuleWithComments :: ParseMode -> String -> ParseResult (Module SrcSpanInfo, [Comment])
parseModuleWithComments = parseWithComments
parseExp :: String -> ParseResult (Exp SrcSpanInfo)
parseExp = parse
parseExpWithMode :: ParseMode -> String -> ParseResult (Exp SrcSpanInfo)
parseExpWithMode = parseWithMode
parseExpWithComments :: ParseMode -> String -> ParseResult (Exp SrcSpanInfo, [Comment])
parseExpWithComments = parseWithComments
parsePat :: String -> ParseResult (Pat SrcSpanInfo)
parsePat = parse
parsePatWithMode :: ParseMode -> String -> ParseResult (Pat SrcSpanInfo)
parsePatWithMode = parseWithMode
parsePatWithComments :: ParseMode -> String -> ParseResult (Pat SrcSpanInfo, [Comment])
parsePatWithComments = parseWithComments
parseDecl :: String -> ParseResult (Decl SrcSpanInfo)
parseDecl = parse
parseDeclWithMode :: ParseMode -> String -> ParseResult (Decl SrcSpanInfo)
parseDeclWithMode = parseWithMode
parseDeclWithComments :: ParseMode -> String -> ParseResult (Decl SrcSpanInfo, [Comment])
parseDeclWithComments = parseWithComments
parseType :: String -> ParseResult (Type SrcSpanInfo)
parseType = parse
parseTypeWithMode :: ParseMode -> String -> ParseResult (Type SrcSpanInfo)
parseTypeWithMode = parseWithMode
parseTypeWithComments :: ParseMode -> String -> ParseResult (Type SrcSpanInfo, [Comment])
parseTypeWithComments = parseWithComments
parseStmt :: String -> ParseResult (Stmt SrcSpanInfo)
parseStmt = parse
parseStmtWithMode :: ParseMode -> String -> ParseResult (Stmt SrcSpanInfo)
parseStmtWithMode = parseWithMode
parseStmtWithComments :: ParseMode -> String -> ParseResult (Stmt SrcSpanInfo, [Comment])
parseStmtWithComments = parseWithComments
parseImportDecl :: String -> ParseResult (ImportDecl SrcSpanInfo)
parseImportDecl = parse
parseImportDeclWithMode :: ParseMode -> String -> ParseResult (ImportDecl SrcSpanInfo)
parseImportDeclWithMode = parseWithMode
parseImportDeclWithComments :: ParseMode -> String -> ParseResult (ImportDecl SrcSpanInfo, [Comment])
parseImportDeclWithComments = parseWithComments
getTopPragmas :: String -> ParseResult [ModulePragma SrcSpanInfo]
getTopPragmas = fmap (unListOf . unNonGreedy) . parse
instance Parseable (NonGreedy (ListOf (ModulePragma SrcSpanInfo))) where
parser = nglistParserNoFixity ngparseModulePragmas
nglistParserNoFixity :: P ([a SrcSpanInfo], [SrcSpan], SrcSpanInfo) -> Maybe [Fixity] -> P (NonGreedy (ListOf (a SrcSpanInfo)))
nglistParserNoFixity f = fmap (NonGreedy . toListOf) . normalParserNoFixity f
data PragmasAndModuleName l = PragmasAndModuleName l
[ModulePragma l]
(Maybe (ModuleName l))
deriving (Eq,Ord,Show,Typeable,Data)
instance Parseable (NonGreedy (PragmasAndModuleName SrcSpanInfo)) where
parser _ = do
((pragmas, pss, pl), mn) <- ngparsePragmasAndModuleName
let l = combSpanMaybe (pl <** pss) (fmap ann mn)
return $ NonGreedy $ PragmasAndModuleName l pragmas mn
data PragmasAndModuleHead l = PragmasAndModuleHead l
[ModulePragma l]
(Maybe (ModuleHead l))
deriving (Eq,Ord,Show,Typeable,Data)
instance Parseable (NonGreedy (PragmasAndModuleHead SrcSpanInfo)) where
parser _ = do
((pragmas, pss, pl), mh) <- ngparsePragmasAndModuleHead
let l = combSpanMaybe (pl <** pss) (fmap ann mh)
return $ NonGreedy $ PragmasAndModuleHead l pragmas mh
data ModuleHeadAndImports l = ModuleHeadAndImports l
[ModulePragma l]
(Maybe (ModuleHead l))
[ImportDecl l]
deriving (Eq,Ord,Show,Typeable,Data)
instance Parseable (NonGreedy (ModuleHeadAndImports SrcSpanInfo)) where
parser _ = do
((pragmas, pss, pl), mh, mimps) <- ngparseModuleHeadAndImports
let l = (pl <** pss) `combSpanMaybe`
(fmap ann mh) `combSpanMaybe`
(fmap (\(_, iss, il) -> il <** iss) mimps)
imps = maybe [] (\(x, _, _) -> x) mimps
return $ NonGreedy $ ModuleHeadAndImports l pragmas mh imps
newtype NonGreedy a = NonGreedy { unNonGreedy :: a }
deriving (Eq,Ord,Show,Typeable,Data)
instance Functor NonGreedy where
fmap f (NonGreedy x) = NonGreedy (f x)
data ListOf a = ListOf SrcSpanInfo [a]
deriving (Eq,Ord,Show,Typeable,Data,Functor)
unListOf :: ListOf a -> [a]
unListOf (ListOf _ xs) = xs
toListOf :: ([a], [SrcSpan], SrcSpanInfo) -> ListOf a
toListOf (xs, ss, l) = ListOf (infoSpan (srcInfoSpan l) ss) xs