Skip to content

Commit

Permalink
Merge pull request #6505 from commercialhaskell/re6492-2
Browse files Browse the repository at this point in the history
Re #6492 Further prefer 'project packages' to 'local packages'
  • Loading branch information
mpilgrem committed Mar 2, 2024
2 parents 2adc11c + d007ba3 commit 2892da7
Show file tree
Hide file tree
Showing 22 changed files with 59 additions and 56 deletions.
10 changes: 5 additions & 5 deletions src/Stack/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -272,11 +272,11 @@ warnIfExecutablesWithSameNameCouldBeOverwritten locals plan = do
| not (null otherLocals)
]
where
-- Cases of several local packages having executables with the same name.
-- Cases of several project packages having executables with the same name.
-- The Map entries have the following form:
--
-- executable name: ( package names for executables that are being built
-- , package names for other local packages that have an
-- , package names for other project packages that have an
-- executable with the same name
-- )
warnings :: Map Text ([PackageName],[PackageName])
Expand All @@ -285,16 +285,16 @@ warnIfExecutablesWithSameNameCouldBeOverwritten locals plan = do
(\(pkgsToBuild, localPkgs) ->
case (pkgsToBuild, NE.toList localPkgs \\ NE.toList pkgsToBuild) of
(_ :| [], []) ->
-- We want to build the executable of single local package
-- and there are no other local packages with an executable of
-- We want to build the executable of single project package
-- and there are no other project packages with an executable of
-- the same name. Nothing to warn about, ignore.
Nothing
(_, otherLocals) ->
-- We could be here for two reasons (or their combination):
-- 1) We are building two or more executables with the same
-- name that will end up overwriting each other.
-- 2) In addition to the executable(s) that we want to build
-- there are other local packages with an executable of the
-- there are other project packages with an executable of the
-- same name that might get overwritten.
-- Both cases warrant a warning.
Just (NE.toList pkgsToBuild, otherLocals))
Expand Down
4 changes: 2 additions & 2 deletions src/Stack/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,7 @@ import System.Environment ( lookupEnv )
-- and the interdependencies among the build 'Task's. In particular:
--
-- 1) It determines which packages need to be built, based on the transitive
-- deps of the current targets. For local packages, this is indicated by the
-- deps of the current targets. For project packages, this is indicated by the
-- 'lpWanted' boolean. For extra packages to build, this comes from the
-- @extraToBuild0@ argument of type @Set PackageName@. These are usually
-- packages that have been specified on the command line.
Expand Down Expand Up @@ -312,7 +312,7 @@ constructPlan
pure $ pPackages <> deps

-- | Determine which packages to unregister based on the given tasks and
-- already registered local packages.
-- already registered project packages and local extra-deps.
mkUnregisterLocal ::
Map PackageName Task
-- ^ Tasks
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build/Execute.hs
Original file line number Diff line number Diff line change
Expand Up @@ -210,7 +210,7 @@ executePlan :: HasEnvConfig env
-> [LocalPackage]
-> [DumpPackage] -- ^ global packages
-> [DumpPackage] -- ^ snapshot packages
-> [DumpPackage] -- ^ local packages
-> [DumpPackage] -- ^ project packages and local extra-deps
-> InstalledMap
-> Map PackageName Target
-> Plan
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build/ExecuteEnv.hs
Original file line number Diff line number Diff line change
Expand Up @@ -251,7 +251,7 @@ withExecuteEnv ::
-> [LocalPackage]
-> [DumpPackage] -- ^ global packages
-> [DumpPackage] -- ^ snapshot packages
-> [DumpPackage] -- ^ local packages
-> [DumpPackage] -- ^ project packages and local extra-deps
-> Maybe Int -- ^ largest package name, for nicer interleaved output
-> (ExecuteEnv -> RIO env a)
-> RIO env a
Expand Down
8 changes: 4 additions & 4 deletions src/Stack/Build/Haddock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,7 @@ shouldHaddockPackage bopts wanted name =
shouldHaddockDeps :: BuildOpts -> Bool
shouldHaddockDeps bopts = fromMaybe bopts.buildHaddocks bopts.haddockDeps

-- | Generate Haddock index and contents for local packages.
-- | Generate Haddock index and contents for project packages.
generateLocalHaddockIndex ::
(HasCompiler env, HasProcessContext env, HasTerm env)
=> BaseConfigOpts
Expand All @@ -141,7 +141,7 @@ generateLocalHaddockIndex bco localDumpPkgs locals = do
"."
(localDocDir bco)

-- | Generate Haddock index and contents for local packages and their
-- | Generate Haddock index and contents for project packages and their
-- dependencies.
generateDepsHaddockIndex ::
(HasCompiler env, HasProcessContext env, HasTerm env)
Expand Down Expand Up @@ -319,11 +319,11 @@ lookupDumpPackage ghcPkgId dumpPkgs =
haddockIndexFile :: Path Abs Dir -> Path Abs File
haddockIndexFile destDir = destDir </> relFileIndexHtml

-- | Path of local packages documentation directory.
-- | Path of project packages documentation directory.
localDocDir :: BaseConfigOpts -> Path Abs Dir
localDocDir bco = bco.localInstallRoot </> docDirSuffix

-- | Path of documentation directory for the dependencies of local packages
-- | Path of documentation directory for the dependencies of project packages
localDepsDocDir :: BaseConfigOpts -> Path Abs Dir
localDepsDocDir bco = localDocDir bco </> relDirAll

Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -209,7 +209,7 @@ depPackageHashableContent dp =
<> getUtf8Builder (mconcat ghcOptions)
<> getUtf8Builder (mconcat cabalConfigOpts)

-- | All flags for a local package.
-- | All flags for a project package.
getLocalFlags ::
BuildOptsCLI
-> PackageName
Expand Down
6 changes: 3 additions & 3 deletions src/Stack/Build/Target.hs
Original file line number Diff line number Diff line change
Expand Up @@ -171,8 +171,8 @@ parseRawTargetDirs root locals ri =
[] -> pure $ Left $
fillSep
[ style Dir (fromString $ T.unpack t)
, flow "is not a local package directory and it is not a \
\parent directory of any local package directory."
, flow "is not a local directory for a package and it is not a \
\parent directory of any such directory."
]
names -> pure $ Right $ map ((ri, ) . RTPackage) names
where
Expand Down Expand Up @@ -316,7 +316,7 @@ resolveRawTarget sma allLocs (rawInput, rt) =
case Map.lookup name locals of
Nothing -> pure $ Left $
fillSep
[ flow "Unknown local package:"
[ flow "Unknown project package:"
, style Target (fromPackageName name) <> "."
]
Just pp -> do
Expand Down
4 changes: 2 additions & 2 deletions src/Stack/Clean.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,8 +49,8 @@ instance Exception CleanException where
data CleanOpts
= CleanShallow [PackageName]
-- ^ Delete the "dist directories" as defined in
-- 'Stack.Constants.Config.distRelativeDir' for the given local packages. If
-- no packages are given, all project packages should be cleaned.
-- 'Stack.Constants.Config.distRelativeDir' for the given project packages.
-- If no project packages are given, all project packages should be cleaned.
| CleanFull
-- ^ Delete all work directories in the project.

Expand Down
7 changes: 4 additions & 3 deletions src/Stack/Dot.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,11 +27,11 @@ dotCmd dotOpts = do
printGraph dotOpts localNames prunedGraph

-- | Print a graphviz graph of the edges in the Map and highlight the given
-- local packages
-- project packages
printGraph ::
(Applicative m, MonadIO m)
=> DotOpts
-> Set PackageName -- ^ all locals
-> Set PackageName -- ^ All project packages.
-> Map PackageName (Set PackageName, DotPayload)
-> m ()
printGraph dotOpts locals graph = do
Expand All @@ -44,7 +44,8 @@ printGraph dotOpts locals graph = do
filteredLocals =
Set.filter (\local' -> local' `Set.notMember` dotOpts.prune) locals

-- | Print the local nodes with a different style depending on options
-- | Print the project packages nodes with a different style, depending on
-- options
printLocalNodes ::
(F.Foldable t, MonadIO m)
=> DotOpts
Expand Down
24 changes: 12 additions & 12 deletions src/Stack/Ghci.hs
Original file line number Diff line number Diff line change
Expand Up @@ -219,9 +219,8 @@ ghciCmd ghciOpts =
}
local (set buildOptsL boptsLocal) (ghci ghciOpts)

-- | Launch a GHCi session for the given local package targets with the
-- given options and configure it with the load paths and extensions
-- of those targets.
-- | Launch a GHCi session for the given project package targets with the given
-- options and configure it with the load paths and extensions of those targets.
ghci :: HasEnvConfig env => GhciOpts -> RIO env ()
ghci opts = do
let buildOptsCLI = defaultBuildOptsCLI
Expand Down Expand Up @@ -280,7 +279,7 @@ ghci opts = do
case targets of
TargetAll _ -> [T.pack (packageNameString pn)]
TargetComps comps -> [renderPkgComponent (pn, c) | c <- toList comps]
-- Build required dependencies and setup local packages.
-- Build required dependencies and setup project packages.
buildDepsAndInitialSteps opts $
concatMap (\(pn, (_, t)) -> pkgTargets pn t) localTargets
targetWarnings localTargets nonLocalTargets mfileTargets
Expand Down Expand Up @@ -472,11 +471,11 @@ getAllNonLocalTargets targets = do
buildDepsAndInitialSteps :: HasEnvConfig env => GhciOpts -> [Text] -> RIO env ()
buildDepsAndInitialSteps ghciOpts localTargets = do
let targets = localTargets ++ map T.pack ghciOpts.additionalPackages
-- If necessary, do the build, for local packagee targets, only do
-- If necessary, do the build, for project packagee targets, only do
-- 'initialBuildSteps'.
whenJust (nonEmpty targets) $ \nonEmptyTargets ->
unless ghciOpts.noBuild $ do
-- only new local targets could appear here
-- only new project package targets could appear here
eres <- buildLocalTargets nonEmptyTargets
case eres of
Right () -> pure ()
Expand Down Expand Up @@ -1133,19 +1132,20 @@ targetWarnings localTargets nonLocalTargets mfileTargets = do
, parens $ fillSep $ punctuate "," $ map
(style Good . fromPackageName)
nonLocalTargets
, flow "are not local packages, and so cannot be directly loaded. In \
, flow "are not project packages, and so cannot be directly loaded. In \
\future versions of Stack, this might be supported - see"
, style Url "https://github.com/commercialhaskell/stack/issues/1441"
, "."
, style Url "https://github.com/commercialhaskell/stack/issues/1441" <> "."
, flow "It can still be useful to specify these, as they will be passed \
\to ghci via -package flags."
\to ghci via"
, style Shell "-package"
, "flags."
]
when (null localTargets && isNothing mfileTargets) $ do
smWanted <- view $ buildConfigL . to (.smWanted)
stackYaml <- view stackYamlL
prettyNote $ vsep
[ flow "No local targets specified, so a plain ghci will be started with \
\no package hiding or package options."
[ flow "No project package targets specified, so a plain ghci will be \
\started with no package hiding or package options."
, ""
, flow $ T.unpack $ utf8BuilderToText $
"You are using snapshot: " <>
Expand Down
4 changes: 2 additions & 2 deletions src/Stack/Init.hs
Original file line number Diff line number Diff line change
Expand Up @@ -671,8 +671,8 @@ cabalPackagesCheck cabaldirs = do
when (null cabaldirs) $
prettyWarn $
fillSep
[ flow "Stack did not find any local package directories. You may \
\want to create a package with"
[ flow "Stack did not find any local directories containing a \
\package description. You may want to create a package with"
, style Shell (flow "stack new")
, flow "instead."
]
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Ls.hs
Original file line number Diff line number Diff line change
Expand Up @@ -131,7 +131,7 @@ data ListDepsTextFilter
= FilterPackage PackageName
-- ^ Item is a package name.
| FilterLocals
-- ^ Item represents all local packages.
-- ^ Item represents all project packages.

-- | Type representing command line options for the @stack ls stack-colors@ and
-- @stack ls stack-colours@ commands.
Expand Down
5 changes: 3 additions & 2 deletions src/Stack/Options/BuildMonoidParser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -172,8 +172,9 @@ buildOptsMonoidParser hide0 = BuildOptsMonoid
hide
forceDirty = firstBoolFlagsFalse
"force-dirty"
"forcing the treatment of all local packages as having dirty files. \
\Useful for cases where Stack can't detect a file change."
"forcing the treatment of all project packages and local extra-deps as \
\having dirty files. Useful for cases where Stack can't detect a file \
\change."
hide
tests = firstBoolFlagsFalse
"test"
Expand Down
5 changes: 3 additions & 2 deletions src/Stack/SDist.hs
Original file line number Diff line number Diff line change
Expand Up @@ -186,7 +186,8 @@ sdistCmd sdistOpts =
createDirectoryIfMissing True $ FP.takeDirectory targetTarPath
copyFile (toFilePath tarPath) targetTarPath

-- | Given the path to a local package, creates its source distribution tarball.
-- | Given the path to a package directory, creates a source distribution
-- tarball for the package.
--
-- While this yields a 'FilePath', the name of the tarball, this tarball is not
-- written to the disk and instead yielded as a lazy bytestring.
Expand All @@ -195,7 +196,7 @@ getSDistTarball ::
=> Maybe PvpBounds
-- ^ Override Config value
-> Path Abs Dir
-- ^ Path to local package
-- ^ Path to package directory
-> RIO
env
( FilePath
Expand Down
6 changes: 3 additions & 3 deletions src/Stack/Types/ApplyGhcOptions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,9 +10,9 @@ import Stack.Prelude

-- | Which packages do ghc-options on the command line apply to?
data ApplyGhcOptions
= AGOTargets -- ^ all local targets
| AGOLocals -- ^ all local packages, even non-targets
| AGOEverything -- ^ every package
= AGOTargets -- ^ All project packages that are targets.
| AGOLocals -- ^ All project packages, even non-targets.
| AGOEverything -- ^ All packages, project packages and dependencies.
deriving (Bounded, Enum, Eq, Ord, Read, Show)

instance FromJSON ApplyGhcOptions where
Expand Down
6 changes: 3 additions & 3 deletions src/Stack/Types/ApplyProgOptions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,9 @@ import Stack.Prelude
-- | Which packages do all and any --PROG-option options on the command line
-- apply to?
data ApplyProgOptions
= APOTargets -- ^ All local packages that are targets.
| APOLocals -- ^ All local packages (targets or otherwise).
| APOEverything -- ^ All packages (local or otherwise).
= APOTargets -- ^ All project packages that are targets.
| APOLocals -- ^ All project packages (targets or otherwise).
| APOEverything -- ^ All packages (project packages or dependencies).
deriving (Bounded, Enum, Eq, Ord, Read, Show)

instance FromJSON ApplyProgOptions where
Expand Down
4 changes: 2 additions & 2 deletions src/Stack/Types/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -236,8 +236,8 @@ instance HasCompiler Ctx where
instance HasEnvConfig Ctx where
envConfigL = lens (.ctxEnvConfig) (\x y -> x { ctxEnvConfig = y })

-- | State to be maintained during the calculation of local packages to
-- unregister.
-- | State to be maintained during the calculation of project packages and local
-- extra-deps to unregister.
data UnregisterState = UnregisterState
{ toUnregister :: !(Map GhcPkgId (PackageIdentifier, Text))
, toKeep :: ![DumpPackage]
Expand Down
5 changes: 2 additions & 3 deletions src/Stack/Types/Build/Exception.hs
Original file line number Diff line number Diff line change
Expand Up @@ -456,9 +456,8 @@ pprintTargetParseErrors errs =
, style Shell "my-package-0.1.2.3" <> "),"
, flow "a package component (e.g."
, style Shell "my-package:test:my-test-suite" <> "),"
, flow "or, failing that, a relative path to a directory that is a \
\local package directory or a parent directory of one or more \
\local package directories."
, flow "or, failing that, a relative path to a local directory for a \
\package or a parent directory of one or more such directories."
]

pprintExceptions ::
Expand Down
3 changes: 2 additions & 1 deletion src/Stack/Types/BuildOpts.hs
Original file line number Diff line number Diff line change
Expand Up @@ -52,7 +52,8 @@ data BuildOpts = BuildOpts
, keepTmpFiles :: !Bool
-- ^ Keep intermediate files and build directories
, forceDirty :: !Bool
-- ^ Force treating all local packages as having dirty files
-- ^ Force treating all project packages and local extra-deps as having
-- dirty files.
, tests :: !Bool
-- ^ Turn on tests for local targets
, testOpts :: !TestOpts
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Types/EnvConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -231,7 +231,7 @@ packageDatabaseDeps = do
root <- installationRootDeps
pure $ root </> relDirPkgdb

-- | Package database for installing local packages into
-- | Package database for installing project packages and local extra-deps into.
packageDatabaseLocal :: HasEnvConfig env => RIO env (Path Abs Dir)
packageDatabaseLocal = do
root <- installationRootLocal
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Types/EnvSettings.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ import Stack.Prelude
-- | Controls which version of the environment is used
data EnvSettings = EnvSettings
{ includeLocals :: !Bool
-- ^ include local project bin directory, GHC_PACKAGE_PATH, etc
-- ^ include project's local bin directory, GHC_PACKAGE_PATH, etc
, includeGhcPackagePath :: !Bool
-- ^ include the GHC_PACKAGE_PATH variable
, stackExe :: !Bool
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@ import Control.Monad (unless)
import Data.List (isInfixOf)
import StackTest

-- This tests building two local packages, one of which depends on the other
-- This tests building two project packages, one of which depends on the other
-- (subproject). The dependency has a library and a visible sub-library named
-- sub, each of which exposes a module that exports a function.

Expand Down

0 comments on commit 2892da7

Please sign in to comment.