Alan Zimmerman pushed to branch wip/az/ghc-cpp at Glasgow Haskell Compiler / GHC

Commits:

2 changed files:

Changes:

  • compiler/GHC/Parser.y
    ... ... @@ -767,18 +767,6 @@ TH_TY_QUOTE { L _ ITtyQuote } -- ''T
    767 767
     TH_QUASIQUOTE   { L _ (ITquasiQuote _) }
    
    768 768
     TH_QQUASIQUOTE  { L _ (ITqQuasiQuote _) }
    
    769 769
     
    
    770
    --- Ghc CPP
    
    771
    --- '#define'       { L _ (ITcppDefine _) }
    
    772
    --- '#include'      { L _ (ITcppInclude _) }
    
    773
    --- '#undef'        { L _ (ITcppUndef _) }
    
    774
    --- '#error'        { L _ (ITcppError _) }
    
    775
    --- '#if'           { L _ (ITcppIf _) }
    
    776
    --- '#ifdef'        { L _ (ITcppIfdef _) }
    
    777
    --- '#ifndef'       { L _ (ITcppIfndef _) }
    
    778
    --- '#elif'         { L _ (ITcppElif _) }
    
    779
    --- '#else'         { L _ ITcppElse }
    
    780
    --- '#endif'        { L _ ITcppEndif }
    
    781
    -
    
    782 770
     -- %monad { P p } { >>= } { return }
    
    783 771
     %monad { P PpState } { >>= } { return }
    
    784 772
     %lexer { (lexer True) } { L _ ITeof }
    
    ... ... @@ -4611,10 +4599,6 @@ amsA' (L l a) = do
    4611 4599
       !cs <- getCommentsFor l
    
    4612 4600
       return (L (EpAnn (spanAsAnchor l) noAnn cs) a)
    
    4613 4601
     
    
    4614
    --- acsExpr :: (EpAnnComments -> LHsExpr GhcPs) -> P PpState ECP
    
    4615
    --- acsExpr a = do { expr :: (LHsExpr GhcPs) <- runPV $ acsa a
    
    4616 4602
     amsA :: MonadP m => LocatedA a -> [TrailingAnn] -> m (LocatedA a)
    
    4617 4603
     amsA (L !l a) bs = do
    
    4618 4604
       !cs <- getCommentsFor (locA l)
    

  • compiler/GHC/Parser/Lexer.x
    ... ... @@ -2658,15 +2658,6 @@ data PState a = PState {
    2658 2658
     data PpContext = PpContextIf [Located Token]
    
    2659 2659
         deriving (Show)
    
    2660 2660
     
    
    2661
    --- TODO: delete
    
    2662
    --- initPpState :: PpState
    
    2663
    --- initPpState = PpState
    
    2664
    ---    { pp_defines = Map.empty
    
    2665
    ---    , pp_continuation = []
    
    2666
    ---    , pp_context = []
    
    2667
    ---    , pp_accepting = True
    
    2668
    ---    }
    
    2669
    -
    
    2670 2661
     data ALRContext = ALRNoLayout Bool{- does it contain commas? -}
    
    2671 2662
                                   Bool{- is it a 'let' block? -}
    
    2672 2663
                     | ALRLayout ALRLayout Int
    
    ... ... @@ -3104,8 +3095,6 @@ mkParserOpts extensionFlags diag_opts
    3104 3095
           .|. MultilineStringsBit         `xoptBit` LangExt.MultilineStrings
    
    3105 3096
           .|. LevelImportsBit             `xoptBit` LangExt.ExplicitLevelImports
    
    3106 3097
           .|. GhcCppBit                   `xoptBit` LangExt.GhcCpp
    
    3107
    -      -- .|. (trace ("GhcCppBit:" ++ show (GhcCppBit                   `xoptBit` LangExt.GhcCpp))
    
    3108
    -      --       GhcCppBit                   `xoptBit` LangExt.GhcCpp)
    
    3109 3098
         optBits =
    
    3110 3099
               HaddockBit        `setBitIf` isHaddock
    
    3111 3100
           .|. RawTokenStreamBit `setBitIf` rawTokStream
    
    ... ... @@ -3148,7 +3137,6 @@ extBitEnabled bit opts = xtest bit (pExtsBitmap opts)
    3148 3137
     -- | Set parser options for parsing OPTIONS pragmas
    
    3149 3138
     initPragState :: p -> ParserOpts -> StringBuffer -> RealSrcLoc -> PState p
    
    3150 3139
     initPragState p options buf loc = (initParserState p options buf loc)
    
    3151
    --- initPragState options buf loc = (initParserState options buf (trace ("initPragState:" ++ show bol) loc))
    
    3152 3140
        { lex_state = [bol, option_prags, 0]
    
    3153 3141
        }
    
    3154 3142
     
    
    ... ... @@ -3337,9 +3325,6 @@ popContext = P $ \ s@(PState{ buffer = buf, options = o, context = ctx,
    3337 3325
               POk s{ context = tl } ()
    
    3338 3326
             []     ->
    
    3339 3327
               unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s
    
    3340
    -          -- let s' = (trace "popContext empty" s)
    
    3341
    -          -- in
    
    3342
    -          --   unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s'
    
    3343 3328
     
    
    3344 3329
     -- Push a new layout context at the indentation of the last token read.
    
    3345 3330
     pushCurrentContext :: GenSemic -> P p ()
    
    ... ... @@ -3395,8 +3380,6 @@ srcParseFail :: P p a
    3395 3380
     srcParseFail = P $ \s@PState{ buffer = buf, options = o, last_len = len,
    
    3396 3381
                                 last_loc = last_loc } ->
    
    3397 3382
         unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s
    
    3398
    -    -- let s' = trace ("srcParseFail") s
    
    3399
    -    -- in unP (addFatalError $ srcParseErr o buf len (mkSrcSpanPs last_loc)) s'
    
    3400 3383
     
    
    3401 3384
     -- A lexical error is reported at a particular position in the source file,
    
    3402 3385
     -- not over a token range.