[Git][ghc/ghc][master] Hadrian: fix ghcDebugged and document it

Marge Bot gitlab at gitlab.haskell.org
Thu Apr 18 12:24:22 UTC 2019



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


Commits:
4c8a67a4 by Alp Mestanogullari at 2019-04-18T12:18:18Z
Hadrian: fix ghcDebugged and document it

- - - - -


4 changed files:

- hadrian/doc/user-settings.md
- hadrian/src/Expression.hs
- hadrian/src/Packages.hs
- hadrian/src/Settings/Builders/Ghc.hs


Changes:

=====================================
hadrian/doc/user-settings.md
=====================================
@@ -114,6 +114,21 @@ devel2WerrorFlavour :: Flavour
 devel2WerrorFlavour = werror (developmentFlavour Stage2)
 ```
 
+### Linking GHC against the debugged RTS
+
+What was previously achieved by having `GhcDebugged=YES` in `mk/build.mk` can
+be done by defining a custom flavour in the user settings file, one that
+sets the `ghcDebugged` field of `Flavour` to `True`, e.g:
+
+``` haskell
+quickDebug :: Flavour
+quickDebug = quickFlavour { name = "dbg", ghcDebugged = True }
+```
+
+Running `build --flavour=dbg` will build a `quick`-flavoured GHC and link
+GHC, iserv, iserv-proxy and remote-iserv against the debugged RTS, by passing
+`-debug` to the commands that link those executables.
+
 ## Packages
 
 Users can add and remove packages from particular build stages. As an example,


=====================================
hadrian/src/Expression.hs
=====================================
@@ -7,7 +7,7 @@ module Expression (
 
     -- ** Predicates
     (?), stage, stage0, stage1, stage2, notStage0, package, notPackage,
-    libraryPackage, builder, way, input, inputs, output, outputs,
+     packageOneOf, libraryPackage, builder, way, input, inputs, output, outputs,
 
     -- ** Evaluation
     interpret, interpretInContext,
@@ -44,6 +44,9 @@ stage s = (s ==) <$> getStage
 package :: Package -> Predicate
 package p = (p ==) <$> getPackage
 
+packageOneOf :: [Package] -> Predicate
+packageOneOf ps = (`elem` ps) <$> getPackage
+
 -- | This type class allows the user to construct both precise builder
 -- predicates, such as @builder (Ghc CompileHs Stage1)@, as well as predicates
 -- covering a set of similar builders. For example, @builder (Ghc CompileHs)@


=====================================
hadrian/src/Packages.hs
=====================================
@@ -5,10 +5,10 @@ module Packages (
     compareSizes, compiler, containers, deepseq, deriveConstants, directory,
     filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCompact,
     ghcHeap, ghci, ghcPkg, ghcPrim, haddock, haskeline,
-    hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi,
-    libiserv, mtl, parsec, pretty, primitive, process, rts, runGhc,
-    stm, templateHaskell, terminfo, text, time, timeout, touchy, transformers,
-    unlit, unix, win32, xhtml, ghcPackages, isGhcPackage,
+    hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy,
+    libffi, libiserv, mtl, parsec, pretty, primitive, process, remoteIserv, rts,
+    runGhc, stm, templateHaskell, terminfo, text, time, timeout, touchy,
+    transformers, unlit, unix, win32, xhtml, ghcPackages, isGhcPackage,
 
     -- * Package information
     programName, nonHsMainPackage, autogenPath, programPath, timeoutPath,
@@ -78,6 +78,7 @@ hpcBin              = util "hpc-bin"         `setPath` "utils/hpc"
 integerGmp          = lib  "integer-gmp"
 integerSimple       = lib  "integer-simple"
 iserv               = util "iserv"
+iservProxy          = util "iserv-proxy"
 libffi              = top  "libffi"
 libiserv            = lib  "libiserv"
 mtl                 = lib  "mtl"
@@ -85,6 +86,7 @@ parsec              = lib  "parsec"
 pretty              = lib  "pretty"
 primitive           = lib  "primitive"
 process             = lib  "process"
+remoteIserv         = util "remote-iserv"
 rts                 = top  "rts"
 runGhc              = util "runghc"
 stm                 = lib  "stm"


=====================================
hadrian/src/Settings/Builders/Ghc.hs
=====================================
@@ -3,6 +3,7 @@ module Settings.Builders.Ghc (ghcBuilderArgs, haddockGhcArgs) where
 import Hadrian.Haskell.Cabal
 import Hadrian.Haskell.Cabal.Type
 
+import Flavour
 import Packages
 import Settings.Builders.Common
 import Settings.Warnings
@@ -69,6 +70,7 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
     useSystemFfi <- expr (flag UseSystemFfi)
     buildPath <- getBuildPath
     libffiName' <- libffiName
+    debugged <- ghcDebugged <$> expr flavour
 
     let
         dynamic = Dynamic `wayUnit` way
@@ -110,6 +112,9 @@ ghcLinkArgs = builder (Ghc LinkHs) ? do
             , pure [ "-L" ++ libDir | libDir <- libDirs ]
             , rtsFfiArg
             , darwin ? pure (concat [ ["-framework", fmwk] | fmwk <- fmwks ])
+            , debugged ? packageOneOf [ghc, iservProxy, iserv, remoteIserv] ?
+              arg "-debug"
+
             ]
 
 findHsDependencies :: Args



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/4c8a67a4b025774993b80442fb3654c8868c1d24

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/4c8a67a4b025774993b80442fb3654c8868c1d24
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190418/8d1fda93/attachment-0001.html>


More information about the ghc-commits mailing list