Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC

Commits:

20 changed files:

Changes:

  • CODEOWNERS
    ... ... @@ -66,7 +66,6 @@
    66 66
     
    
    67 67
     [Internal utilities and libraries]
    
    68 68
     /utils/iserv-proxy/               @angerman @simonmar
    
    69
    -/utils/iserv/                     @angerman @simonmar
    
    70 69
     /utils/fs/                        @Phyx
    
    71 70
     /utils/jsffi                      @TerrorJack
    
    72 71
     /utils/haddock                     @Kleidukos
    

  • cabal.project-reinstall
    ... ... @@ -52,7 +52,6 @@ packages: ./compiler
    52 52
               ./utils/hsc2hs
    
    53 53
               ./utils/runghc
    
    54 54
               ./utils/unlit
    
    55
    -          ./utils/iserv
    
    56 55
               ./linters/**/*.cabal
    
    57 56
     
    
    58 57
     constraints: ghc +internal-interpreter +dynamic-system-linke,
    

  • compiler/GHC/Runtime/Interpreter/Init.hs
    ... ... @@ -128,13 +128,7 @@ initInterpreter dflags tmpfs logger platform finder_cache unit_env opts = do
    128 128
             prog <- case interpProg opts of
    
    129 129
               -- build iserv program if none specified
    
    130 130
               "" -> generateIservC dflags logger tmpfs (interpExecutableLinkOpts opts) unit_env
    
    131
    -          _ -> pure (interpProg opts ++ flavour)
    
    132
    -            where
    
    133
    -              flavour
    
    134
    -                | profiled && dynamic = "-prof-dyn"
    
    135
    -                | profiled  = "-prof"
    
    136
    -                | dynamic   = "-dyn"
    
    137
    -                | otherwise = ""
    
    131
    +          _  -> pure $ interpProg opts
    
    138 132
             let msg = text "Starting " <> text prog
    
    139 133
             tr <- if interpVerbosity opts >= 3
    
    140 134
                    then return (logInfo logger $ withPprStyle defaultDumpStyle msg)
    

  • compiler/GHC/Settings/IO.hs
    ... ... @@ -41,8 +41,6 @@ initSettings
    41 41
     initSettings top_dir = do
    
    42 42
       let installed :: FilePath -> FilePath
    
    43 43
           installed file = top_dir </> file
    
    44
    -      libexec :: FilePath -> FilePath
    
    45
    -      libexec file = top_dir </> ".." </> "bin" </> file
    
    46 44
           settingsFile = installed "settings"
    
    47 45
           targetFile   = installed $ "targets" </> "default.target"
    
    48 46
     
    
    ... ... @@ -142,7 +140,9 @@ initSettings top_dir = do
    142 140
             ld_r_prog <- tgtMergeObjs target
    
    143 141
             let (ld_r_path, ld_r_args) = getTool (mergeObjsProgram . const ld_r_prog)
    
    144 142
             pure (ld_r_path, map Option ld_r_args)
    
    145
    -      iserv_prog   = libexec "ghc-iserv"
    
    143
    +      -- Default to the on-demand external interpreter. A non-empty value can
    
    144
    +      -- be provided via -pgmi to use a custom external interpreter.
    
    145
    +      iserv_prog   = ""
    
    146 146
     
    
    147 147
       ghcWithInterpreter <- getBooleanSetting "Use interpreter"
    
    148 148
     
    

  • docs/users_guide/ghci.rst
    ... ... @@ -3560,15 +3560,18 @@ default in future releases.
    3560 3560
     Building an external interpreter
    
    3561 3561
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    3562 3562
     
    
    3563
    -The source code for the external interpreter program is in `utils/iserv`. It is
    
    3564
    -very simple because most of the heavy lifting code is from the `ghci` library.
    
    3563
    +When :ghc-flag:`-fexternal-interpreter` is enabled, GHC builds a small external
    
    3564
    +interpreter executable on demand using the installed `ghci` library and runs it
    
    3565
    +directly. There is no longer a dedicated `utils/iserv` program in the tree.
    
    3565 3566
     
    
    3566 3567
     It is sometimes desirable to customize the external interpreter program. For
    
    3567 3568
     example, it is possible to add symbols to the RTS linker used by the external
    
    3568 3569
     interpreter. This is done simply at link time by linking an additional `.o` that
    
    3569 3570
     defines a `rtsExtraSyms` function returning the extra symbols. Doing it this way
    
    3570 3571
     avoids the need to recompile the RTS with symbols added to its built-in list.
    
    3571
    -A typical C file would look like this:
    
    3572
    +Build your custom interpreter (using `ghci:GHCi.Server.defaultServer` as the
    
    3573
    +entry point) and point :ghc-flag:`-pgmi ⟨cmd⟩` at it. A typical C file would
    
    3574
    +look like this:
    
    3572 3575
     
    
    3573 3576
     .. code:: C
    
    3574 3577
     
    

  • docs/users_guide/phases.rst
    ... ... @@ -151,16 +151,10 @@ given compilation phase:
    151 151
         :category: phase-programs
    
    152 152
     
    
    153 153
         Use ⟨cmd⟩ as the external interpreter command (see
    
    154
    -    :ref:`external-interpreter`).  Default: ``ghc-iserv-prof`` if
    
    155
    -    :ghc-flag:`-prof` is enabled, ``ghc-iserv-dyn`` if :ghc-flag:`-dynamic` is
    
    156
    -    enabled, or ``ghc-iserv`` otherwise.
    
    157
    -
    
    158
    -    If <cmd> is the empty string then GHC will try to build an appropriate iserv
    
    159
    -    program for the target platform. It does this by looking for the installed
    
    160
    -    ``ghci`` unit and by building an executable program that uses
    
    161
    -    ``ghci:GHCi.Server.defaultServer`` as an entry point. Note that it doesn't
    
    162
    -    work when cross-compiling: the cross-compiled ``iserv`` program (if it can
    
    163
    -    be built) can't be run on the build platform.
    
    154
    +    :ref:`external-interpreter`).  By default GHC builds an on-demand external
    
    155
    +    interpreter using the installed ``ghci`` unit and runs it directly. This
    
    156
    +    requires that target executables can run on the build host; when
    
    157
    +    cross-compiling, pass ``-pgmi`` to use a proxy such as ``iserv-proxy``.
    
    164 158
     
    
    165 159
     
    
    166 160
     .. _forcing-options-through:
    

  • hadrian/doc/user-settings.md
    ... ... @@ -238,7 +238,7 @@ quickDebug = quickFlavour { name = "dbg", ghcDebugged = const True }
    238 238
     ```
    
    239 239
     
    
    240 240
     Running `build --flavour=dbg` will build a `quick`-flavoured GHC and link
    
    241
    -GHC, iserv, iserv-proxy and remote-iserv against the debugged RTS, by passing
    
    241
    +GHC, iserv-proxy and remote-iserv against the debugged RTS, by passing
    
    242 242
     `-debug` to the commands that link those executables.
    
    243 243
     
    
    244 244
     More generally, a predicate on `Stage` can be provided to specify which stages should be built debugged. For example, setting `ghcDebugged = (>= Stage2)` will build a debugged compiler at stage 2 or higher, but not stage 1.
    

  • hadrian/src/Packages.hs
    ... ... @@ -7,7 +7,7 @@ module Packages (
    7 7
         exceptions, filepath, fileio, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform,
    
    8 8
         ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim,
    
    9 9
         ghcToolchain, ghcToolchainBin, haddockApi, haddockLibrary, haddock, haskeline,
    
    10
    -    hsc2hs, hp2ps, hpc, hpcBin, integerGmp, iserv, iservProxy,
    
    10
    +    hsc2hs, hp2ps, hpc, hpcBin, integerGmp, iservProxy,
    
    11 11
         libffi, mtl, osString, parsec, pretty, primitive, process, remoteIserv, rts,
    
    12 12
         runGhc, semaphoreCompat, stm, templateHaskell, thLift, thQuasiquoter, terminfo, text, time, timeout,
    
    13 13
         transformers, unlit, unix, win32, xhtml,
    
    ... ... @@ -38,7 +38,7 @@ ghcPackages =
    38 38
         , exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform
    
    39 39
         , ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim
    
    40 40
         , ghcToolchain, ghcToolchainBin, haddockApi, haddockLibrary, haddock, haskeline, hsc2hs
    
    41
    -    , hp2ps, hpc, hpcBin, integerGmp, iserv, libffi, mtl, osString
    
    41
    +    , hp2ps, hpc, hpcBin, integerGmp, libffi, mtl, osString
    
    42 42
         , parsec, pretty, process, rts, runGhc, stm, semaphoreCompat, templateHaskell, thLift, thQuasiquoter
    
    43 43
         , terminfo, text, time, transformers, unlit, unix, win32, xhtml, fileio
    
    44 44
         , timeout
    
    ... ... @@ -55,7 +55,7 @@ array, base, binary, bytestring, cabalSyntax, cabal, checkPpr, checkExact, count
    55 55
       exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform,
    
    56 56
       ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghci, ghcInternal, ghciWrapper, ghcPkg, ghcPrim,
    
    57 57
       ghcToolchain, ghcToolchainBin, haddockLibrary, haddockApi, haddock, haskeline, hsc2hs,
    
    58
    -  hp2ps, hpc, hpcBin, integerGmp, iserv, iservProxy, remoteIserv, libffi, mtl,
    
    58
    +  hp2ps, hpc, hpcBin, integerGmp, iservProxy, remoteIserv, libffi, mtl,
    
    59 59
       osString, parsec, pretty, primitive, process, rts, runGhc, semaphoreCompat, stm, templateHaskell, thLift, thQuasiquoter,
    
    60 60
       terminfo, text, time, transformers, unlit, unix, win32, xhtml,
    
    61 61
       timeout,
    
    ... ... @@ -109,7 +109,6 @@ hp2ps = util "hp2ps"
    109 109
     hpc                 = lib  "hpc"
    
    110 110
     hpcBin              = util "hpc-bin"         `setPath` "utils/hpc"
    
    111 111
     integerGmp          = lib  "integer-gmp"
    
    112
    -iserv               = util "iserv"
    
    113 112
     iservProxy          = util "iserv-proxy"
    
    114 113
     libffi              = top  "libffi"
    
    115 114
     mtl                 = lib  "mtl"
    
    ... ... @@ -182,24 +181,12 @@ programName :: Context -> Action String
    182 181
     programName Context {..} = do
    
    183 182
         prefix <- crossPrefix
    
    184 183
         -- TODO: Can we extract this information from Cabal files?
    
    185
    -    -- Alp: We could, but then the iserv package would have to
    
    186
    -    --      use Cabal conditionals + a 'profiling' flag
    
    187
    -    --      to declare the executable name, and I'm not sure
    
    188
    -    --      this is allowed (or desired for that matter).
    
    189 184
         return $ prefix ++ basename
    
    190 185
       where
    
    191 186
         basename
    
    192 187
           | package == ghc          = "ghc"
    
    193 188
           | package == ghciWrapper  = "ghci" -- See Note [Hadrian's ghci-wrapper package]
    
    194 189
           | package == hpcBin       = "hpc"
    
    195
    -      | package == iserv        = "ghc-iserv" ++ concat [
    
    196
    -                                        if wayUnit' `wayUnit` way
    
    197
    -                                            then suffix
    
    198
    -                                            else ""
    
    199
    -                                        | (wayUnit', suffix) <- [
    
    200
    -                                            (Profiling, "-prof"),
    
    201
    -                                            (Dynamic,   "-dyn")
    
    202
    -                                        ]]
    
    203 190
           | otherwise               = pkgName package
    
    204 191
     
    
    205 192
     -- | The 'FilePath' to a program executable in a given 'Context'.
    

  • hadrian/src/Rules/BinaryDist.hs
    ... ... @@ -5,7 +5,6 @@ import CommandLine
    5 5
     import Context
    
    6 6
     import Expression
    
    7 7
     import Oracles.Setting
    
    8
    -import Oracles.Flag
    
    9 8
     import Packages
    
    10 9
     import Settings
    
    11 10
     import Settings.Program (programContext)
    
    ... ... @@ -154,10 +153,7 @@ bindistRules = do
    154 153
             -- We 'need' all binaries and libraries
    
    155 154
             all_pkgs <- stagePackages Stage1
    
    156 155
             (lib_targets, bin_targets) <- partitionEithers <$> mapM pkgTarget all_pkgs
    
    157
    -        cross <- flag CrossCompiling
    
    158
    -        iserv_targets <- if cross then pure [] else iservBins
    
    159
    -
    
    160
    -        let lib_exe_targets = (lib_targets ++ (map (\(_, p) -> p) (bin_targets ++ iserv_targets)))
    
    156
    +        let lib_exe_targets = lib_targets ++ map snd bin_targets
    
    161 157
     
    
    162 158
             let doc_target = ["docs"]
    
    163 159
     
    
    ... ... @@ -173,7 +169,7 @@ bindistRules = do
    173 169
             createDirectory (bindistFilesDir -/- "bin")
    
    174 170
             createDirectory (bindistFilesDir -/- "lib")
    
    175 171
             -- Also create wrappers with version suffixes (#20074)
    
    176
    -        forM_ (bin_targets ++ iserv_targets) $ \(pkg, prog_path) -> do
    
    172
    +        forM_ bin_targets $ \(pkg, prog_path) -> do
    
    177 173
                 let orig_filename = takeFileName prog_path
    
    178 174
                     (name, ext) = splitExtensions orig_filename
    
    179 175
                     suffix = if useGhcPrefix pkg
    
    ... ... @@ -481,20 +477,6 @@ ghciScriptWrapper = do
    481 477
         [ "executable=\"$bindir/" ++ prefix ++ "ghc-" ++ version ++ "\""
    
    482 478
         , "exec $executable --interactive \"$@\"" ]
    
    483 479
     
    
    484
    --- | When not on Windows, we want to ship the 3 flavours of the iserv program
    
    485
    ---   in binary distributions. This isn't easily achievable by just asking for
    
    486
    ---   the package to be built, since here we're generating 3 different
    
    487
    ---   executables out of just one package, so we need to specify all 3 contexts
    
    488
    ---   explicitly and 'need' the result of building them.
    
    489
    -iservBins :: Action [(Package, FilePath)]
    
    490
    -iservBins = do
    
    491
    -  rtsways <- interpretInContext (vanillaContext Stage1 ghc) getRtsWays
    
    492
    -  traverse (fmap (\p -> (iserv, p)) . programPath)
    
    493
    -      [ Context Stage1 iserv w Final
    
    494
    -      | w <- [vanilla, profiling, dynamic]
    
    495
    -      , w `elem` rtsways
    
    496
    -      ]
    
    497
    -
    
    498 480
     -- Version wrapper scripts
    
    499 481
     -- See Note [Two Types of Wrappers]
    
    500 482
     
    

  • hadrian/src/Rules/CabalReinstall.hs
    ... ... @@ -2,7 +2,6 @@ module Rules.CabalReinstall where
    2 2
     
    
    3 3
     import Context
    
    4 4
     import Expression
    
    5
    -import Oracles.Flag
    
    6 5
     import Packages
    
    7 6
     import Settings
    
    8 7
     import Target
    
    ... ... @@ -48,9 +47,7 @@ cabalBuildRules = do
    48 47
             -- We 'need' all binaries and libraries
    
    49 48
             all_pkgs <- stagePackages Stage1
    
    50 49
             (lib_targets, bin_targets) <- partitionEithers <$> mapM pkgTarget all_pkgs
    
    51
    -        cross <- flag CrossCompiling
    
    52
    -        iserv_targets <- if cross then pure [] else iservBins
    
    53
    -        need (lib_targets ++ (map (\(_, p) -> p) (bin_targets ++ iserv_targets)))
    
    50
    +        need (lib_targets ++ map snd bin_targets)
    
    54 51
     
    
    55 52
             distDir        <- Context.distDir (vanillaContext Stage1 rts)
    
    56 53
             let rtsIncludeDir    = distDir -/- "include"
    
    ... ... @@ -69,7 +66,7 @@ cabalBuildRules = do
    69 66
     
    
    70 67
             let cabal_package_db = cwd -/- root -/- "stage-cabal" -/- "dist-newstyle" -/- "packagedb" -/- "ghc-" ++ version
    
    71 68
     
    
    72
    -        forM_ (filter ((/= iserv) . fst) bin_targets) $ \(bin_pkg,_bin_path) -> do
    
    69
    +        forM_ bin_targets $ \(bin_pkg,_bin_path) -> do
    
    73 70
                 let pgmName pkg
    
    74 71
                       | pkg == ghc    = "ghc"
    
    75 72
                       | pkg == hpcBin = "hpc"
    
    ... ... @@ -92,14 +89,4 @@ cabalBuildRules = do
    92 89
                   makeExecutable output_file
    
    93 90
                   pure ()
    
    94 91
     
    
    95
    -        -- Just symlink these for now
    
    96
    -        -- TODO: build these with cabal as well
    
    97
    -        forM_ iserv_targets $ \(_bin_pkg,bin_path') -> do
    
    98
    -            bin_path <- liftIO $ makeAbsolute bin_path'
    
    99
    -            let orig_filename = takeFileName bin_path
    
    100
    -                output_file = outputDir -/- orig_filename
    
    101
    -            liftIO $ do
    
    102
    -              IO.removeFile output_file <|> pure ()
    
    103
    -              IO.createFileLink bin_path output_file
    
    104
    -            pure ()
    
    105 92
             writeFile' stamp "OK"

  • hadrian/src/Rules/Generate.hs
    ... ... @@ -351,7 +351,6 @@ templateRules = do
    351 351
       templateRule "compiler/ghc.cabal" $ projectVersion
    
    352 352
       templateRule "driver/ghci/ghci-wrapper.cabal" $ projectVersion
    
    353 353
       templateRule "ghc/ghc-bin.cabal" $ projectVersion
    
    354
    -  templateRule "utils/iserv/iserv.cabal" $ projectVersion
    
    355 354
       templateRule "utils/remote-iserv/remote-iserv.cabal" $ projectVersion
    
    356 355
       templateRule "utils/runghc/runghc.cabal" $ projectVersion
    
    357 356
       templateRule "libraries/ghc-boot/ghc-boot.cabal" $ projectVersion
    

  • hadrian/src/Rules/Program.hs
    ... ... @@ -53,27 +53,10 @@ getProgramContexts stage = do
    53 53
       -- TODO: Shall we use Stage2 for testsuite packages instead?
    
    54 54
       let allPackages = sPackages
    
    55 55
                      ++ tPackages
    
    56
    -  fmap concat . forM allPackages $ \pkg -> do
    
    57
    -    -- the iserv pkg results in three different programs at
    
    58
    -    -- the moment, ghc-iserv (built the vanilla way),
    
    59
    -    -- ghc-iserv-prof (built the profiling way),
    
    60
    -    -- ghc-iserv-dyn (built the dynamic way), and
    
    61
    -    -- ghc-iserv-prof-dyn (built the profiling+dynamic way).
    
    62
    -    -- The testsuite requires all to be present, so we
    
    63
    -    -- make sure that we cover these
    
    64
    -    -- "prof-build-under-other-name" cases.
    
    65
    -    -- iserv gets its names from Packages.hs:programName
    
    56
    +  forM allPackages $ \pkg -> do
    
    66 57
         ctx <- programContext stage pkg -- TODO: see todo on programContext.
    
    67
    -    let allCtxs = if pkg == iserv
    
    68
    -        then [ vanillaContext stage pkg
    
    69
    -             , Context stage pkg profiling Final
    
    70
    -             , Context stage pkg dynamic Final
    
    71
    -             , Context stage pkg profilingDynamic Final
    
    72
    -             ]
    
    73
    -        else [ ctx ]
    
    74
    -    forM allCtxs $ \ctx -> do
    
    75
    -      name <- programName ctx
    
    76
    -      return (name <.> exe, ctx)
    
    58
    +    name <- programName ctx
    
    59
    +    return (name <.> exe, ctx)
    
    77 60
     
    
    78 61
     lookupProgramContext :: FilePath -> [(FilePath, Context)] -> Maybe Context
    
    79 62
     lookupProgramContext wholePath progs = lookup (takeFileName wholePath) progs
    

  • hadrian/src/Rules/Test.hs
    ... ... @@ -17,7 +17,6 @@ import Settings.Builders.RunTest
    17 17
     import Settings.Program (programContext)
    
    18 18
     import Target
    
    19 19
     import Utilities
    
    20
    -import Context.Type
    
    21 20
     import qualified System.Directory as IO
    
    22 21
     
    
    23 22
     import GHC.Toolchain as Toolchain
    
    ... ... @@ -320,11 +319,9 @@ needTestsuitePackages stg = do
    320 319
       -- This is a hack, but a major usecase for testing the stage1 compiler is
    
    321 320
       -- so that we can use it even if ghc stage2 fails to build
    
    322 321
       -- Unfortunately, we still need the liba
    
    323
    -  let pkgs = filter (\(_,p) -> not $ "iserv" `isInfixOf` pkgName p || ((pkgName p `elem` ["ghc", "Cabal"]) && isStage0 stg))
    
    322
    +  let pkgs = filter (\(_,p) -> not $ (pkgName p `elem` ["ghc", "Cabal"]) && isStage0 stg)
    
    324 323
                         (libpkgs ++ exepkgs ++ [ (stg,timeout) | windowsHost ])
    
    325 324
       need =<< mapM (uncurry pkgFile) pkgs
    
    326
    -  cross <- flag CrossCompiling
    
    327
    -  when (not cross) $ needIservBins stg
    
    328 325
     
    
    329 326
     -- stage 1 ghc lives under stage0/bin,
    
    330 327
     -- stage 2 ghc lives under stage1/bin, etc
    
    ... ... @@ -334,28 +331,6 @@ stageOf "stage2" = Just Stage1
    334 331
     stageOf "stage3" = Just Stage2
    
    335 332
     stageOf _ = Nothing
    
    336 333
     
    
    337
    -needIservBins :: Stage -> Action ()
    
    338
    -needIservBins stg = do
    
    339
    -  let ws = [vanilla, profiling, dynamic]
    
    340
    -  progs <- catMaybes <$> mapM (canBuild stg) ws
    
    341
    -  need progs
    
    342
    -  where
    
    343
    -    -- Only build iserv binaries if all dependencies are built the right
    
    344
    -    -- way already. In particular this fixes the case of no_profiled_libs
    
    345
    -    -- not working with the testsuite, see #19624
    
    346
    -    canBuild (Stage0 {}) _ = pure Nothing
    
    347
    -    canBuild stg w = do
    
    348
    -      contextDeps <- contextDependencies (Context stg iserv w Final)
    
    349
    -      ws <- forM contextDeps $ \c ->
    
    350
    -              interpretInContext c (getLibraryWays <>
    
    351
    -                                    if Context.Type.package c == rts
    
    352
    -                                      then getRtsWays
    
    353
    -                                      else mempty)
    
    354
    -      if (all (w `elem`) ws)
    
    355
    -        then Just <$> programPath (Context stg iserv w Final)
    
    356
    -        else return Nothing
    
    357
    -
    
    358
    -
    
    359 334
     pkgFile :: Stage -> Package -> Action FilePath
    
    360 335
     pkgFile stage pkg
    
    361 336
         | isLibrary pkg = pkgConfFile (Context stage pkg profilingDynamic Final)
    

  • hadrian/src/Settings/Builders/Ghc.hs
    ... ... @@ -168,7 +168,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
    168 168
                 , pure [ "-L" ++ libDir | libDir <- libDirs ]
    
    169 169
                 , rtsFfiArg
    
    170 170
                 , osxTarget ? pure (concat [ ["-framework", fmwk] | fmwk <- fmwks ])
    
    171
    -            , debugged ? packageOneOf [ghc, iservProxy, iserv, remoteIserv] ?
    
    171
    +            , debugged ? packageOneOf [ghc, iservProxy, remoteIserv] ?
    
    172 172
                   arg "-debug"
    
    173 173
                 ]
    
    174 174
     
    

  • hadrian/src/Settings/Default.hs
    ... ... @@ -183,7 +183,6 @@ stage1Packages = do
    183 183
             ]
    
    184 184
           , when (not cross)
    
    185 185
             [ hpcBin
    
    186
    -        , iserv
    
    187 186
             , runGhc
    
    188 187
             , ghcToolchainBin
    
    189 188
             ]
    

  • hadrian/src/Settings/Packages.hs
    ... ... @@ -41,8 +41,6 @@ packageArgs = do
    41 41
         libzstdLibraryDir <- getSetting LibZstdLibDir
    
    42 42
         stageVersion <- readVersion <$> (expr $ ghcVersionStage stage)
    
    43 43
     
    
    44
    -    rtsWays <- getRtsWays
    
    45
    -
    
    46 44
         mconcat
    
    47 45
             --------------------------------- base ---------------------------------
    
    48 46
             [ package base ? mconcat
    
    ... ... @@ -179,23 +177,6 @@ packageArgs = do
    179 177
             , package directory ? builder (Cabal Flags) ? arg "+os-string"
    
    180 178
             , package win32 ? builder (Cabal Flags) ? arg "+os-string"
    
    181 179
     
    
    182
    -        --------------------------------- iserv --------------------------------
    
    183
    -        -- Add -Wl,--export-dynamic enables GHCi to load dynamic objects that
    
    184
    -        -- refer to the RTS.  This is harmless if you don't use it (adds a bit
    
    185
    -        -- of overhead to startup and increases the binary sizes) but if you
    
    186
    -        -- need it there's no alternative.
    
    187
    -        --
    
    188
    -        -- The Solaris linker does not support --export-dynamic option. It also
    
    189
    -        -- does not need it since it exports all dynamic symbols by default
    
    190
    -        , package iserv ? mconcat [
    
    191
    -            expr isElfTarget
    
    192
    -          ? notM (expr $ anyTargetOs [OSFreeBSD, OSSolaris2])? mconcat
    
    193
    -          [ builder (Ghc LinkHs) ? arg "-optl-Wl,--export-dynamic" ]
    
    194
    -
    
    195
    -            -- Link iserv with -threaded if possible
    
    196
    -          , builder (Cabal Flags) ? any (wayUnit Threaded) rtsWays `cabalFlag` "threaded"
    
    197
    -        ]
    
    198
    -
    
    199 180
             -------------------------------- haddock -------------------------------
    
    200 181
             , package haddockApi ?
    
    201 182
               builder (Cabal Flags) ? arg "in-ghc-tree"
    

  • testsuite/tests/driver/T24731.hs deleted
    1
    -{-# LANGUAGE TemplateHaskell #-}
    
    2
    -module T24731 where
    
    3
    -
    
    4
    -foo :: Int
    
    5
    -foo = $([|10|])            

  • testsuite/tests/driver/all.T
    ... ... @@ -333,4 +333,3 @@ test('T25382', normal, makefile_test, [])
    333 333
     test('T26018', req_c, makefile_test, [])
    
    334 334
     test('T24120', normal, compile, ['-Wunused-packages -hide-all-packages -package base -package system-cxx-std-lib'])
    
    335 335
     test('T26551', [extra_files(['T26551.hs'])], makefile_test, [])
    336
    -test('T24731', [only_ways(['ext-interp'])], compile, ['-fexternal-interpreter -pgmi ""'])

  • utils/iserv/iserv.cabal.in deleted
    1
    --- WARNING: iserv.cabal is automatically generated from iserv.cabal.in by
    
    2
    --- ../../configure.  Make sure you are editing iserv.cabal.in, not
    
    3
    --- iserv.cabal.
    
    4
    -
    
    5
    -Name: iserv
    
    6
    -Version: @ProjectVersion@
    
    7
    -Copyright: XXX
    
    8
    -License: BSD3
    
    9
    --- XXX License-File: LICENSE
    
    10
    -Author: XXX
    
    11
    -Maintainer: XXX
    
    12
    -Synopsis: iserv allows GHC to delegate Template Haskell computations
    
    13
    -Description:
    
    14
    -  GHC can be provided with a path to the iserv binary with
    
    15
    -  @-pgmi=/path/to/iserv-bin@, and will in combination with
    
    16
    -  @-fexternal-interpreter@, compile Template Haskell though the
    
    17
    -  @iserv-bin@ delegate. This is very similar to how ghcjs has been
    
    18
    -  compiling Template Haskell, by spawning a separate delegate (so
    
    19
    -  called runner on the javascript vm) and evaluating the splices
    
    20
    -  there.
    
    21
    -
    
    22
    -Category: Development
    
    23
    -build-type: Simple
    
    24
    -cabal-version: >=1.10
    
    25
    -
    
    26
    -Flag threaded
    
    27
    -    Description: Link the iserv executable against the threaded RTS
    
    28
    -    Default: True
    
    29
    -    Manual: True
    
    30
    -
    
    31
    -Executable iserv
    
    32
    -    Default-Language: Haskell2010
    
    33
    -    -- We never know what symbols GHC will look up in the future, so we
    
    34
    -    -- must retain CAFs for running interpreted code.
    
    35
    -    ghc-options: -fkeep-cafs -rtsopts
    
    36
    -    if flag(threaded)
    
    37
    -      ghc-options: -threaded
    
    38
    -    Main-Is: Main.hs
    
    39
    -    Hs-Source-Dirs: src
    
    40
    -    include-dirs: .
    
    41
    -    Build-Depends:
    
    42
    -      base >= 4   && < 5,
    
    43
    -      ghci == @ProjectVersionMunged@

  • utils/iserv/src/Main.hs deleted
    1
    --- |
    
    2
    --- The Remote GHCi server.
    
    3
    ---
    
    4
    --- For details on Remote GHCi, see Note [Remote GHCi] in
    
    5
    --- compiler/GHC/Runtime/Interpreter.hs.
    
    6
    ---
    
    7
    -module Main (main) where
    
    8
    -
    
    9
    -import GHCi.Server (defaultServer)
    
    10
    -
    
    11
    -main :: IO ()
    
    12
    -main = defaultServer