cabal init -i should sanitize suggested package name (fix #8404) (#8561)
[cabal.git] / cabal-install / src / Distribution / Client / DistDirLayout.hs
blob2b88ddc430277670cbed906f59535382a6a445fe
1 {-# LANGUAGE RecordWildCards #-}
3 -- |
4 --
5 -- The layout of the .\/dist\/ directory where cabal keeps all of its state
6 -- and build artifacts.
7 --
8 module Distribution.Client.DistDirLayout (
9 -- * 'DistDirLayout'
10 DistDirLayout(..),
11 DistDirParams(..),
12 defaultDistDirLayout,
13 ProjectRoot(..),
15 -- * 'StoreDirLayout'
16 StoreDirLayout(..),
17 defaultStoreDirLayout,
19 -- * 'CabalDirLayout'
20 CabalDirLayout(..),
21 mkCabalDirLayout,
22 defaultCabalDirLayout
23 ) where
25 import Distribution.Client.Compat.Prelude
26 import Prelude ()
28 import System.FilePath
30 import Distribution.Client.Config
31 ( defaultStoreDir, defaultLogsDir)
32 import Distribution.Package
33 ( PackageId, PackageIdentifier, ComponentId, UnitId )
34 import Distribution.Compiler
35 import Distribution.Simple.Compiler
36 ( PackageDB(..), PackageDBStack, OptimisationLevel(..) )
37 import Distribution.Types.ComponentName
38 import Distribution.Types.LibraryName
39 import Distribution.System
42 -- | Information which can be used to construct the path to
43 -- the build directory of a build. This is LESS fine-grained
44 -- than what goes into the hashed 'InstalledPackageId',
45 -- and for good reason: we don't want this path to change if
46 -- the user, say, adds a dependency to their project.
47 data DistDirParams = DistDirParams {
48 distParamUnitId :: UnitId,
49 distParamPackageId :: PackageId,
50 distParamComponentId :: ComponentId,
51 distParamComponentName :: Maybe ComponentName,
52 distParamCompilerId :: CompilerId,
53 distParamPlatform :: Platform,
54 distParamOptimization :: OptimisationLevel
55 -- TODO (see #3343):
56 -- Flag assignments
57 -- Optimization
61 -- | The layout of the project state directory. Traditionally this has been
62 -- called the @dist@ directory.
64 data DistDirLayout = DistDirLayout {
66 -- | The root directory of the project. Many other files are relative to
67 -- this location. In particular, the @cabal.project@ lives here.
69 distProjectRootDirectory :: FilePath,
71 -- | The @cabal.project@ file and related like @cabal.project.freeze@.
72 -- The parameter is for the extension, like \"freeze\", or \"\" for the
73 -- main file.
75 distProjectFile :: String -> FilePath,
77 -- | The \"dist\" directory, which is the root of where cabal keeps all
78 -- its state including the build artifacts from each package we build.
80 distDirectory :: FilePath,
82 -- | The directory under dist where we keep the build artifacts for a
83 -- package we're building from a local directory.
85 -- This uses a 'UnitId' not just a 'PackageName' because technically
86 -- we can have multiple instances of the same package in a solution
87 -- (e.g. setup deps).
89 distBuildDirectory :: DistDirParams -> FilePath,
90 distBuildRootDirectory :: FilePath,
92 -- | The directory under dist where we download tarballs and source
93 -- control repos to.
95 distDownloadSrcDirectory :: FilePath,
97 -- | The directory under dist where we put the unpacked sources of
98 -- packages, in those cases where it makes sense to keep the build
99 -- artifacts to reduce rebuild times.
101 distUnpackedSrcDirectory :: PackageId -> FilePath,
102 distUnpackedSrcRootDirectory :: FilePath,
104 -- | The location for project-wide cache files (e.g. state used in
105 -- incremental rebuilds).
107 distProjectCacheFile :: String -> FilePath,
108 distProjectCacheDirectory :: FilePath,
110 -- | The location for package-specific cache files (e.g. state used in
111 -- incremental rebuilds).
113 distPackageCacheFile :: DistDirParams -> String -> FilePath,
114 distPackageCacheDirectory :: DistDirParams -> FilePath,
116 -- | The location that sdists are placed by default.
117 distSdistFile :: PackageId -> FilePath,
118 distSdistDirectory :: FilePath,
120 distTempDirectory :: FilePath,
121 distBinDirectory :: FilePath,
123 distPackageDB :: CompilerId -> PackageDB
127 -- | The layout of a cabal nix-style store.
129 data StoreDirLayout = StoreDirLayout {
130 storeDirectory :: CompilerId -> FilePath,
131 storePackageDirectory :: CompilerId -> UnitId -> FilePath,
132 storePackageDBPath :: CompilerId -> FilePath,
133 storePackageDB :: CompilerId -> PackageDB,
134 storePackageDBStack :: CompilerId -> PackageDBStack,
135 storeIncomingDirectory :: CompilerId -> FilePath,
136 storeIncomingLock :: CompilerId -> UnitId -> FilePath
140 --TODO: move to another module, e.g. CabalDirLayout?
141 -- or perhaps rename this module to DirLayouts.
143 -- | The layout of the user-wide cabal directory, that is the @~/.cabal@ dir
144 -- on unix, and equivalents on other systems.
146 -- At the moment this is just a partial specification, but the idea is
147 -- eventually to cover it all.
149 data CabalDirLayout = CabalDirLayout {
150 cabalStoreDirLayout :: StoreDirLayout,
152 cabalLogsDirectory :: FilePath
156 -- | Information about the root directory of the project.
158 -- It can either be an implicit project root in the current dir if no
159 -- @cabal.project@ file is found, or an explicit root if the file is found.
161 data ProjectRoot =
162 -- | -- ^ An implicit project root. It contains the absolute project
163 -- root dir.
164 ProjectRootImplicit FilePath
166 -- | -- ^ An explicit project root. It contains the absolute project
167 -- root dir and the relative @cabal.project@ file (or explicit override)
168 | ProjectRootExplicit FilePath FilePath
169 deriving (Eq, Show)
171 -- | Make the default 'DistDirLayout' based on the project root dir and
172 -- optional overrides for the location of the @dist@ directory and the
173 -- @cabal.project@ file.
175 defaultDistDirLayout :: ProjectRoot -- ^ the project root
176 -> Maybe FilePath -- ^ the @dist@ directory or default
177 -- (absolute or relative to the root)
178 -> DistDirLayout
179 defaultDistDirLayout projectRoot mdistDirectory =
180 DistDirLayout {..}
181 where
182 (projectRootDir, projectFile) = case projectRoot of
183 ProjectRootImplicit dir -> (dir, dir </> "cabal.project")
184 ProjectRootExplicit dir file -> (dir, dir </> file)
186 distProjectRootDirectory :: FilePath
187 distProjectRootDirectory = projectRootDir
189 distProjectFile :: String -> FilePath
190 distProjectFile ext = projectFile <.> ext
192 distDirectory :: FilePath
193 distDirectory = distProjectRootDirectory
194 </> fromMaybe "dist-newstyle" mdistDirectory
195 --TODO: switch to just dist at some point, or some other new name
197 distBuildRootDirectory :: FilePath
198 distBuildRootDirectory = distDirectory </> "build"
200 distBuildDirectory :: DistDirParams -> FilePath
201 distBuildDirectory params =
202 distBuildRootDirectory </>
203 prettyShow (distParamPlatform params) </>
204 prettyShow (distParamCompilerId params) </>
205 prettyShow (distParamPackageId params) </>
206 (case distParamComponentName params of
207 Nothing -> ""
208 Just (CLibName LMainLibName) -> ""
209 Just (CLibName (LSubLibName name)) -> "l" </> prettyShow name
210 Just (CFLibName name) -> "f" </> prettyShow name
211 Just (CExeName name) -> "x" </> prettyShow name
212 Just (CTestName name) -> "t" </> prettyShow name
213 Just (CBenchName name) -> "b" </> prettyShow name) </>
214 (case distParamOptimization params of
215 NoOptimisation -> "noopt"
216 NormalOptimisation -> ""
217 MaximumOptimisation -> "opt") </>
218 (let uid_str = prettyShow (distParamUnitId params)
219 in if uid_str == prettyShow (distParamComponentId params)
220 then ""
221 else uid_str)
223 distUnpackedSrcRootDirectory :: FilePath
224 distUnpackedSrcRootDirectory = distDirectory </> "src"
226 distUnpackedSrcDirectory :: PackageId -> FilePath
227 distUnpackedSrcDirectory pkgid = distUnpackedSrcRootDirectory
228 </> prettyShow pkgid
229 -- we shouldn't get name clashes so this should be fine:
230 distDownloadSrcDirectory :: FilePath
231 distDownloadSrcDirectory = distUnpackedSrcRootDirectory
233 distProjectCacheDirectory :: FilePath
234 distProjectCacheDirectory = distDirectory </> "cache"
236 distProjectCacheFile :: FilePath -> FilePath
237 distProjectCacheFile name = distProjectCacheDirectory </> name
239 distPackageCacheDirectory :: DistDirParams -> FilePath
240 distPackageCacheDirectory params = distBuildDirectory params </> "cache"
242 distPackageCacheFile :: DistDirParams -> String -> FilePath
243 distPackageCacheFile params name = distPackageCacheDirectory params </> name
245 distSdistFile :: PackageIdentifier -> FilePath
246 distSdistFile pid = distSdistDirectory </> prettyShow pid <.> "tar.gz"
248 distSdistDirectory :: FilePath
249 distSdistDirectory = distDirectory </> "sdist"
251 distTempDirectory :: FilePath
252 distTempDirectory = distDirectory </> "tmp"
254 distBinDirectory :: FilePath
255 distBinDirectory = distDirectory </> "bin"
257 distPackageDBPath :: CompilerId -> FilePath
258 distPackageDBPath compid = distDirectory </> "packagedb" </> prettyShow compid
260 distPackageDB :: CompilerId -> PackageDB
261 distPackageDB = SpecificPackageDB . distPackageDBPath
264 defaultStoreDirLayout :: FilePath -> StoreDirLayout
265 defaultStoreDirLayout storeRoot =
266 StoreDirLayout {..}
267 where
268 storeDirectory :: CompilerId -> FilePath
269 storeDirectory compid =
270 storeRoot </> prettyShow compid
272 storePackageDirectory :: CompilerId -> UnitId -> FilePath
273 storePackageDirectory compid ipkgid =
274 storeDirectory compid </> prettyShow ipkgid
276 storePackageDBPath :: CompilerId -> FilePath
277 storePackageDBPath compid =
278 storeDirectory compid </> "package.db"
280 storePackageDB :: CompilerId -> PackageDB
281 storePackageDB compid =
282 SpecificPackageDB (storePackageDBPath compid)
284 storePackageDBStack :: CompilerId -> PackageDBStack
285 storePackageDBStack compid =
286 [GlobalPackageDB, storePackageDB compid]
288 storeIncomingDirectory :: CompilerId -> FilePath
289 storeIncomingDirectory compid =
290 storeDirectory compid </> "incoming"
292 storeIncomingLock :: CompilerId -> UnitId -> FilePath
293 storeIncomingLock compid unitid =
294 storeIncomingDirectory compid </> prettyShow unitid <.> "lock"
297 defaultCabalDirLayout :: IO CabalDirLayout
298 defaultCabalDirLayout =
299 mkCabalDirLayout Nothing Nothing
301 mkCabalDirLayout :: Maybe FilePath -- ^ Store directory. Must be absolute
302 -> Maybe FilePath -- ^ Log directory
303 -> IO CabalDirLayout
304 mkCabalDirLayout mstoreDir mlogDir = do
305 cabalStoreDirLayout <-
306 defaultStoreDirLayout <$> maybe defaultStoreDir pure mstoreDir
307 cabalLogsDirectory <-
308 maybe defaultLogsDir pure mlogDir
309 pure $ CabalDirLayout {..}