[commit: ghc] master: Work around the "can't use Natural in base" problem on a per-flavour basis (#676) (1bbc4b3)

git at git.haskell.org git at git.haskell.org
Tue Oct 23 20:20:01 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/1bbc4b3b620562c673ee0871254e3cae3e3cb232/ghc

>---------------------------------------------------------------

commit 1bbc4b3b620562c673ee0871254e3cae3e3cb232
Author: Alp Mestanogullari <alpmestan at gmail.com>
Date:   Wed Sep 5 19:41:45 2018 +0200

    Work around the "can't use Natural in base" problem on a per-flavour basis (#676)
    
    * Work around the "can't use natural in base" problem on a per-flavour basis
    
    The only flavours that need the workaround are the ones that build
    GHC/{Natural, Num}.hs with -O0, namely 'quick', 'quickest' and 'prof'.
    This patches defines the necessary arguments in one place and uses them
    in all the aforementionned flavour definitions.
    
    This will allow us to have both quick/quickest/prof builds that come through
    as well as an efficient compiler when we want it (with e.g perf), which wasn't
    the case before my series of patches for this problem.
    
    * address @snowleopard's feedback


>---------------------------------------------------------------

1bbc4b3b620562c673ee0871254e3cae3e3cb232
 hadrian.cabal                       |  1 +
 src/Settings/Flavours/Common.hs     | 11 +++++++++++
 src/Settings/Flavours/Profiled.hs   |  6 +++++-
 src/Settings/Flavours/Quick.hs      |  6 +++++-
 src/Settings/Flavours/QuickCross.hs |  6 +++++-
 src/Settings/Flavours/Quickest.hs   |  6 +++++-
 6 files changed, 32 insertions(+), 4 deletions(-)

diff --git a/hadrian.cabal b/hadrian.cabal
index 6bb0d73..2fd2c8c 100644
--- a/hadrian.cabal
+++ b/hadrian.cabal
@@ -87,6 +87,7 @@ executable hadrian
                        , Settings.Builders.RunTest
                        , Settings.Builders.Xelatex
                        , Settings.Default
+                       , Settings.Flavours.Common
                        , Settings.Flavours.Development
                        , Settings.Flavours.Performance
                        , Settings.Flavours.Profiled
diff --git a/src/Settings/Flavours/Common.hs b/src/Settings/Flavours/Common.hs
new file mode 100644
index 0000000..a1eb2fb
--- /dev/null
+++ b/src/Settings/Flavours/Common.hs
@@ -0,0 +1,11 @@
+module Settings.Flavours.Common where
+
+import Expression
+
+-- See https://ghc.haskell.org/trac/ghc/ticket/15286 and
+-- https://phabricator.haskell.org/D4880
+naturalInBaseFixArgs :: Args
+naturalInBaseFixArgs = mconcat
+  [ input "//Natural.hs" ? pure ["-fno-omit-interface-pragmas"]
+  , input "//Num.hs" ? pure ["-fno-ignore-interface-pragmas"]
+  ]
diff --git a/src/Settings/Flavours/Profiled.hs b/src/Settings/Flavours/Profiled.hs
index d56cc10..91b7f3b 100644
--- a/src/Settings/Flavours/Profiled.hs
+++ b/src/Settings/Flavours/Profiled.hs
@@ -3,6 +3,7 @@ module Settings.Flavours.Profiled (profiledFlavour) where
 import Expression
 import Flavour
 import {-# SOURCE #-} Settings.Default
+import Settings.Flavours.Common (naturalInBaseFixArgs)
 
 -- Please update doc/flavours.md when changing this file.
 profiledFlavour :: Flavour
@@ -13,7 +14,10 @@ profiledFlavour = defaultFlavour
 
 profiledArgs :: Args
 profiledArgs = sourceArgs SourceArgs
-    { hsDefault  = pure ["-O0", "-H64m"]
+    { hsDefault  = mconcat
+        [ pure ["-O0", "-H64m"]
+        , naturalInBaseFixArgs
+        ]
     , hsLibrary  = notStage0 ? arg "-O"
     , hsCompiler = arg "-O"
     , hsGhc      = arg "-O" }
diff --git a/src/Settings/Flavours/Quick.hs b/src/Settings/Flavours/Quick.hs
index 99dade9..3da1dcf 100644
--- a/src/Settings/Flavours/Quick.hs
+++ b/src/Settings/Flavours/Quick.hs
@@ -4,6 +4,7 @@ import Expression
 import Flavour
 import Oracles.Flag
 import {-# SOURCE #-} Settings.Default
+import Settings.Flavours.Common (naturalInBaseFixArgs)
 
 -- Please update doc/flavours.md when changing this file.
 quickFlavour :: Flavour
@@ -16,7 +17,10 @@ quickFlavour = defaultFlavour
 
 quickArgs :: Args
 quickArgs = sourceArgs SourceArgs
-    { hsDefault  = pure ["-O0", "-H64m"]
+    { hsDefault  = mconcat $
+        [ pure ["-O0", "-H64m"]
+        , naturalInBaseFixArgs
+        ]
     , hsLibrary  = notStage0 ? arg "-O"
     , hsCompiler =    stage0 ? arg "-O"
     , hsGhc      =    stage0 ? arg "-O" }
diff --git a/src/Settings/Flavours/QuickCross.hs b/src/Settings/Flavours/QuickCross.hs
index 3d0c410..cfc3586 100644
--- a/src/Settings/Flavours/QuickCross.hs
+++ b/src/Settings/Flavours/QuickCross.hs
@@ -4,6 +4,7 @@ import Expression
 import Flavour
 import Oracles.Flag
 import {-# SOURCE #-} Settings.Default
+import Settings.Flavours.Common
 
 -- Please update doc/flavours.md when changing this file.
 quickCrossFlavour :: Flavour
@@ -16,7 +17,10 @@ quickCrossFlavour = defaultFlavour
 
 quickCrossArgs :: Args
 quickCrossArgs = sourceArgs SourceArgs
-    { hsDefault  = pure ["-O0", "-H64m"]
+    { hsDefault  = mconcat $
+        [ pure ["-O0", "-H64m"]
+        , naturalInBaseFixArgs
+        ]
     , hsLibrary  = notStage0 ? mconcat [ arg "-O", arg "-fllvm" ]
     , hsCompiler = stage0 ? arg "-O"
     , hsGhc      = mconcat
diff --git a/src/Settings/Flavours/Quickest.hs b/src/Settings/Flavours/Quickest.hs
index 836b935..2bcfac4 100644
--- a/src/Settings/Flavours/Quickest.hs
+++ b/src/Settings/Flavours/Quickest.hs
@@ -3,6 +3,7 @@ module Settings.Flavours.Quickest (quickestFlavour) where
 import Expression
 import Flavour
 import {-# SOURCE #-} Settings.Default
+import Settings.Flavours.Common (naturalInBaseFixArgs)
 
 -- Please update doc/flavours.md when changing this file.
 quickestFlavour :: Flavour
@@ -14,7 +15,10 @@ quickestFlavour = defaultFlavour
 
 quickestArgs :: Args
 quickestArgs = sourceArgs SourceArgs
-    { hsDefault  = pure ["-O0", "-H64m"]
+    { hsDefault  = mconcat $
+        [ pure ["-O0", "-H64m"]
+        , naturalInBaseFixArgs
+        ]
     , hsLibrary  = mempty
     , hsCompiler = stage0 ? arg "-O"
     , hsGhc      = stage0 ? arg "-O" }



More information about the ghc-commits mailing list