Skip to content
Snippets Groups Projects
Commit fe3596b9 authored by Duncan Coutts's avatar Duncan Coutts Committed by Mikhail Glushenkov
Browse files

Add new DistDirLayout module

This describes in one place the layout of the new dist dir, as used by
the nix-local-build branch. Also a similar approach to describing the
layout of the user-wide cabal directory.

The idea is that this centralises the description and makes it easier
to change and handle systematically (e.g. we have problems currently
with some user-wide files not being reolocatable).

(cherry picked from commit 7907a55c)
parent 306210bc
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE RecordWildCards #-}
-- |
--
-- The layout of the .\/dist\/ directory where cabal keeps all of it's state
-- and build artifacts.
--
module Distribution.Client.DistDirLayout where
import System.FilePath
import Distribution.Package
( PackageId )
import Distribution.Compiler
import Distribution.Simple.Compiler (PackageDB(..))
import Distribution.Text
import Distribution.Client.Types
( InstalledPackageId )
-- | The layout of the project state directory. Traditionally this has been
-- called the @dist@ directory.
--
data DistDirLayout = DistDirLayout {
-- | The dist directory, which is the root of where cabal keeps all its
-- state including the build artifacts from each package we build.
--
distDirectory :: FilePath,
-- | The directory under dist where we keep the build artifacts for a
-- package we're building from a local directory.
--
-- This uses a 'PackageId' not just a 'PackageName' because technically
-- we can have multiple instances of the same package in a solution
-- (e.g. setup deps).
--
distBuildDirectory :: PackageId -> FilePath,
distBuildRootDirectory :: FilePath,
-- | The directory under dist where we put the unpacked sources of
-- packages, in those cases where it makes sense to keep the build
-- artifacts to reduce rebuild times. These can be tarballs or could be
-- scm repos.
--
distUnpackedSrcDirectory :: PackageId -> FilePath,
distUnpackedSrcRootDirectory :: FilePath,
-- | The location for project-wide cache files (e.g. state used in
-- incremental rebuilds).
--
distProjectCacheFile :: String -> FilePath,
distProjectCacheDirectory :: FilePath,
-- | The location for package-specific cache files (e.g. state used in
-- incremental rebuilds).
--
distPackageCacheFile :: PackageId -> String -> FilePath,
distPackageCacheDirectory :: PackageId -> FilePath,
distTempDirectory :: FilePath,
distBinDirectory :: FilePath,
distPackageDB :: CompilerId -> PackageDB
}
--TODO: move to another module, e.g. CabalDirLayout?
data CabalDirLayout = CabalDirLayout {
cabalStoreDirectory :: CompilerId -> FilePath,
cabalStorePackageDirectory :: CompilerId -> InstalledPackageId
-> FilePath,
cabalStorePackageDBPath :: CompilerId -> FilePath,
cabalStorePackageDB :: CompilerId -> PackageDB,
cabalPackageCacheDirectory :: FilePath,
cabalLogsDirectory :: FilePath,
cabalWorldFile :: FilePath
}
defaultDistDirLayout :: FilePath -> DistDirLayout
defaultDistDirLayout projectRootDirectory =
DistDirLayout {..}
where
distDirectory = projectRootDirectory </> "dist-newstyle"
--TODO: switch to just dist at some point, or some other new name
distBuildRootDirectory = distDirectory </> "build"
distBuildDirectory pkgid = distBuildRootDirectory </> display pkgid
distUnpackedSrcRootDirectory = distDirectory </> "src"
distUnpackedSrcDirectory pkgid = distUnpackedSrcRootDirectory
</> display pkgid
distProjectCacheDirectory = distDirectory </> "cache"
distProjectCacheFile name = distProjectCacheDirectory </> name
distPackageCacheDirectory pkgid = distBuildDirectory pkgid </> "cache"
distPackageCacheFile pkgid name = distPackageCacheDirectory pkgid </> name
distTempDirectory = distDirectory </> "tmp"
distBinDirectory = distDirectory </> "bin"
distPackageDBPath compid = distDirectory </> "packagedb" </> display compid
distPackageDB = SpecificPackageDB . distPackageDBPath
defaultCabalDirLayout :: FilePath -> CabalDirLayout
defaultCabalDirLayout cabalDir =
CabalDirLayout {..}
where
cabalStoreDirectory compid =
cabalDir </> "store" </> display compid
cabalStorePackageDirectory compid ipkgid =
cabalStoreDirectory compid </> display ipkgid
cabalStorePackageDBPath compid =
cabalStoreDirectory compid </> "package.db"
cabalStorePackageDB =
SpecificPackageDB . cabalStorePackageDBPath
cabalPackageCacheDirectory = cabalDir </> "packages"
cabalLogsDirectory = cabalDir </> "logs"
cabalWorldFile = cabalDir </> "world"
......@@ -64,6 +64,22 @@ instance Binary SourcePackageDb
-- * Various kinds of information about packages
-- ------------------------------------------------------------
-- | Within Cabal the library we no longer have a @InstalledPackageId@ type.
-- That's because it deals with the compilers' notion of a registered library,
-- and those really are libraries not packages. Those are now named units.
--
-- The package management layer does however deal with installed packages, as
-- whole packages not just as libraries. So we do still need a type for
-- installed package ids. At the moment however we track instaled packages via
-- their primary library, which is a unit id. In future this may change
-- slightly and we may distinguish these two types and have an explicit
-- conversion when we register units with the compiler.
--
type InstalledPackageId = UnitId
installedPackageId :: HasUnitId pkg => pkg -> InstalledPackageId
installedPackageId = installedUnitId
-- | Subclass of packages that have specific versioned dependencies.
--
-- So for example a not-yet-configured package has dependencies on version
......
......@@ -69,6 +69,7 @@ import qualified Distribution.Client.List as List
--TODO: temporary import, just to force these modules to be built.
-- It will be replaced by import of new build command once merged.
import Distribution.Client.RebuildMonad ()
import Distribution.Client.DistDirLayout ()
import Distribution.Client.Install (install)
import Distribution.Client.Configure (configure)
......
......@@ -153,6 +153,7 @@ executable cabal
Distribution.Client.Dependency.Modular.Tree
Distribution.Client.Dependency.Modular.Validate
Distribution.Client.Dependency.Modular.Version
Distribution.Client.DistDirLayout
Distribution.Client.Exec
Distribution.Client.Fetch
Distribution.Client.FetchUtils
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment