Skip to content

Commit 979e613

Browse files
authored
Merge pull request #3795 from commercialhaskell/fix-ghci-autogen-path-3791
Use per-component build directories for ghci with Cabal>=2.0 #3791
2 parents c5aed6e + 54afd66 commit 979e613

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
@@ -105,6 +105,8 @@ Bug fixes:
105105
resilient against SIGKILL and machine failure. See
106106
[hackage-security #187](https://github.com/haskell/hackage-security/issues/187)
107107
and [#3073](https://github.com/commercialhaskell/stack/issues/3073).
108+
* `stack ghci` now uses correct paths for autogen files with
109+
[#3791](https://github.com/commercialhaskell/stack/issues/3791)
108110

109111

110112
## v1.6.3.1

src/Stack/Build/ConstructPlan.hs

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

src/Stack/Build/Execute.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -790,7 +790,7 @@ getConfigCache ExecuteEnv {..} task@Task {..} installedMap enableTest enableBenc
790790
, configCacheDeps = allDeps
791791
, configCacheComponents =
792792
case taskType of
793-
TTFiles lp _ -> Set.map renderComponent $ lpComponents lp
793+
TTFiles lp _ -> Set.map (encodeUtf8 . renderComponent) $ lpComponents lp
794794
TTIndex{} -> Set.empty
795795
, configCacheHaddock =
796796
shouldHaddockPackage eeBuildOpts eeWanted (packageIdentifierName taskProvides)
@@ -1411,9 +1411,9 @@ singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} installedMap
14111411
-- https://github.com/commercialhaskell/stack/issues/2649
14121412
-- is resolved, we will want to partition the warnings
14131413
-- based on variety, and output in different lists.
1414-
let showModuleWarning (UnlistedModulesWarning mcomp modules) =
1414+
let showModuleWarning (UnlistedModulesWarning comp modules) =
14151415
"- In" <+>
1416-
maybe "the library component" (\c -> fromString c <+> "component") mcomp <>
1416+
fromString (T.unpack (renderComponent comp)) <>
14171417
":" <> line <>
14181418
indent 4 (mconcat $ intersperse line $ map (styleGood . fromString . C.display) modules)
14191419
forM_ mlocalWarnings $ \(cabalfp, warnings) -> do
@@ -1938,7 +1938,7 @@ cabalIsSatisfied = all (== ExecutableBuilt) . M.elems
19381938
-- Test-suite and benchmark build components.
19391939
finalComponentOptions :: LocalPackage -> [String]
19401940
finalComponentOptions lp =
1941-
map (T.unpack . decodeUtf8 . renderComponent) $
1941+
map (T.unpack . renderComponent) $
19421942
Set.toList $
19431943
Set.filter (\c -> isCTest c || isCBench c) (lpComponents lp)
19441944

src/Stack/Ghci.hs

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

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

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

819828
setScriptPerms :: MonadIO m => FilePath -> m ()
@@ -846,50 +855,6 @@ hasLocalComp p t =
846855
TargetAll ProjectPackage -> True
847856
_ -> False
848857

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

0 commit comments

Comments
 (0)