[Git][ghc/ghc][wip/az/ghc-cpp] Clean up a bit

Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC Commits: eadbe239 by Alan Zimmerman at 2025-06-22T22:05:12+01:00 Clean up a bit - - - - - 2 changed files: - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x Changes: ===================================== compiler/GHC/Parser.y ===================================== @@ -767,18 +767,6 @@ TH_TY_QUOTE { L _ ITtyQuote } -- ''T TH_QUASIQUOTE { L _ (ITquasiQuote _) } TH_QQUASIQUOTE { L _ (ITqQuasiQuote _) } --- Ghc CPP --- '#define' { L _ (ITcppDefine _) } --- '#include' { L _ (ITcppInclude _) } --- '#undef' { L _ (ITcppUndef _) } --- '#error' { L _ (ITcppError _) } --- '#if' { L _ (ITcppIf _) } --- '#ifdef' { L _ (ITcppIfdef _) } --- '#ifndef' { L _ (ITcppIfndef _) } --- '#elif' { L _ (ITcppElif _) } --- '#else' { L _ ITcppElse } --- '#endif' { L _ ITcppEndif } - -- %monad { P p } { >>= } { return } %monad { P PpState } { >>= } { return } %lexer { (lexer True) } { L _ ITeof } @@ -4611,10 +4599,6 @@ amsA' (L l a) = do !cs <- getCommentsFor l return (L (EpAnn (spanAsAnchor l) noAnn cs) a) --- acsExpr :: (EpAnnComments -> LHsExpr GhcPs) -> P PpState ECP --- acsExpr a = do { expr :: (LHsExpr GhcPs) <- runPV $ acsa a --- ; return (ecpFromExp $ expr) } - amsA :: MonadP m => LocatedA a -> [TrailingAnn] -> m (LocatedA a) amsA (L !l a) bs = do !cs <- getCommentsFor (locA l) ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -2658,15 +2658,6 @@ data PState a = PState { data PpContext = PpContextIf [Located Token] deriving (Show) --- TODO: delete --- initPpState :: PpState --- initPpState = PpState --- { pp_defines = Map.empty --- , pp_continuation = [] --- , pp_context = [] --- , pp_accepting = True --- } - data ALRContext = ALRNoLayout Bool{- does it contain commas? -} Bool{- is it a 'let' block? -} | ALRLayout ALRLayout Int @@ -3104,8 +3095,6 @@ mkParserOpts extensionFlags diag_opts .|. MultilineStringsBit `xoptBit` LangExt.MultilineStrings .|. LevelImportsBit `xoptBit` LangExt.ExplicitLevelImports .|. GhcCppBit `xoptBit` LangExt.GhcCpp - -- .|. (trace ("GhcCppBit:" ++ show (GhcCppBit `xoptBit` LangExt.GhcCpp)) - -- GhcCppBit `xoptBit` LangExt.GhcCpp) optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream @@ -3148,7 +3137,6 @@ extBitEnabled bit opts = xtest bit (pExtsBitmap opts) -- | Set parser options for parsing OPTIONS pragmas initPragState :: p -> ParserOpts -> StringBuffer -> RealSrcLoc -> PState p initPragState p options buf loc = (initParserState p options buf loc) --- initPragState options buf loc = (initParserState options buf (trace ("initPragState:" ++ show bol) loc)) { lex_state = [bol, option_prags, 0] } @@ -3337,9 +3325,6 @@ popContext = P $ \ s@(PState{ buffer = buf, options = o, context = ctx, POk s{ context = tl } () [] -> unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s - -- let s' = (trace "popContext empty" s) - -- in - -- unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s' -- Push a new layout context at the indentation of the last token read. pushCurrentContext :: GenSemic -> P p () @@ -3395,8 +3380,6 @@ srcParseFail :: P p a srcParseFail = P $ \s@PState{ buffer = buf, options = o, last_len = len, last_loc = last_loc } -> unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s - -- let s' = trace ("srcParseFail") s - -- in unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s' -- A lexical error is reported at a particular position in the source file, -- not over a token range. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eadbe239c57c52d209ea58aa56e2603d... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eadbe239c57c52d209ea58aa56e2603d... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Alan Zimmerman (@alanz)