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

Commits:

3 changed files:

Changes:

  • compiler/GHC/Parser/PreProcess/State.hs
    ... ... @@ -32,8 +32,8 @@ module GHC.Parser.PreProcess.State (
    32 32
     
    
    33 33
     import Data.List.NonEmpty ((<|))
    
    34 34
     import Data.List.NonEmpty qualified as NonEmpty
    
    35
    -import Data.Map (Map)
    
    36
    -import Data.Map qualified as Map
    
    35
    +import Data.Map.Strict (Map)
    
    36
    +import Data.Map.Strict qualified as Map
    
    37 37
     import Data.Maybe (isJust)
    
    38 38
     import GHC.Base
    
    39 39
     import GHC.Data.StringBuffer
    
    ... ... @@ -317,7 +317,7 @@ addDefine name def = do
    317 317
     
    
    318 318
     addDefine' :: PpState -> MacroName -> MacroDef -> PpState
    
    319 319
     addDefine' s name def =
    
    320
    -    s{pp_defines = insertMacroDef name def (pp_defines s)}
    
    320
    +    s{ pp_defines = insertMacroDef name def (pp_defines s)}
    
    321 321
     
    
    322 322
     ppDefine :: MacroName -> MacroDef -> PP ()
    
    323 323
     ppDefine name val = addDefine name val
    

  • utils/check-cpp/Example12.hs
    1
    +{-# LANGUAGE
    
    2
    +    GHC_CPP
    
    3
    +  , DeriveGeneric
    
    4
    +#-}
    
    5
    +
    
    6
    +module Example12 where

  • utils/check-cpp/Example13.hs
    1
    +{-# LANGUAGE GHC_CPP #-}
    
    2
    +-- {-# OPTIONS -ddump-ghc-cpp -dkeep-comments #-}
    
    3
    +module Example13 where
    
    4
    +
    
    5
    +foo =
    
    6
    +#if MIN_VERSION_GLASGOW_HASKELL(19,13,20250101,0)
    
    7
    +  'a'
    
    8
    +#else
    
    9
    +  'b'
    
    10
    +#endif