Skip to content

Commit

Permalink
Use 'sub-library' terminology consistently
Browse files Browse the repository at this point in the history
  • Loading branch information
mpilgrem committed Oct 25, 2023
1 parent f0b7fa0 commit 1908cf6
Show file tree
Hide file tree
Showing 17 changed files with 99 additions and 99 deletions.
4 changes: 2 additions & 2 deletions src/Stack/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -372,8 +372,8 @@ checkComponentsBuildable lps =
, c <- Set.toList (lpUnbuildable lp)
]

-- | Find if any sublibrary dependency (other than internal libraries) exists in
-- each project package.
-- | Find if any sub-library dependency (other than internal libraries) exists
-- in each project package.
checkSubLibraryDependencies :: HasTerm env => [ProjectPackage] -> RIO env ()
checkSubLibraryDependencies projectPackages =
forM_ projectPackages $ \projectPackage -> do
Expand Down
10 changes: 5 additions & 5 deletions src/Stack/Build/Cache.hs
Original file line number Diff line number Diff line change
Expand Up @@ -134,7 +134,7 @@ buildCacheFile dir component = do
let nonLibComponent prefix name = prefix <> "-" <> T.unpack name
cacheFileName <- parseRelFile $ case component of
CLib -> "lib"
CInternalLib name -> nonLibComponent "internal-lib" name
CSubLib name -> nonLibComponent "sub-lib" name
CExe name -> nonLibComponent "exe" name
CTest name -> nonLibComponent "test" name
CBench name -> nonLibComponent "bench" name
Expand Down Expand Up @@ -375,23 +375,23 @@ writePrecompiledCache ::
-> ConfigureOpts
-> Bool -- ^ build haddocks
-> Installed -- ^ library
-> [GhcPkgId] -- ^ sublibraries, in the GhcPkgId format
-> [GhcPkgId] -- ^ sub-libraries, in the GhcPkgId format
-> Set Text -- ^ executables
-> RIO env ()
writePrecompiledCache baseConfigOpts loc copts buildHaddocks mghcPkgId sublibs exes = do
writePrecompiledCache baseConfigOpts loc copts buildHaddocks mghcPkgId subLibs exes = do
key <- getPrecompiledCacheKey loc copts buildHaddocks
ec <- view envConfigL
let stackRootRelative = makeRelative (view stackRootL ec)
mlibpath <- case mghcPkgId of
Executable _ -> pure Nothing
Library _ ipid _ -> Just <$> pathFromPkgId stackRootRelative ipid
sublibpaths <- mapM (pathFromPkgId stackRootRelative) sublibs
subLibPaths <- mapM (pathFromPkgId stackRootRelative) subLibs
exes' <- forM (Set.toList exes) $ \exe -> do
name <- parseRelFile $ T.unpack exe
stackRootRelative $ bcoSnapInstallRoot baseConfigOpts </> bindirSuffix </> name
let precompiled = PrecompiledCache
{ pcLibrary = mlibpath
, pcSubLibs = sublibpaths
, pcSubLibs = subLibPaths
, pcExes = exes'
}
savePrecompiledCache key precompiled
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 @@ -1161,10 +1161,10 @@ addPackageDeps package = do
TTLocalMutable lp -> packageHasLibrary $ lpPackage lp
TTRemotePackage _ p _ -> packageHasLibrary p

-- make sure we consider internal libraries as libraries too
-- make sure we consider sub-libraries as libraries too
packageHasLibrary :: Package -> Bool
packageHasLibrary p =
not (Set.null (packageInternalLibraries p)) ||
not (Set.null (packageSubLibraries p)) ||
case packageLibraries p of
HasLibraries _ -> True
NoLibraries -> False
Expand Down
56 changes: 28 additions & 28 deletions src/Stack/Build/Execute.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1727,7 +1727,7 @@ singleBuild
where
result = T.intercalate " + " $ concat
[ ["lib" | taskAllInOne && hasLib]
, ["internal-lib" | taskAllInOne && hasSubLib]
, ["sub-lib" | taskAllInOne && hasSubLib]
, ["exe" | taskAllInOne && hasExe]
, ["test" | enableTests]
, ["bench" | enableBenchmarks]
Expand All @@ -1739,10 +1739,10 @@ singleBuild
case packageLibraries package of
NoLibraries -> False
HasLibraries _ -> True
hasSubLibrary = not . Set.null $ packageInternalLibraries package
hasSubLibraries = not . Set.null $ packageSubLibraries package
hasExecutables =
not . Set.null $ exesToBuild executableBuildStatuses lp
in (hasLibrary, hasSubLibrary, hasExecutables)
in (hasLibrary, hasSubLibraries, hasExecutables)
-- This isn't true, but we don't want to have this info for upstream deps.
_ -> (False, False, False)

Expand Down Expand Up @@ -1776,29 +1776,29 @@ singleBuild
pure $ if b then Just pc else Nothing
_ -> pure Nothing

copyPreCompiled (PrecompiledCache mlib sublibs exes) = do
copyPreCompiled (PrecompiledCache mlib subLibs exes) = do
announceTask ee task "using precompiled package"

-- We need to copy .conf files for the main library and all sublibraries
-- We need to copy .conf files for the main library and all sub-libraries
-- which exist in the cache, from their old snapshot to the new one.
-- However, we must unregister any such library in the new snapshot, in case
-- it was built with different flags.
let
subLibNames = Set.toList $ case taskType of
TTLocalMutable lp -> packageInternalLibraries $ lpPackage lp
TTRemotePackage _ p _ -> packageInternalLibraries p
TTLocalMutable lp -> packageSubLibraries $ lpPackage lp
TTRemotePackage _ p _ -> packageSubLibraries p
toMungedPackageId :: Text -> MungedPackageId
toMungedPackageId sublib =
let sublibName = LSubLibName $ mkUnqualComponentName $ T.unpack sublib
in MungedPackageId (MungedPackageName pname sublibName) pversion
toMungedPackageId subLib =
let subLibName = LSubLibName $ mkUnqualComponentName $ T.unpack subLib
in MungedPackageId (MungedPackageName pname subLibName) pversion
toPackageId :: MungedPackageId -> PackageIdentifier
toPackageId (MungedPackageId n v) =
PackageIdentifier (encodeCompatPackageName n) v
allToUnregister :: [Either PackageIdentifier GhcPkgId]
allToUnregister = mcons
(Left pkgId <$ mlib)
(map (Left . toPackageId . toMungedPackageId) subLibNames)
allToRegister = mcons mlib sublibs
allToRegister = mcons mlib subLibs

unless (null allToRegister) $
withMVar eeInstallLock $ \() -> do
Expand Down Expand Up @@ -2030,11 +2030,11 @@ singleBuild
NoLibraries -> False
HasLibraries _ -> True
packageHasComponentSet f = not $ Set.null $ f package
hasInternalLibrary = packageHasComponentSet packageInternalLibraries
hasSubLibraries = packageHasComponentSet packageSubLibraries
hasExecutables = packageHasComponentSet packageExes
shouldCopy =
not isFinalBuild
&& (hasLibrary || hasInternalLibrary || hasExecutables)
&& (hasLibrary || hasSubLibraries || hasExecutables)
when shouldCopy $ withMVar eeInstallLock $ \() -> do
announce "copy/register"
eres <- try $ cabal KeepTHLoading ["copy"]
Expand All @@ -2044,7 +2044,7 @@ singleBuild
(packageBuildType package == C.Simple)
(displayException err)
_ -> pure ()
when (hasLibrary || hasInternalLibrary) $ cabal KeepTHLoading ["register"]
when (hasLibrary || hasSubLibraries) $ cabal KeepTHLoading ["register"]

-- copy ddump-* files
case T.unpack <$> boptsDdumpDir eeBuildOpts of
Expand Down Expand Up @@ -2078,31 +2078,31 @@ singleBuild
( bcoLocalDB eeBaseConfigOpts
, eeLocalDumpPkgs )
let ident = PackageIdentifier (packageName package) (packageVersion package)
-- only pure the sublibs to cache them if we also cache the main lib (that
-- is, if it exists)
(mpkgid, sublibsPkgIds) <- case packageLibraries package of
-- only pure the sub-libraries to cache them if we also cache the main
-- library (that is, if it exists)
(mpkgid, subLibsPkgIds) <- case packageLibraries package of
HasLibraries _ -> do
sublibsPkgIds <- fmap catMaybes $
forM (Set.toList $ packageInternalLibraries package) $ \sublib -> do
let sublibName = MungedPackageName
subLibsPkgIds <- fmap catMaybes $
forM (Set.toList $ packageSubLibraries package) $ \subLib -> do
let subLibName = MungedPackageName
(packageName package)
(LSubLibName $ mkUnqualComponentName $ T.unpack sublib)
(LSubLibName $ mkUnqualComponentName $ T.unpack subLib)
loadInstalledPkg
[installedPkgDb]
installedDumpPkgsTVar
(encodeCompatPackageName sublibName)
(encodeCompatPackageName subLibName)

mpkgid <- loadInstalledPkg
[installedPkgDb]
installedDumpPkgsTVar
(packageName package)
case mpkgid of
Nothing -> throwM $ Couldn'tFindPkgId $ packageName package
Just pkgid -> pure (Library ident pkgid Nothing, sublibsPkgIds)
Just pkgid -> pure (Library ident pkgid Nothing, subLibsPkgIds)
NoLibraries -> do
markExeInstalled (taskLocation task) pkgId -- TODO unify somehow
-- with writeFlagCache?
pure (Executable ident, []) -- don't pure sublibs in this case
-- with writeFlagCache?
pure (Executable ident, []) -- don't pure sub-libraries in this case

case taskType of
TTRemotePackage Immutable _ loc ->
Expand All @@ -2112,7 +2112,7 @@ singleBuild
(configCacheOpts cache)
(configCacheHaddock cache)
mpkgid
sublibsPkgIds
subLibsPkgIds
(packageExes package)
_ -> pure ()

Expand Down Expand Up @@ -2675,7 +2675,7 @@ extraBuildOptions wc bopts = do
else
pure [optsFlag, baseOpts]

-- Library, internal and foreign libraries and executable build components.
-- Library, sub-library, foreign library and executable build components.
primaryComponentOptions ::
Map Text ExecutableBuildStatus
-> LocalPackage
Expand All @@ -2693,7 +2693,7 @@ primaryComponentOptions executableBuildStatuses lp =
)
++ map
(T.unpack . T.append "lib:")
(Set.toList $ packageInternalLibraries package)
(Set.toList $ packageSubLibraries package)
++ map
(T.unpack . T.append "exe:")
(Set.toList $ exesToBuild executableBuildStatuses lp)
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build/Installed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -181,7 +181,7 @@ isAllowed :: InstallMap
isAllowed installMap mloc dp = case Map.lookup name installMap of
Nothing ->
-- If the sourceMap has nothing to say about this package,
-- check if it represents a sublibrary first
-- check if it represents a sub-library first
-- See: https://github.com/commercialhaskell/stack/issues/3899
case dpParentLibIdent dp of
Just (PackageIdentifier parentLibName version') ->
Expand Down
8 changes: 4 additions & 4 deletions src/Stack/Build/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ import Stack.Types.EnvConfig
)
import Stack.Types.FileDigestCache ( readFileDigest )
import Stack.Types.NamedComponent
( NamedComponent (..), isCInternalLib )
( NamedComponent (..), isCSubLib )
import Stack.Types.Package
( FileCacheInfo (..), LocalPackage (..), Package (..)
, PackageConfig (..), PackageLibraries (..)
Expand Down Expand Up @@ -280,7 +280,7 @@ splitComponents =
where
go a b c [] = (Set.fromList $ a [], Set.fromList $ b [], Set.fromList $ c [])
go a b c (CLib:xs) = go a b c xs
go a b c (CInternalLib x:xs) = go (a . (x:)) b c xs
go a b c (CSubLib x:xs) = go (a . (x:)) b c xs
go a b c (CExe x:xs) = go (a . (x:)) b c xs
go a b c (CTest x:xs) = go a (b . (x:)) c xs
go a b c (CBench x:xs) = go a b (c . (x:)) xs
Expand Down Expand Up @@ -348,7 +348,7 @@ loadLocalPackage pp = do
HasLibraries _ -> True
in hasLibrary
|| not (Set.null nonLibComponents)
|| not (Set.null $ packageInternalLibraries pkg)
|| not (Set.null $ packageSubLibraries pkg)

filterSkippedComponents =
Set.filter (not . (`elem` boptsSkipComponents bopts))
Expand Down Expand Up @@ -510,7 +510,7 @@ getPackageFilesForTargets pkg cabalFP nonLibComponents = do
(components',compFiles,otherFiles,warnings) <-
getPackageFiles (packageFiles pkg) cabalFP
let necessaryComponents =
Set.insert CLib $ Set.filter isCInternalLib (M.keysSet components')
Set.insert CLib $ Set.filter isCSubLib (M.keysSet components')
components = necessaryComponents `Set.union` nonLibComponents
componentsFiles = M.map
(\files ->
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build/Target.hs
Original file line number Diff line number Diff line change
Expand Up @@ -260,7 +260,7 @@ resolveRawTarget sma allLocs (ri, rt) =
-- 'ComponentName'
isCompNamed :: ComponentName -> NamedComponent -> Bool
isCompNamed _ CLib = False
isCompNamed t1 (CInternalLib t2) = t1 == t2
isCompNamed t1 (CSubLib t2) = t1 == t2
isCompNamed t1 (CExe t2) = t1 == t2
isCompNamed t1 (CTest t2) = t1 == t2
isCompNamed t1 (CBench t2) = t1 == t2
Expand Down
4 changes: 2 additions & 2 deletions src/Stack/ComponentFile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -332,7 +332,7 @@ componentOutputDir :: NamedComponent -> Path Abs Dir -> Path Abs Dir
componentOutputDir namedComponent distDir =
case namedComponent of
CLib -> buildDir distDir
CInternalLib name -> makeTmp name
CSubLib name -> makeTmp name
CExe name -> makeTmp name
CTest name -> makeTmp name
CBench name -> makeTmp name
Expand Down Expand Up @@ -551,7 +551,7 @@ componentBuildDir cabalVer component distDir
| otherwise =
case component of
CLib -> buildDir distDir
CInternalLib name -> buildDir distDir </> componentNameToDir name
CSubLib name -> buildDir distDir </> componentNameToDir name
CExe name -> buildDir distDir </> componentNameToDir name
CTest name -> buildDir distDir </> componentNameToDir name
CBench name -> buildDir distDir </> componentNameToDir name
Expand Down
21 changes: 11 additions & 10 deletions src/Stack/Coverage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -185,12 +185,12 @@ generateHpcReport pkgDir package tests = do
case packageLibraries package of
NoLibraries -> False
HasLibraries _ -> True
internalLibs = packageInternalLibraries package
subLibs = packageSubLibraries package
eincludeName <-
-- Pre-7.8 uses plain PKG-version in tix files.
if ghcVersion < mkVersion [7, 10] then pure $ Right $ Just [pkgId]
-- We don't expect to find a package key if there is no library.
else if not hasLibrary && Set.null internalLibs then pure $ Right Nothing
else if not hasLibrary && Set.null subLibs then pure $ Right Nothing
-- Look in the inplace DB for the package key.
-- See https://github.com/commercialhaskell/stack/issues/1181#issuecomment-148968986
else do
Expand All @@ -201,7 +201,7 @@ generateHpcReport pkgDir package tests = do
findPackageFieldForBuiltPackage
pkgDir
(packageIdentifier package)
internalLibs
subLibs
hpcNameField
case eincludeName of
Left err -> do
Expand Down Expand Up @@ -593,7 +593,7 @@ findPackageFieldForBuiltPackage ::
HasEnvConfig env
=> Path Abs Dir -> PackageIdentifier -> Set.Set Text -> Text
-> RIO env (Either Text [Text])
findPackageFieldForBuiltPackage pkgDir pkgId internalLibs field = do
findPackageFieldForBuiltPackage pkgDir pkgId subLibs field = do
distDir <- distDirFromDir pkgDir
let inplaceDir = distDir </> relDirPackageConfInplace
pkgIdStr = packageIdentifierString pkgId
Expand All @@ -613,12 +613,13 @@ findPackageFieldForBuiltPackage pkgDir pkgId internalLibs field = do
logDebug $ displayShow files
-- From all the files obtained from the scanning process above, we need to
-- identify which are .conf files and then ensure that there is at most one
-- .conf file for each library and internal library (some might be missing if
-- that component has not been built yet). We should error if there are more
-- than one .conf file for a component or if there are no .conf files at all
-- in the searched location.
-- .conf file for each library and sub-library (some might be missing if that
-- component has not been built yet). We should error if there are more than
-- one .conf file for a component or if there are no .conf files at all in the
-- searched location.
let toFilename = T.pack . toFilePath . filename
-- strip known prefix and suffix from the found files to determine only the conf files
-- strip known prefix and suffix from the found files to determine only
-- the .conf files
stripKnown =
T.stripSuffix ".conf" <=< T.stripPrefix (T.pack (pkgIdStr ++ "-"))
stripped =
Expand All @@ -629,7 +630,7 @@ findPackageFieldForBuiltPackage pkgDir pkgId internalLibs field = do
in if T.null z then "" else T.tail z
matchedComponents = map (\(n, f) -> (stripHash n, [f])) stripped
byComponents =
Map.restrictKeys (Map.fromListWith (++) matchedComponents) $ Set.insert "" internalLibs
Map.restrictKeys (Map.fromListWith (++) matchedComponents) $ Set.insert "" subLibs
logDebug $ displayShow byComponents
if Map.null $ Map.filter (\fs -> length fs > 1) byComponents
then case concat $ Map.elems byComponents of
Expand Down
6 changes: 3 additions & 3 deletions src/Stack/Ghci.hs
Original file line number Diff line number Diff line change
Expand Up @@ -791,7 +791,7 @@ figureOutMainFile bopts mainIsTargets targets0 packages =
renderComp c =
case c of
CLib -> "lib"
CInternalLib name -> "internal-lib:" <> fromString (T.unpack name)
CSubLib name -> "sub-lib:" <> fromString (T.unpack name)
CExe name -> "exe:" <> fromString (T.unpack name)
CTest name -> "test:" <> fromString ( T.unpack name)
CBench name -> "bench:" <> fromString (T.unpack name)
Expand Down Expand Up @@ -939,9 +939,9 @@ wantedPackageComponents _ (TargetComps cs) _ = cs
wantedPackageComponents bopts (TargetAll PTProject) pkg = S.fromList $
(case packageLibraries pkg of
NoLibraries -> []
HasLibraries names -> CLib : map CInternalLib (S.toList names)) ++
HasLibraries names -> CLib : map CSubLib (S.toList names)) ++
map CExe (S.toList (packageExes pkg)) <>
map CInternalLib (S.toList $ packageInternalLibraries pkg) <>
map CSubLib (S.toList $ packageSubLibraries pkg) <>
(if boptsTests bopts then map CTest (M.keys (packageTests pkg)) else []) <>
(if boptsBenchmarks bopts then map CBench (S.toList (packageBenchmarks pkg)) else [])
wantedPackageComponents _ _ _ = S.empty
Expand Down
Loading

0 comments on commit 1908cf6

Please sign in to comment.