{-# LANGUAGE CPP #-}
#include "ghclib_api.h"
module Language.Haskell.GhclibParserEx.GHC.Parser(
    parseFile
  , parseModule
  , parseSignature
  , parseImport
  , parseStatement
  , parseBackpack
  , parseDeclaration
  , parseExpression
  , parsePattern
  , parseTypeSignature
  , parseStmt
  , parseIdentifier
  , parseType
  , parseHeader
  , parse
  )
  where
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_904) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900) || defined (GHCLIB_API_810)
import GHC.Hs
#else
import HsSyn
#endif
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_904) || defined(GHCLIB_API_902)
#  if defined (GHCLIB_API_902)
import GHC.Driver.Config
#  endif
#  if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_904)
import GHC.Driver.Config.Parser
#  endif
#endif
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_904) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)
import GHC.Parser.PostProcess
import GHC.Driver.Session
import GHC.Data.StringBuffer
import GHC.Parser.Lexer
import qualified GHC.Parser.Lexer as Lexer
import qualified GHC.Parser as Parser
import GHC.Data.FastString
import GHC.Types.SrcLoc
import GHC.Driver.Backpack.Syntax
import GHC.Unit.Info
import GHC.Types.Name.Reader
#else
import DynFlags
import StringBuffer
import Lexer
import qualified Parser
import FastString
import SrcLoc
import BkpSyn
import PackageConfig
import RdrName
#endif
#if defined (GHCLIB_API_810)
import RdrHsSyn
#endif
parse :: P a -> String -> DynFlags -> ParseResult a
parse :: forall a. P a -> String -> DynFlags -> ParseResult a
parse P a
p String
str DynFlags
flags =
  forall a. P a -> PState -> ParseResult a
Lexer.unP P a
p PState
parseState
  where
    location :: RealSrcLoc
location = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (String -> FastString
mkFastString String
"<string>") Int
1 Int
1
    buffer :: StringBuffer
buffer = String -> StringBuffer
stringToStringBuffer String
str
    parseState :: PState
parseState =
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_904) || defined(GHCLIB_API_902)
      ParserOpts -> StringBuffer -> RealSrcLoc -> PState
initParserState (DynFlags -> ParserOpts
initParserOpts DynFlags
flags) StringBuffer
buffer RealSrcLoc
location
#else
      mkPState flags buffer location
#endif
#if defined (GHCLIB_API_904) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)
parseModule :: String -> DynFlags -> ParseResult (Located HsModule)
#else
parseModule :: String -> DynFlags -> ParseResult (Located (HsModule GhcPs))
#endif
parseModule :: String -> DynFlags -> ParseResult (Located (HsModule GhcPs))
parseModule = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (Located (HsModule GhcPs))
Parser.parseModule
#if defined (GHCLIB_API_904) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)
parseSignature :: String -> DynFlags -> ParseResult (Located HsModule)
#else
parseSignature :: String -> DynFlags -> ParseResult (Located (HsModule GhcPs))
#endif
parseSignature :: String -> DynFlags -> ParseResult (Located (HsModule GhcPs))
parseSignature = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (Located (HsModule GhcPs))
Parser.parseSignature
parseImport :: String -> DynFlags -> ParseResult (LImportDecl GhcPs)
parseImport :: String -> DynFlags -> ParseResult (LImportDecl GhcPs)
parseImport = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (GenLocated SrcSpanAnnA (ImportDecl GhcPs))
Parser.parseImport
parseStatement :: String -> DynFlags -> ParseResult (LStmt GhcPs (LHsExpr GhcPs))
parseStatement :: String -> DynFlags -> ParseResult (LStmt GhcPs (LHsExpr GhcPs))
parseStatement = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (GenLocated
     SrcSpanAnnA
     (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))))
Parser.parseStatement
parseBackpack :: String -> DynFlags -> ParseResult [LHsUnit PackageName]
parseBackpack :: String -> DynFlags -> ParseResult [LHsUnit PackageName]
parseBackpack = forall a. P a -> String -> DynFlags -> ParseResult a
parse P [LHsUnit PackageName]
Parser.parseBackpack
parseDeclaration :: String -> DynFlags -> ParseResult (LHsDecl GhcPs)
parseDeclaration :: String -> DynFlags -> ParseResult (LHsDecl GhcPs)
parseDeclaration = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (GenLocated SrcSpanAnnA (HsDecl GhcPs))
Parser.parseDeclaration
parseExpression :: String -> DynFlags -> ParseResult (LHsExpr GhcPs)
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_904) || defined(GHCLIB_API_902)
parseExpression :: String -> DynFlags -> ParseResult (LHsExpr GhcPs)
parseExpression String
s DynFlags
flags =
  
  
  case forall a. P a -> String -> DynFlags -> ParseResult a
parse P ECP
Parser.parseExpression String
s DynFlags
flags of
    POk PState
state ECP
e ->
      let e' :: ECP
e' = ECP
e :: ECP
          parser_validator :: PV (LHsExpr GhcPs)
parser_validator = ECP -> forall b. DisambECP b => PV (LocatedA b)
unECP ECP
e' :: PV (LHsExpr GhcPs)
          parser :: P (LHsExpr GhcPs)
parser = forall a. PV a -> P a
runPV PV (GenLocated SrcSpanAnnA (HsExpr GhcPs))
parser_validator :: P (LHsExpr GhcPs)
      in forall a. P a -> PState -> ParseResult a
unP P (GenLocated SrcSpanAnnA (HsExpr GhcPs))
parser PState
state :: ParseResult (LHsExpr GhcPs)
    PFailed PState
ps -> forall a. PState -> ParseResult a
PFailed PState
ps
#elif defined (GHCLIB_API_810) || defined (GHCLIB_API_900)
parseExpression s flags =
  case parse Parser.parseExpression s flags of
    POk s e -> unP (runECP_P e) s
    PFailed ps -> PFailed ps
#else
parseExpression = parse Parser.parseExpression
#endif
parsePattern :: String -> DynFlags -> ParseResult (LPat GhcPs)
parsePattern :: String -> DynFlags -> ParseResult (LPat GhcPs)
parsePattern = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (GenLocated SrcSpanAnnA (Pat GhcPs))
Parser.parsePattern
parseTypeSignature :: String -> DynFlags -> ParseResult (LHsDecl GhcPs)
parseTypeSignature :: String -> DynFlags -> ParseResult (LHsDecl GhcPs)
parseTypeSignature = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (GenLocated SrcSpanAnnA (HsDecl GhcPs))
Parser.parseTypeSignature
parseStmt :: String -> DynFlags -> ParseResult (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
parseStmt :: String
-> DynFlags -> ParseResult (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
parseStmt = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (Maybe
     (GenLocated
        SrcSpanAnnA
        (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs)))))
Parser.parseStmt
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_904) || defined (GHCLIB_API_902)
parseIdentifier :: String -> DynFlags -> ParseResult (LocatedN RdrName)
#else
parseIdentifier :: String -> DynFlags -> ParseResult (Located RdrName)
#endif
parseIdentifier :: String -> DynFlags -> ParseResult (LocatedN RdrName)
parseIdentifier = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (LocatedN RdrName)
Parser.parseIdentifier
parseType :: String -> DynFlags -> ParseResult (LHsType GhcPs)
parseType :: String -> DynFlags -> ParseResult (LHsType GhcPs)
parseType = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (GenLocated SrcSpanAnnA (HsType GhcPs))
Parser.parseType
#if defined (GHCLIB_API_904) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)
parseHeader :: String -> DynFlags -> ParseResult (Located HsModule)
#else
parseHeader :: String -> DynFlags -> ParseResult (Located (HsModule GhcPs))
#endif
 = forall a. P a -> String -> DynFlags -> ParseResult a
parse P (Located (HsModule GhcPs))
Parser.parseHeader
#if defined (GHCLIB_API_904) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)
parseFile :: String
          -> DynFlags
          -> String
          -> ParseResult (Located HsModule)
#else
parseFile :: String
          -> DynFlags
          -> String
          -> ParseResult (Located (HsModule GhcPs))
#endif
parseFile :: String
-> DynFlags -> String -> ParseResult (Located (HsModule GhcPs))
parseFile String
filename DynFlags
flags String
str =
  forall a. P a -> PState -> ParseResult a
unP P (Located (HsModule GhcPs))
Parser.parseModule PState
parseState
  where
    location :: RealSrcLoc
location = FastString -> Int -> Int -> RealSrcLoc
mkRealSrcLoc (String -> FastString
mkFastString String
filename) Int
1 Int
1
    buffer :: StringBuffer
buffer = String -> StringBuffer
stringToStringBuffer String
str
    parseState :: PState
parseState =
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_904) || defined(GHCLIB_API_902)
      ParserOpts -> StringBuffer -> RealSrcLoc -> PState
initParserState (DynFlags -> ParserOpts
initParserOpts DynFlags
flags) StringBuffer
buffer RealSrcLoc
location
#else
      mkPState flags buffer location
#endif