aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--lib/Distribution/Helper.hs119
-rw-r--r--src/CabalHelper/Compiletime/Program/CabalInstall.hs98
-rw-r--r--src/CabalHelper/Compiletime/Program/Stack.hs25
-rw-r--r--src/CabalHelper/Compiletime/Types.hs28
-rw-r--r--tests/GhcSession.hs4
5 files changed, 170 insertions, 104 deletions
diff --git a/lib/Distribution/Helper.hs b/lib/Distribution/Helper.hs
index 89ce6f9..3f56328 100644
--- a/lib/Distribution/Helper.hs
+++ b/lib/Distribution/Helper.hs
@@ -1,5 +1,5 @@
-- cabal-helper: Simple interface to Cabal's configuration state
--- Copyright (C) 2015-2018 Daniel Gröber <cabal-helper@dxld.at>
+-- Copyright (C) 2015-2019 Daniel Gröber <cabal-helper@dxld.at>
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU General Public License as published by
@@ -41,12 +41,17 @@ module Distribution.Helper (
-- ** Project queries
, compilerVersion
- , projectUnits
+ , projectPackages
- -- ** Unit queries
+ -- ** 'Package' queries
+ , Package -- abstract
+ , pPackageName
+ , pSourceDir
+ , pUnits
+
+ -- ** 'Unit' queries
, Unit -- abstract
, uComponentName
- , uPackageDir
, UnitId -- abstract
, UnitInfo(..)
, unitInfo
@@ -105,6 +110,7 @@ import Control.Monad.Trans.Maybe
import Control.Monad.IO.Class
import Control.Exception as E
import qualified Data.ByteString.Char8 as BS8
+import qualified Data.ByteString.UTF8 as BSU
import Data.IORef
import Data.List hiding (filter)
import Data.String
@@ -115,11 +121,13 @@ import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Set (Set)
import qualified Data.Set as Set
+import qualified Data.Traversable as T
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Version
import Data.Function
import System.Clock as Clock
+import System.IO
import System.Environment
import System.FilePath
import System.Directory
@@ -147,10 +155,11 @@ import CabalHelper.Runtime.HelperMain (helper_main)
import CabalHelper.Compiletime.Compat.Version
import qualified CabalHelper.Compiletime.Compat.ProgramDb as ProgDb
( defaultProgramDb, programPath, lookupProgram, ghcProgram, ghcPkgProgram )
-
+import Distribution.Package
+ ( packageName )
import Distribution.System (buildPlatform)
import Distribution.Text (display)
-import Distribution.Verbosity (silent, normal, verbose, deafening)
+import Distribution.Verbosity (Verbosity, silent, normal, verbose, deafening)
import Distribution.Simple.GHC as GHC (configure)
-- $type-conventions
@@ -256,8 +265,10 @@ getUnitModTimes :: Unit pt -> IO UnitModTimes
getUnitModTimes
Unit
{ uDistDir=DistDirLib distdirv1
- , uCabalFile=CabalFile cabal_file_path
- , uPackageDir
+ , uPackage=Package
+ { pCabalFile=CabalFile cabal_file_path
+ , pSourceDir
+ }
, uImpl
}
= do
@@ -270,7 +281,7 @@ getUnitModTimes
umtSetupConfig <- (traverse getFileModTime <=< mightExist) setup_config_path
return UnitModTimes {..}
where
- package_yaml_path = uPackageDir </> "package.yaml"
+ package_yaml_path = pSourceDir </> "package.yaml"
setup_config_path = distdirv1 </> "setup-config"
@@ -278,7 +289,8 @@ getUnitModTimes
compilerVersion :: Query pt (String, Version)
compilerVersion = Query $ \qe ->
getProjInfo qe >>= \proj_info ->
- let someUnit = NonEmpty.head $ piUnits proj_info in
+ let someUnit = NonEmpty.head $ pUnits $
+ NonEmpty.head $ piPackages proj_info in
-- ^ ASSUMPTION: Here we assume the compiler version is uniform across all
-- units so we just pick any one.
case piImpl proj_info of
@@ -286,9 +298,9 @@ compilerVersion = Query $ \qe ->
ProjInfoV2 { piV2CompilerId } -> return piV2CompilerId
ProjInfoStack {} -> uiCompilerId <$> getUnitInfo qe someUnit
--- | All local units currently active in a project\'s build plan.
-projectUnits :: Query pt (NonEmpty (Unit pt))
-projectUnits = Query $ \qe -> piUnits <$> getProjInfo qe
+-- | All local packages currently active in a project\'s build plan.
+projectPackages :: Query pt (NonEmpty (Package pt))
+projectPackages = Query $ \qe -> piPackages <$> getProjInfo qe
-- | Get the 'UnitInfo' for a given 'Unit'. To get a 'Unit' see 'projectUnits'.
unitInfo :: Unit pt -> Query pt UnitInfo
@@ -296,13 +308,15 @@ unitInfo u = Query $ \qe -> getUnitInfo qe u
-- | Get information on all units in a project.
allUnits :: (UnitInfo -> a) -> Query pt (NonEmpty a)
-allUnits f = fmap f <$> (mapM unitInfo =<< projectUnits)
+allUnits f = do
+ fmap f <$> (T.mapM unitInfo =<< join . fmap pUnits <$> projectPackages)
getProjInfo :: QueryEnv pt -> IO (ProjInfo pt)
getProjInfo qe@QueryEnv{..} = do
cache@QueryCache{qcProjInfo, qcUnitInfos} <- readIORef qeCacheRef
proj_info <- checkUpdateProjInfo qe qcProjInfo
- let active_units = NonEmpty.toList $ piUnits proj_info
+ let active_units = NonEmpty.toList $ join $
+ fmap pUnits $ piPackages proj_info
writeIORef qeCacheRef $ cache
{ qcProjInfo = Just proj_info
, qcUnitInfos = discardInactiveUnitInfos active_units qcUnitInfos
@@ -400,29 +414,29 @@ shallowReconfigureProject QueryEnv
return ()
reconfigureUnit :: QueryEnvI c pt -> Unit pt -> IO ()
-reconfigureUnit QueryEnv{qeDistDir=(DistDirCabal SCV1 _), ..} Unit{uPackageDir=_} = do
+reconfigureUnit QueryEnv{qeDistDir=(DistDirCabal SCV1 _), ..} Unit{} = do
return ()
reconfigureUnit
QueryEnv{qeProjLoc=ProjLocV2File projfile _projdir, ..}
- Unit{uPackageDir, uImpl}
+ Unit{uPackage=Package{pSourceDir=pkgdir}, uImpl}
= do
- _ <- qeCallProcess (Just uPackageDir) [] (cabalProgram qePrograms)
+ _ <- qeCallProcess (Just pkgdir) [] (cabalProgram qePrograms)
(["new-build", "--project-file="++projfile]
++ uiV2Components uImpl)
return ()
reconfigureUnit
QueryEnv{qeProjLoc=ProjLocV2Dir{}, ..}
- Unit{uPackageDir, uImpl}
+ Unit{uPackage=Package{pSourceDir=pkgdir}, uImpl}
= do
- _ <- qeCallProcess (Just uPackageDir) [] (cabalProgram qePrograms)
+ _ <- qeCallProcess (Just pkgdir) [] (cabalProgram qePrograms)
(["new-build"] ++ uiV2Components uImpl)
-- TODO: version check for --only-configure
return ()
reconfigureUnit
qe@QueryEnv{qeProjLoc=ProjLocStackYaml stack_yaml, ..}
- Unit{uPackageDir}
+ Unit{uPackage=Package{pSourceDir=pkgdir}}
= do
- _ <- Stack.callStackCmd qe (Just uPackageDir)
+ _ <- Stack.callStackCmd qe (Just pkgdir)
["--stack-yaml="++stack_yaml, "build", "--only-configure", "."]
return ()
@@ -440,20 +454,30 @@ readProjInfo qe pc pcm = withVerbosity $ do
setup_config_path <- canonicalizePath (distdir </> "setup-config")
mhdr <- readSetupConfigHeader setup_config_path
case mhdr of
- Just hdr@(UnitHeader _pkgId ("Cabal", hdrCabalVersion) _compId) ->
+ Just hdr@(UnitHeader (pkg_name_bs, _pkg_ver) ("Cabal", hdrCabalVersion) _compId) -> do
+ let
+ v3_0_0_0 = makeVersion [3,0,0,0]
+ pkg_name
+ | hdrCabalVersion >= v3_0_0_0 = BSU.toString pkg_name_bs
+ | otherwise = BS8.unpack pkg_name_bs
+ pkg = Package
+ { pPackageName = pkg_name
+ , pSourceDir = plCabalProjectDir projloc
+ , pCabalFile = CabalFile pcV1CabalFile
+ , pFlags = []
+ , pUnits = (:|[]) Unit
+ { uUnitId = UnitId pkg_name
+ , uPackage = pkg
+ , uDistDir = DistDirLib distdir
+ , uImpl = UnitImplV1
+ }
+ }
+ piImpl = ProjInfoV1 { piV1SetupHeader = hdr }
return ProjInfo
{ piCabalVersion = hdrCabalVersion
, piProjConfModTimes = pcm
- , piUnits = (:|[]) $ Unit
- { uUnitId = UnitId ""
- , uPackageDir = plV1Dir projloc
- , uCabalFile = CabalFile pcV1CabalFile
- , uDistDir = DistDirLib distdir
- , uImpl = UnitImplV1
- }
- , piImpl = ProjInfoV1
- { piV1SetupHeader = hdr
- }
+ , piPackages = pkg :| []
+ , piImpl
}
Just UnitHeader {uhSetupId=(setup_name, _)} ->
panicIO $ printf "Unknown Setup package-id in setup-config header '%s': '%s'"
@@ -465,14 +489,20 @@ readProjInfo qe pc pcm = withVerbosity $ do
let plan_path = distdirv2 </> "cache" </> "plan.json"
plan_mtime <- modificationTime <$> getFileStatus plan_path
plan@PlanJson { pjCabalLibVersion=Ver pjCabalLibVersion
+ , pjCabalVersion
, pjCompilerId=PkgId (PkgName compName) (Ver compVer)
}
<- decodePlanJson plan_path
- Just units <- NonEmpty.nonEmpty <$> CabalInstall.planUnits plan
+ when (pjCabalVersion < Ver [2,4,1,0]) $
+ panicIO $ "plan.json was produced by too-old a version of\
+ \cabal-install. The 'dist-dir' keys will be missing. \
+ \Please upgrade to at least cabal-instal-2.4.1.0"
+
+ Just pkgs <- NonEmpty.nonEmpty <$> CabalInstall.planPackages plan
return ProjInfo
{ piCabalVersion = makeDataVersion pjCabalLibVersion
, piProjConfModTimes = pcm
- , piUnits = units
+ , piPackages = pkgs
, piImpl = ProjInfoV2
{ piV2Plan = plan
, piV2PlanModTime = plan_mtime
@@ -481,7 +511,7 @@ readProjInfo qe pc pcm = withVerbosity $ do
}
(DistDirStack{}, _) -> do
Just cabal_files <- NonEmpty.nonEmpty <$> Stack.listPackageCabalFiles qe
- units <- mapM (Stack.getUnit qe) cabal_files
+ pkgs <- mapM (Stack.getPackage qe) cabal_files
proj_paths <- Stack.projPaths qe
let piImpl = ProjInfoStack { piStackProjPaths = proj_paths }
Just (cabalVer:_) <- withProgs piImpl qe $ runMaybeT $
@@ -490,7 +520,7 @@ readProjInfo qe pc pcm = withVerbosity $ do
return ProjInfo
{ piCabalVersion = cabalVer
, piProjConfModTimes = pcm
- , piUnits = units
+ , piPackages = pkgs
, ..
}
@@ -646,14 +676,21 @@ withProgs impl QueryEnv{..} f = do
same f o o' = f o == f o'
dprogs = defaultPrograms
+getCabalVerbosity :: Verbose => Verbosity
+getCabalVerbosity
+ | ?verbose 2 = normal
+ | ?verbose 3 = verbose
+ | ?verbose 4 = deafening
+ | otherwise = silent
+
newtype Helper pt
= Helper { runHelper :: Unit pt -> [String] -> IO [Maybe ChResponse] }
getHelper :: ProjInfo pt -> QueryEnvI c pt -> IO (Helper pt)
getHelper ProjInfo{piCabalVersion} qe@QueryEnv{..}
| piCabalVersion == bultinCabalVersion = return $ Helper $
- \Unit{ uCabalFile=CabalFile cabal_file
- , uDistDir=DistDirLib distdir
+ \Unit{ uDistDir=DistDirLib distdir
+ , uPackage=Package{pCabalFile=CabalFile cabal_file}
} args ->
let pt = dispHelperProjectType (projTypeOfQueryEnv qe) in
helper_main $ cabal_file : distdir : pt : args
@@ -670,8 +707,8 @@ getHelper proj_info qe@QueryEnv{..} = do
panicIO $ "compileHelper': compiling helper failed! exit code "++ show rv
Right exe ->
let pt = dispHelperProjectType (projTypeOfQueryEnv qe) in
- return $ Helper $ \Unit{uCabalFile, uDistDir} args ->
- readHelper qe exe uCabalFile uDistDir (pt : args)
+ return $ Helper $ \Unit{uDistDir, uPackage=Package{pCabalFile}} args ->
+ readHelper qe exe pCabalFile uDistDir (pt : args)
dispHelperProjectType :: SProjType pt -> String
dispHelperProjectType (SCabal SCV1) = "v1"
diff --git a/src/CabalHelper/Compiletime/Program/CabalInstall.hs b/src/CabalHelper/Compiletime/Program/CabalInstall.hs
index 8ce0135..686743b 100644
--- a/src/CabalHelper/Compiletime/Program/CabalInstall.hs
+++ b/src/CabalHelper/Compiletime/Program/CabalInstall.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DataKinds, MultiWayIf #-}
+{-# LANGUAGE DataKinds, MultiWayIf, TupleSections #-}
-- cabal-helper: Simple interface to Cabal's configuration state
-- Copyright (C) 2018 Daniel Gröber <cabal-helper@dxld.at>
@@ -24,10 +24,12 @@ License : GPL-3
module CabalHelper.Compiletime.Program.CabalInstall where
+import Control.Arrow ((&&&))
import qualified Cabal.Plan as CP
import Control.Monad
import Data.Coerce
-import Data.Either
+import Data.List.NonEmpty (NonEmpty((:|)))
+import Data.Semigroup ((<>))
import Data.Maybe
import Data.Version
import System.IO
@@ -37,7 +39,6 @@ import System.Environment
import System.FilePath
import Text.Printf
import Text.Read
-import Text.Show.Pretty
import qualified Data.Map.Strict as Map
import qualified Data.Text as Text
@@ -86,16 +87,23 @@ installingMessage = message
-- a way to let API clients override this!
hPutStr stderr $ printf "\
\cabal-helper: Installing a private copy of Cabal because we couldn't\n\
-\find the right version in your global/user package-db. This might take a\n\
-\while but will only happen once per Cabal version you're using.\n\
+\find the right version anywhere on your system. You can set the environment\n\
+\variable CABAL_HELPER_DEBUG=1 to see where we searched.\n\
\\n\
-\If anything goes horribly wrong just delete this directory and try again:\n\
-\ %s\n\
+\Note that this installation might take a little while but it will only\n\
+\happen once per Cabal library version used in your build-plans.\n\
\\n\
\If you want to avoid this automatic installation altogether install\n\
-\version %s of Cabal manually (into your user or global package-db):\n\
+\version %s of the Cabal library manually, either using cabal or your\n\
+\system package manager. With cabal you can use the following command:\n\
\ $ cabal install Cabal --constraint \"Cabal == %s\"\n\
\\n\
+\FYI the build products and cabal-helper executable cache are all in the\n\
+\following directory, you can simply delete it if you think something\n\
+\is broken :\n\
+\ %s\n\
+\Please do report any problems you encounter.\n\
+\\n\
\Installing Cabal %s ...\n" appdir sver sver sver
callCabalInstall
@@ -244,39 +252,55 @@ cabalV2WithGHCProgOpts = concat
else []
]
-planUnits :: CP.PlanJson -> IO [Unit ('Cabal 'CV2)]
-planUnits plan = do
- units <- fmap catMaybes $ mapM takeunit $ Map.elems $ CP.pjUnits plan
- case lefts units of
- [] -> return $ rights units
- us@(_:_) -> panicIO $
- msg ++ (concat $ map (unlines . map (" "++) . lines . ppShow) us)
+planPackages :: CP.PlanJson -> IO [Package ('Cabal 'CV2)]
+planPackages plan = do
+ fmap Map.elems $
+ mapM mkPackage $
+ groupByMap $ Map.elems $
+ Map.filter ((==CP.UnitTypeLocal) . CP.uType) $
+ CP.pjUnits plan
where
- msg = "\
-\plan.json doesn't contain 'dist-dir' key for the following local units:\n"
- takeunit u@CP.Unit
- { uType=CP.UnitTypeLocal
- , uDistDir=Just distdirv1
- , uPkgSrc=Just (CP.LocalUnpackedPackage pkgdir)
+ groupByMap = Map.fromListWith (<>) . map (CP.uPId &&& (:|[]))
+
+ mkPackage units@(unit :| _) =
+ case unit of
+ CP.Unit
+ { uPkgSrc=Just (CP.LocalUnpackedPackage pkgdir)
+ } -> do
+ cabal_file <- Cabal.complainIfNoCabalFile pkgdir =<< Cabal.findCabalFile pkgdir
+ let pkg = Package
+ { pPackageName =
+ let CP.PkgId (CP.PkgName pkg_name) _ = CP.uPId unit
+ in Text.unpack pkg_name
+ , pSourceDir = pkgdir
+ , pCabalFile = CabalFile cabal_file
+ , pFlags = []
+ , pUnits = fmap (mkUnit pkg) units
+ }
+ return pkg
+ _ -> panicIO "planPackages.mkPackage: Got non-unpacked package src!"
+
+ mkUnit pkg CP.Unit
+ { uDistDir=Just distdirv1
, uComps=comps
- , uPId=CP.PkgId pkg_name _
- } = do
- cabal_file <- Cabal.complainIfNoCabalFile pkgdir =<< Cabal.findCabalFile pkgdir
- let comp_names = Map.keys comps
- let uiV2Components =
- map (Text.unpack . CP.dispCompNameTarget pkg_name) $ Map.keys comps
- let uiV2ComponentNames = map cpCompNameToChComponentName comp_names
- return $ Just $ Right $ Unit
- { uUnitId = UnitId $ Text.unpack (coerce (CP.uId u))
- , uPackageDir = pkgdir
- , uCabalFile = CabalFile cabal_file
+ , uPId = CP.PkgId pkg_name _
+ , uId
+ } =
+ let comp_names = Map.keys comps in
+ Unit
+ { uUnitId = UnitId $ Text.unpack (coerce uId)
+ , uPackage = pkg
, uDistDir = DistDirLib distdirv1
- , uImpl = UnitImplV2 {..}
+ , uImpl =
+ let
+ uiV2ComponentNames = map cpCompNameToChComponentName comp_names
+ uiV2Components =
+ map (Text.unpack . CP.dispCompNameTarget pkg_name) $
+ Map.keys comps
+ in UnitImplV2 {..}
}
- takeunit u@CP.Unit {uType=CP.UnitTypeLocal} =
- return $ Just $ Left u
- takeunit _ =
- return $ Nothing
+ mkUnit _ _ =
+ error "planPackages.mkUnit: Got package without distdir!"
cpCompNameToChComponentName :: CP.CompName -> ChComponentName
cpCompNameToChComponentName cn =
diff --git a/src/CabalHelper/Compiletime/Program/Stack.hs b/src/CabalHelper/Compiletime/Program/Stack.hs
index 896c73e..264050a 100644
--- a/src/CabalHelper/Compiletime/Program/Stack.hs
+++ b/src/CabalHelper/Compiletime/Program/Stack.hs
@@ -30,6 +30,7 @@ import Control.Monad.Trans.Maybe
import Control.Monad.IO.Class
import Data.Char
import Data.List hiding (filter)
+import Data.List.NonEmpty (NonEmpty(..))
import Data.String
import Data.Maybe
import Data.Function
@@ -45,19 +46,25 @@ import CabalHelper.Compiletime.Types
import CabalHelper.Compiletime.Types.RelativePath
import CabalHelper.Shared.Common
-getUnit :: QueryEnvI c 'Stack -> CabalFile -> IO (Unit 'Stack)
-getUnit qe cabal_file@(CabalFile cabal_file_path) = do
+getPackage :: QueryEnvI c 'Stack -> CabalFile -> IO (Package 'Stack)
+getPackage qe cabal_file@(CabalFile cabal_file_path) = do
let pkgdir = takeDirectory cabal_file_path
let pkg_name = dropExtension $ takeFileName cabal_file_path
look <- paths qe pkgdir
let distdirv1_rel = look "dist-dir:"
- return $ Unit
- { uUnitId = UnitId pkg_name
- , uPackageDir = pkgdir
- , uCabalFile = cabal_file
- , uDistDir = DistDirLib $ pkgdir </> distdirv1_rel
- , uImpl = UnitImplStack
- }
+ let pkg = Package
+ { pPackageName = pkg_name
+ , pSourceDir = pkgdir
+ , pCabalFile = cabal_file
+ , pFlags = []
+ , pUnits = (:|[]) $ Unit
+ { uUnitId = UnitId pkg_name
+ , uDistDir = DistDirLib $ pkgdir </> distdirv1_rel
+ , uPackage = pkg
+ , uImpl = UnitImplStack
+ }
+ }
+ return pkg
projPaths :: QueryEnvI c 'Stack -> IO StackProjPaths
projPaths qe@QueryEnv {qeProjLoc=ProjLocStackYaml stack_yaml} = do
diff --git a/src/CabalHelper/Compiletime/Types.hs b/src/CabalHelper/Compiletime/Types.hs
index 3871576..b9572cb 100644
--- a/src/CabalHelper/Compiletime/Types.hs
+++ b/src/CabalHelper/Compiletime/Types.hs
@@ -106,18 +106,7 @@ demoteSProjType SStack = Stack
--
-- Hence it isn't actually possible to find the whole project's toplevel
-- source directory given just a 'ProjLoc'. However the packages within a
--- project have a well defined source directory.
---
--- Unfortunately we do not expose the concept of a "package" in the API to
--- abstract the differences between the project types. Instead each 'Unit'
--- (which is conceptually part of a "package") carries the corresponding
--- package source directory in 'uPackageDir'. Together with a 'Unit' query
--- such as 'projectUnits' you can thus get the source directory for each
--- unit.
---
--- If you need to present this in a per-package view rather than a per-unit
--- view you should be able to use the source directory as a key to
--- determine which units to group into a package.
+-- project have a well defined source directory, see 'Package.pSourceDir'
data ProjLoc (pt :: ProjType) where
-- | A fully specified @cabal v1-build@ project context. Here you can
-- specify both the path to the @.cabal@ file and the source directory
@@ -287,6 +276,16 @@ data QueryCache pt = QueryCache
newtype DistDirLib = DistDirLib FilePath
deriving (Eq, Ord, Read, Show)
+-- | A 'Package' is a named collection of many 'Unit's.
+data Package pt = Package
+ { pPackageName :: !String
+ , pSourceDir :: !FilePath
+ , pCabalFile :: !CabalFile
+ , pFlags :: ![(String, Bool)]
+ -- | Cabal flags to set when configuring and building this package.
+ , pUnits :: !(NonEmpty (Unit pt))
+ } deriving (Show)
+
-- | A 'Unit' is essentially a "build target". It is used to refer to a set
-- of components (exes, libs, tests etc.) which are managed by a certain
-- instance of the Cabal build-system[1]. We may get information on the
@@ -301,8 +300,7 @@ newtype DistDirLib = DistDirLib FilePath
-- was created in. However this is not enforced by the API.
data Unit pt = Unit
{ uUnitId :: !UnitId
- , uPackageDir :: !FilePath
- , uCabalFile :: !CabalFile
+ , uPackage :: !(Package pt)
, uDistDir :: !DistDirLib
, uImpl :: !(UnitImpl pt)
} deriving (Show)
@@ -414,7 +412,7 @@ newtype ProjConfModTimes = ProjConfModTimes [(FilePath, EpochTime)]
-- | Project-scope information cache.
data ProjInfo pt = ProjInfo
{ piCabalVersion :: !Version
- , piUnits :: !(NonEmpty (Unit pt))
+ , piPackages :: !(NonEmpty (Package pt))
, piImpl :: !(ProjInfoImpl pt)
, piProjConfModTimes :: !ProjConfModTimes
-- ^ Key for cache invalidation. When this is not equal to the return
diff --git a/tests/GhcSession.hs b/tests/GhcSession.hs
index 1a97b89..886ee82 100644
--- a/tests/GhcSession.hs
+++ b/tests/GhcSession.hs
@@ -468,7 +468,7 @@ newBuildProjSetup = ProjSetupDescr "cabal-v2" $ Right $ Ex $ ProjSetupImpl
-- V2File then, also remove addCabalProject below so we
-- cover both cases.
, psiConfigure = \progs dir ->
- runWithCwd dir (cabalProgram progs) [ "new-configure" ]
+ runWithCwd dir (cabalProgram progs) [ "new-build", "--only-configure" ]
, psiBuild = \progs dir ->
runWithCwd dir (cabalProgram progs) [ "new-build" ]
, psiSdist = \progs srcdir destdir -> do
@@ -492,7 +492,7 @@ stackProjSetup ghcVer =
, psiProjLoc = \_cabal_file projdir ->
ProjLocStackYaml $ projdir </> "stack.yaml"
, psiConfigure = \progs dir ->
- runWithCwd dir (stackProgram progs) $ argsBefore ++ [ "build", "--dry-run" ]
+ runWithCwd dir (stackProgram progs) $ argsBefore ++ [ "build", "--only-configure" ]
, psiBuild = \progs dir ->
runWithCwd dir (stackProgram progs) $ argsBefore ++ [ "build" ]
, psiSdist = \progs srcdir destdir -> do