[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: Implement -ddump-c-backend argument

Marge Bot gitlab at gitlab.haskell.org
Sun Nov 22 11:59:05 UTC 2020



 Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00
Implement -ddump-c-backend argument

To dump output of the C backend.

- - - - -
8e596cdf by Ben Gamari at 2020-11-22T06:58:56-05:00
Bump time submodule to 1.11.1

Also bumps directory, Cabal, hpc, time, and unix submodules.

Closes #18847.

- - - - -
412e039c by Ben Gamari at 2020-11-22T06:58:56-05:00
hadrian: Dump STG when ticky is enabled

This changes the "ticky" modifier to enable dumping of final STG as this
is generally needed to make sense of the ticky profiles.

- - - - -
9105f6e8 by Ben Gamari at 2020-11-22T06:58:56-05:00
hadrian: Introduce notion of flavour transformers

This extends Hadrian's notion of "flavour", as described in #18942.

- - - - -
4b26b802 by Ben Gamari at 2020-11-22T06:58:56-05:00
hadrian: Add a viaLlvmBackend modifier

Note that this also slightly changes the semantics of these flavours as
we only use LLVM for >= stage1 builds.

- - - - -
909934ed by Ben Gamari at 2020-11-22T06:58:56-05:00
hadrian: Add profiled_ghc and no_dynamic_ghc modifiers

- - - - -
d1f30757 by Ben Gamari at 2020-11-22T06:58:56-05:00
hadrian: Drop redundant flavour definitions

Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as
these can now be realized with flavour transformers.

- - - - -


20 changed files:

- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Session.hs
- compiler/ghc.cabal.in
- docs/users_guide/debugging.rst
- ghc/ghc-bin.cabal.in
- hadrian/doc/flavours.md
- hadrian/hadrian.cabal
- hadrian/src/Flavour.hs
- hadrian/src/Settings.hs
- − hadrian/src/Settings/Flavours/Llvm.hs
- − hadrian/src/Settings/Flavours/Profiled.hs
- − hadrian/src/Settings/Flavours/ThreadSanitizer.hs
- libraries/Cabal
- libraries/directory
- libraries/hpc
- libraries/time
- libraries/unix
- utils/ghc-cabal/Main.hs
- utils/ghc-cabal/ghc.mk


Changes:

=====================================
compiler/GHC/Driver/CodeOutput.hs
=====================================
@@ -138,7 +138,13 @@ outputC dflags filenm cmm_stream packages =
       hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n")
       hPutStr h "#include \"Stg.h\"\n"
       let platform = targetPlatform dflags
-          writeC = printForC dflags h . cmmToC platform
+          writeC cmm = do
+            let doc = cmmToC platform cmm
+            dumpIfSet_dyn dflags Opt_D_dump_c_backend
+                          "C backend output"
+                          FormatC
+                          doc
+            printForC dflags h doc
       Stream.consume cmm_stream writeC
 
 {-


=====================================
compiler/GHC/Driver/Flags.hs
=====================================
@@ -49,6 +49,7 @@ data DumpFlag
    | Opt_D_dump_asm_conflicts
    | Opt_D_dump_asm_stats
    | Opt_D_dump_asm_expanded
+   | Opt_D_dump_c_backend
    | Opt_D_dump_llvm
    | Opt_D_dump_core_stats
    | Opt_D_dump_deriv


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -2539,6 +2539,8 @@ dynamic_flags_deps = [
         (setDumpFlag Opt_D_dump_asm_expanded)
   , make_ord_flag defGhcFlag "ddump-llvm"
         (NoArg $ setObjBackend LLVM >> setDumpFlag' Opt_D_dump_llvm)
+  , make_ord_flag defGhcFlag "ddump-c-backend"
+        (NoArg $ setDumpFlag' Opt_D_dump_c_backend)
   , make_ord_flag defGhcFlag "ddump-deriv"
         (setDumpFlag Opt_D_dump_deriv)
   , make_ord_flag defGhcFlag "ddump-ds"


=====================================
compiler/ghc.cabal.in
=====================================
@@ -63,7 +63,7 @@ Library
                    process    >= 1   && < 1.7,
                    bytestring >= 0.9 && < 0.11,
                    binary     == 0.8.*,
-                   time       >= 1.4 && < 1.10,
+                   time       >= 1.4 && < 1.12,
                    containers >= 0.6.2.1 && < 0.7,
                    array      >= 0.1 && < 0.6,
                    filepath   >= 1   && < 1.5,


=====================================
docs/users_guide/debugging.rst
=====================================
@@ -552,6 +552,15 @@ LLVM code generator
 
     LLVM code from the :ref:`LLVM code generator <llvm-code-gen>`
 
+C code generator
+~~~~~~~~~~~~~~~~
+
+.. ghc-flag:: -ddump-c-backend
+    :shortdesc: Dump C code produced by the C (unregisterised) backend.
+    :type: dynamic
+
+    :shortdesc: Dump C code produced by the C (unregisterised) backend.
+
 Native code generator
 ~~~~~~~~~~~~~~~~~~~~~
 


=====================================
ghc/ghc-bin.cabal.in
=====================================
@@ -63,7 +63,7 @@ Executable ghc
             ghci           == @ProjectVersionMunged@,
             haskeline      == 0.8.*,
             exceptions     == 0.10.*,
-            time           >= 1.8 && < 1.10
+            time           >= 1.8 && < 1.12
         CPP-Options: -DHAVE_INTERNAL_INTERPRETER
         Other-Modules:
             GHCi.Leak


=====================================
hadrian/doc/flavours.md
=====================================
@@ -99,16 +99,6 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH
     <td>-O</td>
     <td>-O2</td>
   </tr>
-  <tr>
-    <th>prof</td>
-    <td>-O0<br>-H64m</td>
-    <td>-O0<br>-H64m</td>
-    <td></td>
-    <td>-O</td>
-    <td>-O2</td>
-    <td>-O</td>
-    <td>-O</td>
-  </tr>
   <tr>
     <th>bench</td>
     <td>-O<br>-H64m</td>
@@ -166,13 +156,66 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH
   </tr>
 </table>
 
-### LLVM variants
+## Flavour transformers
 
-In addition to the above, there are LLVM variants for the flavours `quick`,
-`prof`, `perf` and `bench`, available by appending a `-llvm` suffix (i.e.,
-`quick-llvm` for the LLVM variant of `quick`). These differ only in that there
-is an additional `-fllvm` flag in `hsDefault` when the stage0 compiler is GHC.
-See `src/Settings/Flavours/Llvm.hs` for details.
+Each of the flavours described above is intended as a starting-point for
+configuring your GHC build. In addition, Hadrian supports a number of "flavour
+transformers" which modify the configuration in various ways.
+
+These can be appended to the flavour name passed via the `--flavour`
+command-line flag, separated by the `+` character. For instance,
+
+```
+hadrian --flavour=perf+thread_sanitizer
+```
+
+The supported transformers are listed below:
+
+<table>
+    <tr>
+        <th>Transformer name</th>
+        <th>Effect</th>
+    </tr>
+    <tr>
+        <td><code>werror</code></td>
+        <td>Use the `-Werror` flag for all stage1+ compilation.</td>
+    </tr>
+    <tr>
+        <td><code>debug_info</code></td>
+        <td>Enable production of native debugging information (via GHC/GCC's `-g3`)
+            during stage1+ compilations.</td>
+    </tr>
+    <tr>
+        <td><code>ticky_ghc</code></td>
+        <td>Compile the GHC executable with Ticky-Ticky profiler support.</td>
+    </tr>
+    <tr>
+        <td><code>split_sections</code></td>
+        <td>Enable section splitting for all libraries (except for the GHC
+            library due to the long linking times that this causes).</td>
+    </tr>
+    <tr>
+        <td><code>thread_sanitizer</code></td>
+        <td>Build the runtime system with ThreadSanitizer support</td>
+    </tr>
+    <tr>
+        <td><code>llvm</code></td>
+        <td>Use GHC's LLVM backend (`-fllvm`) for all stage1+ compilation.</td>
+    </tr>
+    <tr>
+        <td><code>profiled_ghc</code></td>
+        <td>Build the GHC executable with cost-centre profiling support.
+            It is that you use this in conjunction with `no_dynamic_ghc` since
+            GHC does not It is support loading of profiled libraries with the
+            dynamically-linker.</td>
+    </tr>
+    <tr>
+        <td><code>no_dynamic_ghc</code></td>
+        <td>Linked GHC against the statically-linked RTS. This causes GHC to
+            default to loading static rather than dynamic library when,
+            e.g., loading libraries during TemplateHaskell evaluations.</td>
+    </tr>
+</table>
 
 ## Ways
 
@@ -184,7 +227,6 @@ information. The following table lists ways that are built in different flavours
         <th rowspan="2">Flavour</th>
         <th colspan="2">Library ways</th>
         <th colspan="2">RTS ways</th>
-        <th colspan="2">Profiled GHC</th>
     </tr>
     <tr>
         <th>stage0</th>
@@ -195,7 +237,7 @@ information. The following table lists ways that are built in different flavours
         <th>stage1+</th>
     </tr>
     <tr>
-    <th>default<br>perf<br>prof<br>devel1<br>devel2<br>perf-llvm<br>prof-llvm</td>
+    <th>default<br>perf<br>prof<br>devel1<br>devel2</td>
     <td>vanilla</td>
     <td>vanilla<br>profiling<br>dynamic</td>
     <td>logging<br>debug<br>threaded<br>threadedDebug<br>threadedLogging
@@ -208,11 +250,9 @@ information. The following table lists ways that are built in different flavours
         <br>debugDynamic<br>threadedDynamic<br>threadedDebugDynamic
         <br>loggingDynamic<br>threadedLoggingDynamic
     </td>
-    <td>Only in<br>prof<br>flavour</td>
-    <td>Only in<br>prof<br>flavour</td>
 </tr>
 <tr>
-    <th>quick<br>quick-llvm<br>quick-validate<br>quick-debug</th>
+    <th>quick<br>quick-validate<br>quick-debug</th>
     <td>vanilla</td>
     <td>vanilla<br>dynamic</td>
     <td>logging<br>debug<br>threaded<br>threadedDebug<br>threadedLogging
@@ -223,8 +263,6 @@ information. The following table lists ways that are built in different flavours
         <br>debugDynamic<br>threadedDynamic<br>threadedDebugDynamic
         <br>loggingDynamic<br>threadedLoggingDynamic
     </td>
-    <td>No</td>
-    <td>No</td>
 </tr>
 <tr>
     <th>quickest<br>bench</th>
@@ -232,7 +270,5 @@ information. The following table lists ways that are built in different flavours
     <td>vanilla</td>
     <td>vanilla<br>threaded</td>
     <td>vanilla<br>threaded</td>
-    <td>No</td>
-    <td>No</td>
 </tr>
 </table>


=====================================
hadrian/hadrian.cabal
=====================================
@@ -106,13 +106,10 @@ executable hadrian
                        , Settings.Flavours.Benchmark
                        , Settings.Flavours.Development
                        , Settings.Flavours.GhcInGhci
-                       , Settings.Flavours.Llvm
                        , Settings.Flavours.Performance
-                       , Settings.Flavours.Profiled
                        , Settings.Flavours.Quick
                        , Settings.Flavours.QuickCross
                        , Settings.Flavours.Quickest
-                       , Settings.Flavours.ThreadSanitizer
                        , Settings.Flavours.Validate
                        , Settings.Packages
                        , Settings.Parser


=====================================
hadrian/src/Flavour.hs
=====================================
@@ -1,17 +1,28 @@
 module Flavour
   ( Flavour (..), werror
   , DocTargets, DocTarget(..)
+  , parseFlavour
     -- * Flavour transformers
+  , flavourTransformers
   , addArgs
   , splitSections, splitSectionsIf
   , enableThreadSanitizer
   , enableDebugInfo, enableTickyGhc
+  , viaLlvmBackend
+  , enableProfiledGhc
+  , disableDynamicGhcPrograms
   ) where
 
 import Expression
 import Data.Set (Set)
+import Data.Map (Map)
+import qualified Data.Map as M
 import Packages
 
+import Text.Parsec.Prim as P
+import Text.Parsec.Combinator as P
+import Text.Parsec.Char as P
+
 -- Please update doc/{flavours.md, user-settings.md} when changing this file.
 -- | 'Flavour' is a collection of build settings that fully define a GHC build.
 -- Note the following type semantics:
@@ -69,6 +80,58 @@ type DocTargets = Set DocTarget
 data DocTarget = Haddocks | SphinxHTML | SphinxPDFs | SphinxMan | SphinxInfo
   deriving (Eq, Ord, Show, Bounded, Enum)
 
+flavourTransformers :: Map String (Flavour -> Flavour)
+flavourTransformers = M.fromList
+    [ "werror" =: werror
+    , "debug_info" =: enableDebugInfo
+    , "ticky_ghc" =: enableTickyGhc
+    , "split_sections" =: splitSections
+    , "thread_sanitizer" =: enableThreadSanitizer
+    , "llvm" =: viaLlvmBackend
+    , "profiled_ghc" =: enableProfiledGhc
+    , "no_dynamic_ghc" =: disableDynamicGhcPrograms
+    ]
+  where (=:) = (,)
+
+type Parser = Parsec String ()
+
+parseFlavour :: [Flavour]  -- ^ base flavours
+             -> Map String (Flavour -> Flavour) -- ^ modifiers
+             -> String
+             -> Either String Flavour
+parseFlavour baseFlavours transformers str =
+    case P.runParser parser () "" str of
+      Left perr -> Left $ unlines $
+                    [ "error parsing flavour specifier: " ++ show perr
+                    , ""
+                    , "known flavours:"
+                    ] ++
+                    [ "  " ++ name f | f <- baseFlavours ] ++
+                    [ ""
+                    , "known flavour transformers:"
+                    ] ++
+                    [ "  " ++ nm | nm <- M.keys transformers ]
+      Right f -> Right f
+  where
+    parser :: Parser Flavour
+    parser = do
+      base <- baseFlavour
+      transs <- P.many flavourTrans
+      return $ foldr ($) base transs
+
+    baseFlavour :: Parser Flavour
+    baseFlavour =
+        P.choice [ f <$ P.try (P.string (name f))
+                 | f <- baseFlavours
+                 ]
+
+    flavourTrans :: Parser (Flavour -> Flavour)
+    flavourTrans = do
+        void $ P.char '+'
+        P.choice [ trans <$ P.try (P.string nm)
+                 | (nm, trans) <- M.toList transformers
+                 ]
+
 -- | Add arguments to the 'args' of a 'Flavour'.
 addArgs :: Args -> Flavour -> Flavour
 addArgs args' fl = fl { args = args fl <> args' }
@@ -96,7 +159,13 @@ enableTickyGhc =
       [ builder (Ghc CompileHs) ? ticky
       , builder (Ghc LinkHs) ? ticky
       ]
-    ticky = arg "-ticky" <> arg "-ticky-allocd"
+    ticky = mconcat
+      [ arg "-ticky"
+      , arg "-ticky-allocd"
+      -- You generally need STG dumps to interpret ticky profiles
+      , arg "-ddump-to-file"
+      , arg "-ddump-stg-final"
+      ]
 
 -- | Transform the input 'Flavour' so as to build with
 --   @-split-sections@ whenever appropriate. You can
@@ -128,3 +197,17 @@ enableThreadSanitizer = addArgs $ mconcat
     , builder (Cabal Flags) ? arg "thread-sanitizer"
     , builder  RunTest ? arg "--config=have_thread_sanitizer=True"
     ]
+
+-- | Use the LLVM backend in stages 1 and later.
+viaLlvmBackend :: Flavour -> Flavour
+viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm"
+
+-- | Build the GHC executable with profiling enabled. It is also recommended
+-- that you use this with @'dynamicGhcPrograms' = False@ since GHC does not
+-- support loading of profiled libraries with the dynamically-linker.
+enableProfiledGhc :: Flavour -> Flavour
+enableProfiledGhc flavour = flavour { ghcProfiled = True }
+
+-- | Disable 'dynamicGhcPrograms'.
+disableDynamicGhcPrograms :: Flavour -> Flavour
+disableDynamicGhcPrograms flavour = flavour { dynamicGhcPrograms = pure False }


=====================================
hadrian/src/Settings.hs
=====================================
@@ -15,13 +15,10 @@ import {-# SOURCE #-} Settings.Default
 import Settings.Flavours.Benchmark
 import Settings.Flavours.Development
 import Settings.Flavours.GhcInGhci
-import Settings.Flavours.Llvm
 import Settings.Flavours.Performance
-import Settings.Flavours.Profiled
 import Settings.Flavours.Quick
 import Settings.Flavours.Quickest
 import Settings.Flavours.QuickCross
-import Settings.Flavours.ThreadSanitizer
 import Settings.Flavours.Validate
 
 import Control.Monad.Except
@@ -54,13 +51,11 @@ stagePackages stage = do
 hadrianFlavours :: [Flavour]
 hadrianFlavours =
     [ benchmarkFlavour, defaultFlavour, developmentFlavour Stage1
-    , developmentFlavour Stage2, performanceFlavour, profiledFlavour
+    , developmentFlavour Stage2, performanceFlavour
     , quickFlavour, quickValidateFlavour, quickDebugFlavour
     , quickestFlavour
-    , quickCrossFlavour, benchmarkLlvmFlavour
-    , performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour
-    , ghcInGhciFlavour, validateFlavour, slowValidateFlavour
-    , threadSanitizerFlavour ]
+    , quickCrossFlavour
+    , ghcInGhciFlavour, validateFlavour, slowValidateFlavour ]
 
 -- | This action looks up a flavour with the name given on the
 --   command line with @--flavour@, defaulting to 'userDefaultFlavour'
@@ -75,11 +70,9 @@ flavour = do
     let flavours = hadrianFlavours ++ userFlavours
         (_settingErrs, tweak) = applySettings kvs
 
-    return $
-      case filter (\fl -> name fl == flavourName) flavours of
-        []  -> error $ "Unknown build flavour: " ++ flavourName
-        [f] -> tweak f
-        _   -> error $ "Multiple build flavours named " ++ flavourName
+    case parseFlavour flavours flavourTransformers flavourName of
+      Left err -> fail err
+      Right f -> return $ tweak f
 
 -- TODO: switch to Set Package as the order of packages should not matter?
 -- Otherwise we have to keep remembering to sort packages from time to time.


=====================================
hadrian/src/Settings/Flavours/Llvm.hs deleted
=====================================
@@ -1,29 +0,0 @@
-module Settings.Flavours.Llvm (
-  benchmarkLlvmFlavour,
-  performanceLlvmFlavour,
-  profiledLlvmFlavour,
-  quickLlvmFlavour,
-) where
-
-import Expression
-import Flavour
-
-import Settings.Flavours.Benchmark
-import Settings.Flavours.Performance
-import Settings.Flavours.Profiled
-import Settings.Flavours.Quick
-
--- Please update doc/flavours.md when changing this file.
-benchmarkLlvmFlavour, performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour :: Flavour
-benchmarkLlvmFlavour   = mkLlvmFlavour benchmarkFlavour
-performanceLlvmFlavour = mkLlvmFlavour performanceFlavour
-profiledLlvmFlavour    = mkLlvmFlavour profiledFlavour
-quickLlvmFlavour       = mkLlvmFlavour quickFlavour
-
--- | Turn a flavour into an LLVM flavour
-mkLlvmFlavour :: Flavour -> Flavour
-mkLlvmFlavour flav = flav
-    { name = name flav ++ "-llvm"
-    , args = mconcat [ args flav
-                     , builder Ghc ? arg "-fllvm" ]
-    }


=====================================
hadrian/src/Settings/Flavours/Profiled.hs deleted
=====================================
@@ -1,22 +0,0 @@
-module Settings.Flavours.Profiled (profiledFlavour) where
-
-import Expression
-import Flavour
-import {-# SOURCE #-} Settings.Default
-
--- Please update doc/flavours.md when changing this file.
-profiledFlavour :: Flavour
-profiledFlavour = defaultFlavour
-    { name        = "prof"
-    , args        = defaultBuilderArgs <> profiledArgs <> defaultPackageArgs
-    , ghcProfiled = True
-    , dynamicGhcPrograms = pure False }
-
-profiledArgs :: Args
-profiledArgs = sourceArgs SourceArgs
-    { hsDefault  = mconcat
-        [ pure ["-O0", "-H64m"]
-        ]
-    , hsLibrary  = notStage0 ? arg "-O"
-    , hsCompiler = mconcat [stage0 ? arg "-O2", notStage0 ? arg "-O"]
-    , hsGhc      = arg "-O" }


=====================================
hadrian/src/Settings/Flavours/ThreadSanitizer.hs deleted
=====================================
@@ -1,9 +0,0 @@
-module Settings.Flavours.ThreadSanitizer (threadSanitizerFlavour) where
-
-import Flavour
-import Settings.Flavours.Validate
-
-threadSanitizerFlavour :: Flavour
-threadSanitizerFlavour =
-  enableThreadSanitizer (validateFlavour
-    { name = "thread-sanitizer" })


=====================================
libraries/Cabal
=====================================
@@ -1 +1 @@
-Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f
+Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884


=====================================
libraries/directory
=====================================
@@ -1 +1 @@
-Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e
+Subproject commit 0633b48b010093f64f98ee494265436e96456aed


=====================================
libraries/hpc
=====================================
@@ -1 +1 @@
-Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69
+Subproject commit 59e6ba02f3fa5c8f4901b4ce21777c4a9beb14b6


=====================================
libraries/time
=====================================
@@ -1 +1 @@
-Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c
+Subproject commit c25d6a76702b454426e149fb590da5cb69f3bd0a


=====================================
libraries/unix
=====================================
@@ -1 +1 @@
-Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6
+Subproject commit e079823775066bcab56b22842be6cce6e060fb9f


=====================================
utils/ghc-cabal/Main.hs
=====================================
@@ -1,3 +1,4 @@
+{-# LANGUAGE CPP #-}
 {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
 {-# OPTIONS_GHC -Wno-incomplete-uni-patterns    #-}
 
@@ -28,6 +29,7 @@ import Distribution.Verbosity
 import qualified Distribution.InstalledPackageInfo as Installed
 import qualified Distribution.Simple.PackageIndex as PackageIndex
 import Distribution.Utils.ShortText (fromShortText)
+import Distribution.Utils.Path (getSymbolicPath)
 
 import Control.Exception (bracket)
 import Control.Monad
@@ -433,7 +435,7 @@ generate directory distdir config_args
                 variablePrefix ++ "_MODULES = " ++ unwords mods,
                 variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods,
                 variablePrefix ++ "_SYNOPSIS =" ++ (unwords $ lines $ fromShortText $ synopsis pd),
-                variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (hsSourceDirs bi),
+                variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (map getSymbolicPath $ hsSourceDirs bi),
                 variablePrefix ++ "_DEPS = " ++ unwords deps,
                 variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids,
                 variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames,


=====================================
utils/ghc-cabal/ghc.mk
=====================================
@@ -38,20 +38,20 @@ $(ghc-cabal_INPLACE) : $(ghc-cabal_DIST_BINARY) | $$(dir $$@)/.
 	"$(CP)" $< $@
 
 # Minor hack, since we can't reuse the `hs-suffix-rules-srcdir` macro
-ifneq ($(wildcard libraries/Cabal/Cabal/Distribution/Fields/Lexer.x),)
+ifneq ($(wildcard libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x),)
 # Lexer.x exists so we have to call Alex ourselves
-CABAL_LEXER_DEP := bootstrapping/Cabal/Distribution/Fields/Lexer.hs
+CABAL_LEXER_DEP := bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs
 
-bootstrapping/Cabal/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/Distribution/Fields/Lexer.x
-	mkdir -p bootstrapping/Cabal/Distribution/Fields
+bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x
+	mkdir -p bootstrapping/Cabal/src/Distribution/Fields
 	$(call cmd,ALEX) $< -o $@
 else
-CABAL_LEXER_DEP := libraries/Cabal/Cabal/Distribution/Fields/Lexer.hs
+CABAL_LEXER_DEP := libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.hs
 endif
 
-$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*/*.hs)
-$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*.hs)
-$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*.hs)
+$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*/*.hs)
+$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*.hs)
+$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*.hs)
 
 # N.B. Compile with -O0 since this is not a performance-critical executable
 # and the Cabal takes nearly twice as long to build with -O1. See #16817.
@@ -70,7 +70,7 @@ $(ghc-cabal_DIST_BINARY): $(CABAL_LEXER_DEP) utils/ghc-cabal/Main.hs $(TOUCH_DEP
 	       -odir  bootstrapping \
 	       -hidir bootstrapping \
 	       $(CABAL_LEXER_DEP) \
-	       -ilibraries/Cabal/Cabal \
+	       -ilibraries/Cabal/Cabal/src \
 	       -ilibraries/binary/src \
 	       -ilibraries/filepath \
 	       -ilibraries/hpc \



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/26a7c37fa3b176820a52de54daef7b9c8cce91d0...d1f30757d5a951a342ec6170e84795b8ed3efa5f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/26a7c37fa3b176820a52de54daef7b9c8cce91d0...d1f30757d5a951a342ec6170e84795b8ed3efa5f
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/20201122/69ed71f7/attachment-0001.html>


More information about the ghc-commits mailing list