Skip to content

Commit 40c5aa0

Browse files
committed
Use per-component build directories for ghci with Cabal>=2.0 #3791
1 parent cd7ed8f commit 40c5aa0

File tree

7 files changed

+127
-156
lines changed

7 files changed

+127
-156
lines changed

ChangeLog.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -92,6 +92,8 @@ Bug fixes:
9292
resilient against SIGKILL and machine failure. See
9393
[hackage-security #187](https://github.com/haskell/hackage-security/issues/187)
9494
and [#3073](https://github.com/commercialhaskell/stack/issues/3073).
95+
* `stack ghci` now uses correct paths for autogen files with
96+
[#3791](https://github.com/commercialhaskell/stack/issues/3791)
9597

9698
## v1.6.3
9799

src/Stack/Build/ConstructPlan.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ import qualified Data.Map.Strict as M
2828
import qualified Data.Map.Strict as Map
2929
import qualified Data.Set as Set
3030
import qualified Data.Text as T
31-
import Data.Text.Encoding (decodeUtf8With)
31+
import Data.Text.Encoding (encodeUtf8, decodeUtf8With)
3232
import Data.Text.Encoding.Error (lenientDecode)
3333
import qualified Distribution.Text as Cabal
3434
import qualified Distribution.Version as Cabal
@@ -728,7 +728,7 @@ checkDirtiness ps installed package present wanted = do
728728
, configCacheDeps = Set.fromList $ Map.elems present
729729
, configCacheComponents =
730730
case ps of
731-
PSFiles lp _ -> Set.map renderComponent $ lpComponents lp
731+
PSFiles lp _ -> Set.map (encodeUtf8 . renderComponent) $ lpComponents lp
732732
PSIndex{} -> Set.empty
733733
, configCacheHaddock =
734734
shouldHaddockPackage buildOpts wanted (packageName package) ||

src/Stack/Build/Execute.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -798,7 +798,7 @@ getConfigCache ExecuteEnv {..} task@Task {..} installedMap enableTest enableBenc
798798
, configCacheDeps = allDeps
799799
, configCacheComponents =
800800
case taskType of
801-
TTFiles lp _ -> Set.map renderComponent $ lpComponents lp
801+
TTFiles lp _ -> Set.map (encodeUtf8 . renderComponent) $ lpComponents lp
802802
TTIndex{} -> Set.empty
803803
, configCacheHaddock =
804804
shouldHaddockPackage eeBuildOpts eeWanted (packageIdentifierName taskProvides)
@@ -1421,9 +1421,9 @@ singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} installedMap
14211421
-- https://github.com/commercialhaskell/stack/issues/2649
14221422
-- is resolved, we will want to partition the warnings
14231423
-- based on variety, and output in different lists.
1424-
let showModuleWarning (UnlistedModulesWarning mcomp modules) =
1424+
let showModuleWarning (UnlistedModulesWarning comp modules) =
14251425
"- In" <+>
1426-
maybe "the library component" (\c -> fromString c <+> "component") mcomp <>
1426+
fromString (T.unpack (renderComponent comp)) <>
14271427
":" <> line <>
14281428
indent 4 (mconcat $ intersperse line $ map (styleGood . fromString . C.display) modules)
14291429
forM_ mlocalWarnings $ \(cabalfp, warnings) -> do
@@ -1949,7 +1949,7 @@ cabalIsSatisfied = all (== ExecutableBuilt) . M.elems
19491949
-- Test-suite and benchmark build components.
19501950
finalComponentOptions :: LocalPackage -> [String]
19511951
finalComponentOptions lp =
1952-
map (T.unpack . decodeUtf8 . renderComponent) $
1952+
map (T.unpack . renderComponent) $
19531953
Set.toList $
19541954
Set.filter (\c -> isCTest c || isCBench c) (lpComponents lp)
19551955

src/Stack/Ghci.hs

Lines changed: 15 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -398,7 +398,7 @@ runGhci GhciOpts{..} targets mainIsTargets pkgs extraFiles exposePackages = do
398398
scriptPath <- writeGhciScript tmpDirectory (renderScript isIntero pkgs mainFile ghciOnlyMain extraFiles)
399399
execGhci (macrosOptions ++ ["-ghci-script=" <> toFilePath scriptPath])
400400

401-
writeMacrosFile :: (MonadIO m) => Path Abs Dir -> [GhciPkgInfo] -> m [String]
401+
writeMacrosFile :: HasRunner env => Path Abs Dir -> [GhciPkgInfo] -> RIO env [String]
402402
writeMacrosFile tmpDirectory packages = do
403403
preprocessCabalMacros packages macrosFile
404404
where
@@ -807,12 +807,21 @@ getExtraLoadDeps loadAllDeps sourceMap targets =
807807
(_, Just PSIndex{}) -> return loadAllDeps
808808
(_, _) -> return False
809809

810-
preprocessCabalMacros :: MonadIO m => [GhciPkgInfo] -> Path Abs File -> m [String]
811-
preprocessCabalMacros pkgs out = liftIO $ do
812-
let fps = nubOrd (concatMap (mapMaybe (bioCabalMacros . snd) . ghciPkgOpts) pkgs)
813-
files <- mapM (S8.readFile . toFilePath) fps
810+
preprocessCabalMacros :: HasRunner env => [GhciPkgInfo] -> Path Abs File -> RIO env [String]
811+
preprocessCabalMacros pkgs out = do
812+
fps <- fmap (nubOrd . catMaybes . concat) $
813+
forM pkgs $ \pkg -> forM (ghciPkgOpts pkg) $ \(_, bio) -> do
814+
let cabalMacros = bioCabalMacros bio
815+
exists <- liftIO $ doesFileExist cabalMacros
816+
if exists
817+
then return $ Just cabalMacros
818+
else do
819+
prettyWarnL ["Didn't find expected autogen file:", display cabalMacros]
820+
return Nothing
821+
files <- liftIO $ mapM (S8.readFile . toFilePath) fps
814822
if null files then return [] else do
815-
S8.writeFile (toFilePath out) $ S8.concat $ map (<> "\n#undef CURRENT_PACKAGE_KEY\n#undef CURRENT_COMPONENT_ID\n") files
823+
liftIO $ S8.writeFile (toFilePath out) $ S8.concat $
824+
map (<> "\n#undef CURRENT_PACKAGE_KEY\n#undef CURRENT_COMPONENT_ID\n") files
816825
return ["-optP-include", "-optP" <> toFilePath out]
817826

818827
setScriptPerms :: MonadIO m => FilePath -> m ()
@@ -844,47 +853,3 @@ hasLocalComp p t =
844853
TargetComps s -> any p (S.toList s)
845854
TargetAll ProjectPackage -> True
846855
_ -> False
847-
848-
849-
{- Copied from Stack.Ide, may be useful in the future
850-
851-
-- | Get options and target files for the given package info.
852-
getPackageOptsAndTargetFiles
853-
:: (MonadThrow m, MonadIO m, MonadReader env m, HasEnvConfig env)
854-
=> Path Abs Dir -> GhciPkgInfo -> m ([FilePath], [FilePath])
855-
getPackageOptsAndTargetFiles pwd pkg = do
856-
dist <- distDirFromDir (ghciPkgDir pkg)
857-
let autogen = autogenDir dist
858-
paths_foo <-
859-
liftM
860-
(autogen </>)
861-
(parseRelFile
862-
("Paths_" ++ packageNameString (ghciPkgName pkg) ++ ".hs"))
863-
paths_foo_exists <- doesFileExist paths_foo
864-
let ghcOptions bio =
865-
bioOneWordOpts bio ++
866-
bioOpts bio ++
867-
bioPackageFlags bio ++
868-
maybe [] (\cabalMacros -> ["-optP-include", "-optP" <> toFilePath cabalMacros]) (bioCabalMacros bio)
869-
return
870-
( ("--dist-dir=" <> toFilePathNoTrailingSep dist) :
871-
-- FIXME: use compilerOptionsCabalFlag
872-
map ("--ghc-option=" ++) (concatMap (ghcOptions . snd) (ghciPkgOpts pkg))
873-
, mapMaybe
874-
(fmap toFilePath . stripProperPrefix pwd)
875-
(S.toList (ghciPkgCFiles pkg) <> S.toList (ghciPkgModFiles pkg) <>
876-
[paths_foo | paths_foo_exists]))
877-
878-
-- | List load targets for a package target.
879-
targetsCmd :: Text -> GlobalOpts -> IO ()
880-
targetsCmd target go@GlobalOpts{..} =
881-
withBuildConfig go $
882-
do let boptsCli = defaultBuildOptsCLI { boptsCLITargets = [target] }
883-
(_realTargets,_,pkgs) <- ghciSetup (ideGhciOpts boptsCli)
884-
pwd <- getCurrentDir
885-
targets <-
886-
fmap
887-
(concat . snd . unzip)
888-
(mapM (getPackageOptsAndTargetFiles pwd) pkgs)
889-
forM_ targets (liftIO . putStrLn)
890-
-}

0 commit comments

Comments
 (0)