Sven Tennie pushed to branch wip/romes/hadrian-cross-stage2-rebase_SVEN_FIXED at Glasgow Haskell Compiler / GHC

Commits:

5 changed files:

Changes:

  • ghc/GHC/Driver/Session/Mode.hs
    ... ... @@ -134,7 +134,7 @@ isDoEvalMode :: Mode -> Bool
    134 134
     isDoEvalMode (Right (Right (DoEval _))) = True
    
    135 135
     isDoEvalMode _ = False
    
    136 136
     
    
    137
    -#if defined(HAVE_INTERNAL_INTERPRETER)
    
    137
    +#if defined(HAVE_INTERPRETER)
    
    138 138
     isInteractiveMode :: PostLoadMode -> Bool
    
    139 139
     isInteractiveMode DoInteractive = True
    
    140 140
     isInteractiveMode _             = False
    

  • ghc/GHCi/UI.hs
    ... ... @@ -1905,7 +1905,9 @@ changeDirectory dir = do
    1905 1905
           fhv <- compileGHCiExpr $
    
    1906 1906
             "System.Directory.setCurrentDirectory " ++ show dir'
    
    1907 1907
           liftIO $ evalIO interp fhv
    
    1908
    +#if defined(HAVE_INTERNAL_INTERPRETER)
    
    1908 1909
         _ -> pure ()
    
    1910
    +#endif
    
    1909 1911
     
    
    1910 1912
     trySuccess :: GhciMonad m => m SuccessFlag -> m SuccessFlag
    
    1911 1913
     trySuccess act =
    

  • ghc/Main.hs
    ... ... @@ -37,7 +37,7 @@ import GHC.Driver.Config.Diagnostic
    37 37
     import GHC.Platform
    
    38 38
     import GHC.Platform.Host
    
    39 39
     
    
    40
    -#if defined(HAVE_INTERNAL_INTERPRETER)
    
    40
    +#if defined(HAVE_INTERPRETER)
    
    41 41
     import GHCi.UI              ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings )
    
    42 42
     #endif
    
    43 43
     
    
    ... ... @@ -289,7 +289,7 @@ doRun units srcs args = do
    289 289
         args' = drop 1 $ dropWhile (/= "--") $ map unLoc args
    
    290 290
     
    
    291 291
     ghciUI :: [String] -> [(FilePath, Maybe Phase)] -> Maybe [String] -> Ghc ()
    
    292
    -#if !defined(HAVE_INTERNAL_INTERPRETER)
    
    292
    +#if !defined(HAVE_INTERPRETER)
    
    293 293
     ghciUI _ _ _ =
    
    294 294
       throwGhcException (CmdLineError "not built for interactive use")
    
    295 295
     #else
    
    ... ... @@ -333,7 +333,7 @@ showBanner :: PostLoadMode -> DynFlags -> IO ()
    333 333
     showBanner _postLoadMode dflags = do
    
    334 334
        let verb = verbosity dflags
    
    335 335
     
    
    336
    -#if defined(HAVE_INTERNAL_INTERPRETER)
    
    336
    +#if defined(HAVE_INTERPRETER)
    
    337 337
        -- Show the GHCi banner
    
    338 338
        when (isInteractiveMode _postLoadMode && verb >= 1) $ putStrLn ghciWelcomeMsg
    
    339 339
     #endif
    

  • ghc/ghc-bin.cabal.in
    ... ... @@ -22,6 +22,11 @@ Flag internal-interpreter
    22 22
         Default: False
    
    23 23
         Manual: True
    
    24 24
     
    
    25
    +Flag interpreter
    
    26
    +    Description: Build with interpreter support, both internal and external.
    
    27
    +    Default: False
    
    28
    +    Manual: True
    
    29
    +
    
    25 30
     Flag threaded
    
    26 31
         Description: Link the ghc executable against the threaded RTS
    
    27 32
         Default: True
    
    ... ... @@ -56,7 +61,7 @@ Executable ghc
    56 61
                      -rtsopts=all
    
    57 62
                      "-with-rtsopts=-K512M -H -I5 -T"
    
    58 63
     
    
    59
    -    if flag(internal-interpreter)
    
    64
    +    if flag(interpreter)
    
    60 65
             -- NB: this is never built by the bootstrapping GHC+libraries
    
    61 66
             Build-depends:
    
    62 67
                 deepseq        >= 1.4 && < 1.6,
    
    ... ... @@ -65,7 +70,7 @@ Executable ghc
    65 70
                 haskeline      == 0.8.*,
    
    66 71
                 exceptions     == 0.10.*,
    
    67 72
                 time           >= 1.8 && < 1.16
    
    68
    -        CPP-Options: -DHAVE_INTERNAL_INTERPRETER
    
    73
    +        CPP-Options: -DHAVE_INTERPRETER
    
    69 74
             Other-Modules:
    
    70 75
                 GHCi.Leak
    
    71 76
                 GHCi.UI
    
    ... ... @@ -86,6 +91,9 @@ Executable ghc
    86 91
                 UnboxedTuples
    
    87 92
                 ViewPatterns
    
    88 93
     
    
    94
    +    if flag(internal-interpreter)
    
    95
    +       CPP-Options: -DHAVE_INTERNAL_INTERPRETER
    
    96
    +
    
    89 97
         if flag(threaded)
    
    90 98
           ghc-options: -threaded
    
    91 99
     
    

  • hadrian/src/Settings/Packages.hs
    ... ... @@ -114,7 +114,8 @@ packageArgs = do
    114 114
                  , compilerStageOption ghcDebugAssertions ? arg "-DDEBUG" ]
    
    115 115
     
    
    116 116
               , builder (Cabal Flags) ? mconcat
    
    117
    -            [ andM [expr (ghcWithInterpreter stage), orM [expr (notM cross), stage1]] `cabalFlag` "internal-interpreter"
    
    117
    +            [ andM [expr (ghcWithInterpreter stage), orM [expr (notM cross), stage1]] `cabalFlag` "interpreter"
    
    118
    +            , andM [expr (ghcWithInterpreter stage), notM (expr cross)] `cabalFlag` "internal-interpreter"
    
    118 119
                 , ifM stage0
    
    119 120
                       -- We build a threaded stage 1 if the bootstrapping compiler
    
    120 121
                       -- supports it.