-- Copyright (c) 2020, Shayne Fletcher. All rights reserved.
-- SPDX-License-Identifier: BSD-3-Clause.

{-# 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_902) || defined (GHCLIB_API_900) || defined (GHCLIB_API_810)
import GHC.Hs
#else
import HsSyn
#endif
#if defined (GHCLIB_API_HEAD) || defined(GHCLIB_API_902)
#  if defined (GHCLIB_API_902)
import GHC.Driver.Config
#  endif
#  if defined (GHCLIB_API_HEAD)
import GHC.Driver.Config.Parser
#  endif
#endif
#if defined (GHCLIB_API_HEAD) || 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 :: P a -> String -> DynFlags -> ParseResult a
parse P a
p String
str DynFlags
flags =
  P a -> PState -> ParseResult a
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_902)
      initParserState (initParserOpts flags) buffer location
#else
      DynFlags -> StringBuffer -> RealSrcLoc -> PState
mkPState DynFlags
flags StringBuffer
buffer RealSrcLoc
location
#endif
#if defined (GHCLIB_API_HEAD) || 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)
parseModule = P (Located HsModule)
-> String -> DynFlags -> ParseResult (Located HsModule)
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (Located HsModule)
Parser.parseModule

#if defined (GHCLIB_API_HEAD) || 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)
parseSignature = P (Located HsModule)
-> String -> DynFlags -> ParseResult (Located HsModule)
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (Located HsModule)
Parser.parseSignature

parseImport :: String -> DynFlags -> ParseResult (LImportDecl GhcPs)
parseImport :: String -> DynFlags -> ParseResult (LImportDecl GhcPs)
parseImport = P (LImportDecl GhcPs)
-> String -> DynFlags -> ParseResult (LImportDecl GhcPs)
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (LImportDecl GhcPs)
Parser.parseImport

parseStatement :: String -> DynFlags -> ParseResult (LStmt GhcPs (LHsExpr GhcPs))
parseStatement :: String -> DynFlags -> ParseResult (LStmt GhcPs (LHsExpr GhcPs))
parseStatement = P (LStmt GhcPs (LHsExpr GhcPs))
-> String -> DynFlags -> ParseResult (LStmt GhcPs (LHsExpr GhcPs))
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (LStmt GhcPs (LHsExpr GhcPs))
Parser.parseStatement

parseBackpack :: String -> DynFlags -> ParseResult [LHsUnit PackageName]
parseBackpack :: String -> DynFlags -> ParseResult [LHsUnit PackageName]
parseBackpack = P [LHsUnit PackageName]
-> String -> DynFlags -> ParseResult [LHsUnit PackageName]
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 = P (LHsDecl GhcPs)
-> String -> DynFlags -> ParseResult (LHsDecl GhcPs)
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (LHsDecl GhcPs)
Parser.parseDeclaration

parseExpression :: String -> DynFlags -> ParseResult (LHsExpr GhcPs)
#if defined (GHCLIB_API_HEAD) || defined(GHCLIB_API_902)
parseExpression s flags =
  -- The need for annotations here came about first manifested with
  -- ghc-9.0.1
  case parse Parser.parseExpression s flags of
    POk state e ->
      let e' = e :: ECP
          parser_validator = unECP e' :: PV (LHsExpr GhcPs)
          parser = runPV parser_validator :: P (LHsExpr GhcPs)
      in unP parser state :: ParseResult (LHsExpr GhcPs)
    PFailed ps -> PFailed ps
#elif defined (GHCLIB_API_810) || defined (GHCLIB_API_900)
parseExpression :: String -> DynFlags -> ParseResult (LHsExpr GhcPs)
parseExpression String
s DynFlags
flags =
  case P ECP -> String -> DynFlags -> ParseResult ECP
forall a. P a -> String -> DynFlags -> ParseResult a
parse P ECP
Parser.parseExpression String
s DynFlags
flags of
    POk PState
s ECP
e -> P (LHsExpr GhcPs) -> PState -> ParseResult (LHsExpr GhcPs)
forall a. P a -> PState -> ParseResult a
unP (ECP -> P (LHsExpr GhcPs)
forall b. DisambECP b => ECP -> P (Located b)
runECP_P ECP
e) PState
s
    PFailed PState
ps -> PState -> ParseResult (LHsExpr GhcPs)
forall a. PState -> ParseResult a
PFailed PState
ps
#else
parseExpression = parse Parser.parseExpression
#endif

parsePattern :: String -> DynFlags -> ParseResult (LPat GhcPs)
parsePattern :: String -> DynFlags -> ParseResult (LPat GhcPs)
parsePattern = P (Located (Pat GhcPs))
-> String -> DynFlags -> ParseResult (Located (Pat GhcPs))
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (Located (Pat GhcPs))
Parser.parsePattern

parseTypeSignature :: String -> DynFlags -> ParseResult (LHsDecl GhcPs)
parseTypeSignature :: String -> DynFlags -> ParseResult (LHsDecl GhcPs)
parseTypeSignature = P (LHsDecl GhcPs)
-> String -> DynFlags -> ParseResult (LHsDecl GhcPs)
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (LHsDecl GhcPs)
Parser.parseTypeSignature

parseStmt :: String -> DynFlags -> ParseResult (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
parseStmt :: String
-> DynFlags -> ParseResult (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
parseStmt = P (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
-> String
-> DynFlags
-> ParseResult (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (Maybe (LStmt GhcPs (LHsExpr GhcPs)))
Parser.parseStmt

#if defined(GHCLIB_API_HEAD) || defined(GHCLIB_API_902)
parseIdentifier :: String -> DynFlags -> ParseResult (LocatedN RdrName)
#else
parseIdentifier :: String -> DynFlags -> ParseResult (Located RdrName)
#endif
parseIdentifier :: String -> DynFlags -> ParseResult (Located RdrName)
parseIdentifier = P (Located RdrName)
-> String -> DynFlags -> ParseResult (Located RdrName)
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (Located RdrName)
Parser.parseIdentifier

parseType :: String -> DynFlags -> ParseResult (LHsType GhcPs)
parseType :: String -> DynFlags -> ParseResult (LHsType GhcPs)
parseType = P (LHsType GhcPs)
-> String -> DynFlags -> ParseResult (LHsType GhcPs)
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (LHsType GhcPs)
Parser.parseType

#if defined (GHCLIB_API_HEAD) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)
parseHeader :: String -> DynFlags -> ParseResult (Located HsModule)
#else
parseHeader :: String -> DynFlags -> ParseResult (Located (HsModule GhcPs))
#endif
parseHeader :: String -> DynFlags -> ParseResult (Located HsModule)
parseHeader = P (Located HsModule)
-> String -> DynFlags -> ParseResult (Located HsModule)
forall a. P a -> String -> DynFlags -> ParseResult a
parse P (Located HsModule)
Parser.parseHeader

#if defined (GHCLIB_API_HEAD) || 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)
parseFile String
filename DynFlags
flags String
str =
  P (Located HsModule) -> PState -> ParseResult (Located HsModule)
forall a. P a -> PState -> ParseResult a
unP P (Located HsModule)
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_902)
      initParserState (initParserOpts flags) buffer location
#else
      DynFlags -> StringBuffer -> RealSrcLoc -> PState
mkPState DynFlags
flags StringBuffer
buffer RealSrcLoc
location
#endif