[Git][ghc/ghc][wip/rts-cabal-file-no-stage-specific-subst] Do not substitute `@...@` for stage-specific values in cabal files

John Ericson (@Ericson2314) gitlab at gitlab.haskell.org
Thu Oct 12 15:38:14 UTC 2023



John Ericson pushed to branch wip/rts-cabal-file-no-stage-specific-subst at Glasgow Haskell Compiler / GHC


Commits:
1f209951 by John Ericson at 2023-10-12T11:36:54-04:00
Do not substitute `@...@` for stage-specific values in cabal files

`rts` and `ghc-prim` now no longer have a `*.cabal.in` to set Cabal flag
defaults; instead manual choices are passed to configure in the usual
way.

The old way was fundamentally broken, because it meant we were baking
these Cabal files for a specific stage. Now we only do stage-agnostic
@...@ substitution in cabal files (the GHC version), and so all
stage-specific configuration is properly confined to `_build` and the
right stage dir.

Also `include-ghc-prim` is a flag that no longer exists for `ghc-prim`
(it was removed in 835d8ddbbfb11796ea8a03d1806b7cee38ba17a6) so I got
rid of it.

Co-Authored-By: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -


6 changed files:

- .gitignore
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Packages.hs
- libraries/ghc-prim/ghc-prim.cabal.in → libraries/ghc-prim/ghc-prim.cabal
- rts/.gitignore
- rts/rts.cabal.in → rts/rts.cabal


Changes:

=====================================
.gitignore
=====================================
@@ -167,7 +167,6 @@ _darcs/
 /libraries/ghc-boot-th/ghc-boot-th.cabal
 /libraries/ghc-boot-th/ghc.mk
 /libraries/ghc-heap/ghc-heap.cabal
-/libraries/ghc-prim/ghc-prim.cabal
 /libraries/ghci/GNUmakefile
 /libraries/ghci/ghci.cabal
 /libraries/ghci/ghc.mk


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -268,17 +268,6 @@ runInterpolations (Interpolations mk_substs) input = do
         subst = foldr (.) id [replace ("@"++k++"@") v | (k,v) <- substs]
     return (subst input)
 
-toCabalBool :: Bool -> String
-toCabalBool True  = "True"
-toCabalBool False = "False"
-
--- | Interpolate the given variable with the value of the given 'Flag', using
--- Cabal's boolean syntax.
-interpolateCabalFlag :: String -> Flag -> Interpolations
-interpolateCabalFlag name flg = interpolateVar name $ do
-    val <- flag flg
-    return (toCabalBool val)
-
 -- | Interpolate the given variable with the value of the given 'Setting'.
 interpolateSetting :: String -> Setting -> Interpolations
 interpolateSetting name settng = interpolateVar name $ setting settng
@@ -290,31 +279,6 @@ projectVersion = mconcat
     , interpolateSetting "ProjectVersionMunged" ProjectVersionMunged
     ]
 
-rtsCabalFlags :: Interpolations
-rtsCabalFlags = mconcat
-    [ flag "CabalHaveLibdw" UseLibdw
-    , flag "CabalHaveLibm" UseLibm
-    , flag "CabalHaveLibrt" UseLibrt
-    , flag "CabalHaveLibdl" UseLibdl
-    , flag "CabalNeedLibpthread" UseLibpthread
-    , flag "CabalHaveLibbfd" UseLibbfd
-    , flag "CabalHaveLibNuma" UseLibnuma
-    , flag "CabalHaveLibZstd" UseLibzstd
-    , flag "CabalStaticLibZstd" StaticLibzstd
-    , flag "CabalNeedLibatomic" NeedLibatomic
-    , flag "CabalUseSystemLibFFI" UseSystemFfi
-    , targetFlag "CabalLibffiAdjustors" tgtUseLibffiForAdjustors
-    , targetFlag "CabalLeadingUnderscore" tgtSymbolsHaveLeadingUnderscore
-    ]
-  where
-    flag = interpolateCabalFlag
-    targetFlag name q = interpolateVar name $ do
-      val <- queryTargetTarget q
-      return (toCabalBool val)
-
-ghcPrimCabalFlags :: Interpolations
-ghcPrimCabalFlags = interpolateCabalFlag "CabalNeedLibatomic" NeedLibatomic
-
 packageVersions :: Interpolations
 packageVersions = foldMap f [ base, ghcPrim, compiler, ghc, cabal, templateHaskell, ghcCompact, array ]
   where
@@ -347,8 +311,6 @@ templateRule outPath interps = do
 templateRules :: Rules ()
 templateRules = do
   templateRule "compiler/ghc.cabal" $ projectVersion
-  templateRule "rts/rts.cabal" $ rtsCabalFlags
-  templateRule "libraries/ghc-prim/ghc-prim.cabal" $ ghcPrimCabalFlags
   templateRule "driver/ghci/ghci-wrapper.cabal" $ projectVersion
   templateRule "ghc/ghc-bin.cabal" $ projectVersion
   templateRule "utils/iserv/iserv.cabal" $ projectVersion


=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -114,7 +114,7 @@ packageArgs = do
 
         -------------------------------- ghcPrim -------------------------------
         , package ghcPrim ? mconcat
-          [ builder (Cabal Flags) ? arg "include-ghc-prim"
+          [ builder (Cabal Flags) ? flag NeedLibatomic `cabalFlag` "need-atomic"
 
           , builder (Cc CompileC) ? (not <$> flag CcLlvmBackend) ?
             input "**/cbits/atomic.c"  ? arg "-Wno-sync-nand" ]
@@ -281,8 +281,8 @@ rtsPackageArgs = package rts ? do
     targetArch     <- queryTarget queryArch
     targetOs       <- queryTarget queryOS
     targetVendor   <- queryTarget queryVendor
-    ghcUnreg       <- yesNo <$> queryTarget tgtUnregisterised
-    ghcEnableTNC   <- yesNo <$> queryTarget tgtTablesNextToCode
+    ghcUnreg       <- queryTarget tgtUnregisterised
+    ghcEnableTNC   <- queryTarget tgtTablesNextToCode
     rtsWays        <- getRtsWays
     way            <- getWay
     path           <- getBuildPath
@@ -355,8 +355,8 @@ rtsPackageArgs = package rts ? do
             , "-DTargetArch="                ++ show targetArch
             , "-DTargetOS="                  ++ show targetOs
             , "-DTargetVendor="              ++ show targetVendor
-            , "-DGhcUnregisterised="         ++ show ghcUnreg
-            , "-DTablesNextToCode="          ++ show ghcEnableTNC
+            , "-DGhcUnregisterised="         ++ show (yesNo ghcUnreg)
+            , "-DTablesNextToCode="          ++ show (yesNo ghcEnableTNC)
             , "-DRtsWay=\"rts_" ++ show way ++ "\""
             ]
 
@@ -401,8 +401,21 @@ rtsPackageArgs = package rts ? do
           , any (wayUnit Debug) rtsWays     `cabalFlag` "debug"
           , any (wayUnit Dynamic) rtsWays   `cabalFlag` "dynamic"
           , any (wayUnit Threaded) rtsWays  `cabalFlag` "threaded"
+          , ghcEnableTNC                    `cabalFlag` "tables-next-to-code"
+          , ghcUnreg                        `cabalFlag` "unregisterised"
+          , flag UseLibm                    `cabalFlag` "libm"
+          , flag UseLibrt                   `cabalFlag` "librt"
+          , flag UseLibdl                   `cabalFlag` "libdl"
           , useSystemFfi                    `cabalFlag` "use-system-libffi"
           , useLibffiForAdjustors           `cabalFlag` "libffi-adjustors"
+          , flag UseLibpthread              `cabalFlag` "need-pthread"
+          , flag UseLibbfd                  `cabalFlag` "libbfd"
+          , flag NeedLibatomic              `cabalFlag` "need-atomic"
+          , flag UseLibdw                   `cabalFlag` "libdw"
+          , flag UseLibnuma                 `cabalFlag` "libnuma"
+          , flag UseLibzstd                 `cabalFlag` "libzstd"
+          , flag StaticLibzstd              `cabalFlag` "static-libzstd"
+          , queryTargetTarget tgtSymbolsHaveLeadingUnderscore `cabalFlag` "leading-underscore"
           , Debug `wayUnit` way             `cabalFlag` "find-ptr"
           ]
         , builder (Cabal Setup) ? mconcat


=====================================
libraries/ghc-prim/ghc-prim.cabal.in → libraries/ghc-prim/ghc-prim.cabal
=====================================
@@ -28,7 +28,7 @@ custom-setup
     setup-depends: base >= 4 && < 5, process, filepath, directory, Cabal >= 1.23 && < 3.9
 
 flag need-atomic
-  default: @CabalNeedLibatomic@
+  default: False
 
 Library
     default-language: Haskell2010


=====================================
rts/.gitignore
=====================================
@@ -2,8 +2,6 @@
 /dist/
 /dist-*/
 
-/rts.cabal
-
 /include/ghcversion.h
 
 /package.conf.inplace


=====================================
rts/rts.cabal.in → rts/rts.cabal
=====================================
@@ -29,31 +29,31 @@ source-repository head
     subdir:   rts
 
 flag libm
-  default: @CabalHaveLibm@
+  default: False
 flag librt
-  default: @CabalHaveLibrt@
+  default: False
 flag libdl
-  default: @CabalHaveLibdl@
+  default: False
 flag use-system-libffi
-  default: @CabalUseSystemLibFFI@
+  default: False
 flag libffi-adjustors
-  default: @CabalLibffiAdjustors@
+  default: False
 flag need-pthread
-  default: @CabalNeedLibpthread@
+  default: False
 flag libbfd
-  default: @CabalHaveLibbfd@
+  default: False
 flag need-atomic
-  default: @CabalNeedLibatomic@
+  default: False
 flag libdw
-  default: @CabalHaveLibdw@
+  default: False
 flag libnuma
-  default: @CabalHaveLibNuma@
+  default: False
 flag libzstd
-  default: @CabalHaveLibZstd@
+  default: False
 flag static-libzstd
-  default: @CabalStaticLibZstd@
+  default: False
 flag leading-underscore
-  default: @CabalLeadingUnderscore@
+  default: False
 flag smp
   default: True
 flag find-ptr



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1f209951f5683e72b4d83a9739c2ab4d37cc99f8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1f209951f5683e72b4d83a9739c2ab4d37cc99f8
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/20231012/1d2b02d0/attachment-0001.html>


More information about the ghc-commits mailing list