Skip to content
Snippets Groups Projects
Commit d7ee12ea authored by Ben Gamari's avatar Ben Gamari Committed by Marge Bot
Browse files

hadrian: Set -this-package-name

When constructing the GHC flags for a package Hadrian must take care to
set `-this-package-name` in addition to `-this-unit-id`. This hasn't
broken until now as we have not had any uses of qualified package
imports. However, this will change with `filepath-1.5` and the
corresponding `unix` bump, breaking `hadrian/multi-ghci`.
parent 9d65235a
No related branches found
No related tags found
No related merge requests found
......@@ -10,18 +10,25 @@
-- Cabal files.
-----------------------------------------------------------------------------
module Hadrian.Haskell.Cabal (
pkgVersion, pkgUnitId, pkgSynopsis, pkgDescription, pkgSimpleIdentifier,
pkgPackageName, pkgVersion, pkgUnitId,
pkgSynopsis, pkgDescription, pkgSimpleIdentifier,
pkgDependencies, pkgGenericDescription, cabalArchString, cabalOsString
) where
import Development.Shake
import Distribution.PackageDescription (GenericPackageDescription)
import Distribution.PackageDescription (GenericPackageDescription, unPackageName, PackageDescription (package))
import qualified Distribution.Types.PackageId as Cabal
import qualified Distribution.Types.GenericPackageDescription as Cabal
import Hadrian.Haskell.Cabal.Type
import Hadrian.Oracles.Cabal
import Hadrian.Package
import {-# SOURCE #-} Hadrian.Haskell.Hash (pkgUnitId)
-- | The name of the package as written in the package's cabal file.
pkgPackageName :: Package -> Action String
pkgPackageName =
fmap (unPackageName . Cabal.pkgName . package . Cabal.packageDescription) . pkgGenericDescription
-- | Read a Cabal file and return the package version. The Cabal file is tracked.
pkgVersion :: Package -> Action String
......@@ -52,7 +59,8 @@ pkgDescription = fmap description . readPackageData
-- returns a crude overapproximation of actual dependencies. The Cabal file is
-- tracked.
pkgDependencies :: Package -> Action [PackageName]
pkgDependencies = fmap (map pkgName . packageDependencies) . readPackageData
pkgDependencies =
fmap (map Hadrian.Package.pkgName . packageDependencies) . readPackageData
-- | Read a Cabal file and return the 'GenericPackageDescription'. The Cabal
-- file is tracked.
......
......@@ -254,13 +254,17 @@ packageGhcArgs = do
-- sets `-this-unit-id ghc` when hadrian is building stage0, which will
-- overwrite this one.
pkgId <- expr $ pkgUnitId stage package
pkgName <- expr $ pkgPackageName package
mconcat [ arg "-hide-all-packages"
, arg "-no-user-package-db"
, arg "-package-env -"
, packageDatabaseArgs
-- We want to pass -this-unit-id for executables as well for multi-repl to
-- work with executable packages but this is buggy on GHC-9.0.2
, (isLibrary package || (ghc_ver >= makeVersion [9,2,1])) ? arg ("-this-unit-id " ++ pkgId)
, (isLibrary package || (ghc_ver >= makeVersion [9,2,1])) ? mconcat
[ arg ("-this-unit-id " ++ pkgId)
, arg ("-this-package-name " ++ pkgName)
]
, map ("-package-id " ++) <$> getContextData depIds ]
includeGhcArgs :: Args
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment