{-# LANGUAGE CPP #-}
{-# LANGUAGE ViewPatterns #-}
module PyF.Internal.Parser (parseExpression) where
#if MIN_VERSION_ghc(9,0,0)
import GHC.Parser.Lexer (ParseResult (..), PState (..))
#elif MIN_VERSION_ghc(8,10,0)
import Lexer (ParseResult (..), PState (..))
#else
import Lexer (ParseResult (..))
#endif
#if MIN_VERSION_ghc(9,2,0)
import qualified GHC.Parser.Errors.Ppr as ParserErrorPpr
#endif
#if MIN_VERSION_ghc(9,0,0)
import qualified GHC.Types.SrcLoc as SrcLoc
#else
import qualified SrcLoc
#endif
#if MIN_VERSION_ghc(9,0,0)
import GHC.Driver.Session (DynFlags)
#else
import DynFlags (DynFlags)
#endif
#if MIN_VERSION_ghc(8,10,0)
import GHC.Hs.Expr as Expr
import GHC.Hs.Extension as Ext
#else
import HsExpr as Expr
import HsExtension as Ext
import Outputable (showSDoc)
#endif
import qualified PyF.Internal.ParserEx as ParseExp
parseExpression :: String -> DynFlags -> Either (Int, Int, String) (HsExpr GhcPs)
parseExpression :: String -> DynFlags -> Either (Int, Int, String) (HsExpr GhcPs)
parseExpression String
s DynFlags
dynFlags =
case String -> DynFlags -> ParseResult (Located (HsExpr GhcPs))
ParseExp.parseExpression String
s DynFlags
dynFlags of
POk PState
_ Located (HsExpr GhcPs)
locatedExpr ->
let expr :: SrcSpanLess (Located (HsExpr GhcPs))
expr = Located (HsExpr GhcPs) -> SrcSpanLess (Located (HsExpr GhcPs))
forall a. HasSrcSpan a => a -> SrcSpanLess a
SrcLoc.unLoc Located (HsExpr GhcPs)
locatedExpr
in HsExpr GhcPs -> Either (Int, Int, String) (HsExpr GhcPs)
forall a b. b -> Either a b
Right
HsExpr GhcPs
expr
#if MIN_VERSION_ghc(9,2,0)
PFailed PState{loc=SrcLoc.psRealLoc -> srcLoc, errors=errorMessages} ->
#elif MIN_VERSION_ghc(9,0,0)
PFailed PState{loc=SrcLoc.psRealLoc -> srcLoc, messages=msgs} ->
#elif MIN_VERSION_ghc(8,10,0)
PFailed PState{loc :: PState -> RealSrcLoc
loc=RealSrcLoc
srcLoc, messages :: PState -> DynFlags -> Messages
messages=DynFlags -> Messages
msgs} ->
#else
PFailed _ (SrcLoc.srcSpanEnd -> SrcLoc.RealSrcLoc srcLoc) doc ->
#endif
#if MIN_VERSION_ghc(9,2,0)
let
psErrToString e = show $ ParserErrorPpr.pprError e
err = concatMap psErrToString errorMessages
line = SrcLoc.srcLocLine srcLoc
col = SrcLoc.srcLocCol srcLoc
in Left (line, col, err)
#elif MIN_VERSION_ghc(8,10,0)
let
(WarningMessages
_warnMessages, WarningMessages
errorMessages) = DynFlags -> Messages
msgs DynFlags
dynFlags
err :: String
err = (ErrMsg -> String) -> WarningMessages -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ErrMsg -> String
forall a. Show a => a -> String
show WarningMessages
errorMessages
line :: Int
line = RealSrcLoc -> Int
SrcLoc.srcLocLine RealSrcLoc
srcLoc
col :: Int
col = RealSrcLoc -> Int
SrcLoc.srcLocCol RealSrcLoc
srcLoc
in (Int, Int, String) -> Either (Int, Int, String) (HsExpr GhcPs)
forall a b. a -> Either a b
Left (Int
line, Int
col, String
err)
#else
let err = showSDoc dynFlags doc
line = SrcLoc.srcLocLine srcLoc
col = SrcLoc.srcLocCol srcLoc
in Left (line, col, err)
#endif