Skip to content

Commit

Permalink
Include the compiler ABI tag in nix-style package hashes
Browse files Browse the repository at this point in the history
  • Loading branch information
sol committed Oct 12, 2023
1 parent 2794dd8 commit 4c6aa86
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 2 deletions.
12 changes: 10 additions & 2 deletions Cabal/src/Distribution/Simple/GHC.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}

Expand Down Expand Up @@ -83,6 +84,7 @@ import Prelude ()

import Control.Monad (forM_, msum)
import Data.Char (isLower)
import Data.List (stripPrefix)
import qualified Data.Map as Map
import Distribution.CabalSpecVersion
import Distribution.InstalledPackageInfo (InstalledPackageInfo)
Expand Down Expand Up @@ -246,10 +248,16 @@ configure verbosity hcPath hcPkgPath conf0 = do

filterExt ext = filter ((/= EnableExtension ext) . fst)

compilerId :: CompilerId
compilerId = CompilerId GHC ghcVersion

compilerAbiTag :: AbiTag
compilerAbiTag = maybe NoAbiTag AbiTag (Map.lookup "Project Unit Id" ghcInfoMap >>= stripPrefix (prettyShow compilerId <> "-"))

let comp =
Compiler
{ compilerId = CompilerId GHC ghcVersion
, compilerAbiTag = NoAbiTag
{ compilerId
, compilerAbiTag
, compilerCompat = []
, compilerLanguages = languages
, compilerExtensions = extensions
Expand Down
8 changes: 8 additions & 0 deletions cabal-install/src/Distribution/Client/PackageHash.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ import Distribution.Package
)
import Distribution.Simple.Compiler
( CompilerId
, AbiTag(..)
, DebugInfoLevel (..)
, OptimisationLevel (..)
, PackageDB
Expand Down Expand Up @@ -191,6 +192,7 @@ type PackageSourceHash = HashValue
-- package hash.
data PackageHashConfigInputs = PackageHashConfigInputs
{ pkgHashCompilerId :: CompilerId
, pkgHashCompilerAbiTag :: AbiTag
, pkgHashPlatform :: Platform
, pkgHashFlagAssignment :: FlagAssignment -- complete not partial
, pkgHashConfigureScriptArgs :: [String] -- just ./configure for build-type Configure
Expand Down Expand Up @@ -301,6 +303,7 @@ renderPackageHashInputs
pkgHashDirectDeps
, -- and then all the config
entry "compilerid" prettyShow pkgHashCompilerId
, entry "compiler-abi-tag" renderAbiTag pkgHashCompilerAbiTag
, entry "platform" prettyShow pkgHashPlatform
, opt "flags" mempty showFlagAssignment pkgHashFlagAssignment
, opt "configure-script" [] unwords pkgHashConfigureScriptArgs
Expand Down Expand Up @@ -352,3 +355,8 @@ renderPackageHashInputs
opt key def format value
| value == def = Nothing
| otherwise = entry key format value

renderAbiTag :: AbiTag -> String
renderAbiTag abiTag = case abiTag of
NoAbiTag -> "unknown"
AbiTag tag -> tag
1 change: 1 addition & 0 deletions cabal-install/src/Distribution/Client/ProjectPlanning.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4569,6 +4569,7 @@ packageHashConfigInputs
packageHashConfigInputs shared@ElaboratedSharedConfig{..} pkg =
PackageHashConfigInputs
{ pkgHashCompilerId = compilerId pkgConfigCompiler
, pkgHashCompilerAbiTag = compilerAbiTag pkgConfigCompiler
, pkgHashPlatform = pkgConfigPlatform
, pkgHashFlagAssignment = elabFlagAssignment
, pkgHashConfigureScriptArgs = elabConfigureScriptArgs
Expand Down

0 comments on commit 4c6aa86

Please sign in to comment.