Add “Ignore warning” option to cabal check
[cabal.git] / cabal-install / src / Distribution / Client / DistDirLayout.hs
blob2b4bc54fb3ecd517bb0db30ee93cc50fd772c022
1 {-# LANGUAGE RecordWildCards #-}
3 -- |
4 --
5 -- The layout of the .\/dist\/ directory where cabal keeps all of its state
6 -- and build artifacts.
7 module Distribution.Client.DistDirLayout
8 ( -- * 'DistDirLayout'
9 DistDirLayout (..)
10 , DistDirParams (..)
11 , defaultDistDirLayout
13 -- * 'ProjectRoot'
14 , ProjectRoot (..)
15 , defaultProjectFile
17 -- * 'StoreDirLayout'
18 , StoreDirLayout (..)
19 , defaultStoreDirLayout
21 -- * 'CabalDirLayout'
22 , CabalDirLayout (..)
23 , mkCabalDirLayout
24 , defaultCabalDirLayout
25 ) where
27 import Distribution.Client.Compat.Prelude
28 import Prelude ()
30 import System.FilePath
32 import Distribution.Client.Config
33 ( defaultLogsDir
34 , defaultStoreDir
36 import Distribution.Compiler
37 import Distribution.Package
38 ( ComponentId
39 , PackageId
40 , PackageIdentifier
41 , UnitId
43 import Distribution.Simple.Compiler
44 ( OptimisationLevel (..)
45 , PackageDB (..)
46 , PackageDBStack
48 import Distribution.System
49 import Distribution.Types.ComponentName
50 import Distribution.Types.LibraryName
52 -- | Information which can be used to construct the path to
53 -- the build directory of a build. This is LESS fine-grained
54 -- than what goes into the hashed 'InstalledPackageId',
55 -- and for good reason: we don't want this path to change if
56 -- the user, say, adds a dependency to their project.
57 data DistDirParams = DistDirParams
58 { distParamUnitId :: UnitId
59 , distParamPackageId :: PackageId
60 , distParamComponentId :: ComponentId
61 , distParamComponentName :: Maybe ComponentName
62 , distParamCompilerId :: CompilerId
63 , distParamPlatform :: Platform
64 , distParamOptimization :: OptimisationLevel
65 -- TODO (see #3343):
66 -- Flag assignments
67 -- Optimization
70 -- | The layout of the project state directory. Traditionally this has been
71 -- called the @dist@ directory.
72 data DistDirLayout = DistDirLayout
73 { distProjectRootDirectory :: FilePath
74 -- ^ The root directory of the project. Many other files are relative to
75 -- this location (e.g. the @cabal.project@ file).
76 , distProjectFile :: String -> FilePath
77 -- ^ The @cabal.project@ file and related like @cabal.project.freeze@.
78 -- The parameter is for the extension, like \"freeze\", or \"\" for the
79 -- main file.
80 , distDirectory :: FilePath
81 -- ^ The \"dist\" directory, which is the root of where cabal keeps all
82 -- its state including the build artifacts from each package we build.
83 , distBuildDirectory :: DistDirParams -> FilePath
84 -- ^ The directory under dist where we keep the build artifacts for a
85 -- package we're building from a local directory.
87 -- This uses a 'UnitId' not just a 'PackageName' because technically
88 -- we can have multiple instances of the same package in a solution
89 -- (e.g. setup deps).
90 , distBuildRootDirectory :: FilePath
91 , distDownloadSrcDirectory :: FilePath
92 -- ^ The directory under dist where we download tarballs and source
93 -- control repos to.
94 , distUnpackedSrcDirectory :: PackageId -> FilePath
95 -- ^ The directory under dist where we put the unpacked sources of
96 -- packages, in those cases where it makes sense to keep the build
97 -- artifacts to reduce rebuild times.
98 , distUnpackedSrcRootDirectory :: FilePath
99 , distProjectCacheFile :: String -> FilePath
100 -- ^ The location for project-wide cache files (e.g. state used in
101 -- incremental rebuilds).
102 , distProjectCacheDirectory :: FilePath
103 , distPackageCacheFile :: DistDirParams -> String -> FilePath
104 -- ^ The location for package-specific cache files (e.g. state used in
105 -- incremental rebuilds).
106 , distPackageCacheDirectory :: DistDirParams -> FilePath
107 , distSdistFile :: PackageId -> FilePath
108 -- ^ The location that sdists are placed by default.
109 , distSdistDirectory :: FilePath
110 , distTempDirectory :: FilePath
111 , distBinDirectory :: FilePath
112 , distPackageDB :: CompilerId -> PackageDB
113 , distHaddockOutputDir :: Maybe FilePath
114 -- ^ Is needed when `--haddock-output-dir` flag is used.
117 -- | The layout of a cabal nix-style store.
118 data StoreDirLayout = StoreDirLayout
119 { storeDirectory :: CompilerId -> FilePath
120 , storePackageDirectory :: CompilerId -> UnitId -> FilePath
121 , storePackageDBPath :: CompilerId -> FilePath
122 , storePackageDB :: CompilerId -> PackageDB
123 , storePackageDBStack :: CompilerId -> PackageDBStack
124 , storeIncomingDirectory :: CompilerId -> FilePath
125 , storeIncomingLock :: CompilerId -> UnitId -> FilePath
128 -- TODO: move to another module, e.g. CabalDirLayout?
129 -- or perhaps rename this module to DirLayouts.
131 -- | The layout of the user-wide cabal directory, that is the @~/.cabal@ dir
132 -- on unix, and equivalents on other systems.
134 -- At the moment this is just a partial specification, but the idea is
135 -- eventually to cover it all.
136 data CabalDirLayout = CabalDirLayout
137 { cabalStoreDirLayout :: StoreDirLayout
138 , cabalLogsDirectory :: FilePath
141 -- | Information about the root directory of the project.
143 -- It can either be an implicit project root in the current dir if no
144 -- @cabal.project@ file is found, or an explicit root if either
145 -- the file is found or the project root directory was specicied.
146 data ProjectRoot
147 = -- | An implicit project root. It contains the absolute project
148 -- root dir.
149 ProjectRootImplicit FilePath
150 | -- | An explicit project root. It contains the absolute project
151 -- root dir and the relative @cabal.project@ file (or explicit override)
152 ProjectRootExplicit FilePath FilePath
153 | -- | An explicit, absolute project root dir and an explicit, absolute
154 -- @cabal.project@ file.
155 ProjectRootExplicitAbsolute FilePath FilePath
156 deriving (Eq, Show)
158 defaultProjectFile :: FilePath
159 defaultProjectFile = "cabal.project"
161 -- | Make the default 'DistDirLayout' based on the project root dir and
162 -- optional overrides for the location of the @dist@ directory, the
163 -- @cabal.project@ file and the documentation directory.
164 defaultDistDirLayout
165 :: ProjectRoot
166 -- ^ the project root
167 -> Maybe FilePath
168 -- ^ the @dist@ directory or default
169 -- (absolute or relative to the root)
170 -> Maybe FilePath
171 -- ^ the documentation directory
172 -> DistDirLayout
173 defaultDistDirLayout projectRoot mdistDirectory haddockOutputDir =
174 DistDirLayout{..}
175 where
176 (projectRootDir, projectFile) = case projectRoot of
177 ProjectRootImplicit dir -> (dir, dir </> defaultProjectFile)
178 ProjectRootExplicit dir file -> (dir, dir </> file)
179 ProjectRootExplicitAbsolute dir file -> (dir, file)
181 distProjectRootDirectory :: FilePath
182 distProjectRootDirectory = projectRootDir
184 distProjectFile :: String -> FilePath
185 distProjectFile ext = projectFile <.> ext
187 distDirectory :: FilePath
188 distDirectory =
189 distProjectRootDirectory
190 </> fromMaybe "dist-newstyle" mdistDirectory
191 -- TODO: switch to just dist at some point, or some other new name
193 distBuildRootDirectory :: FilePath
194 distBuildRootDirectory = distDirectory </> "build"
196 distBuildDirectory :: DistDirParams -> FilePath
197 distBuildDirectory params =
198 distBuildRootDirectory
199 </> prettyShow (distParamPlatform params)
200 </> prettyShow (distParamCompilerId params)
201 </> prettyShow (distParamPackageId params)
202 </> ( case distParamComponentName params of
203 Nothing -> ""
204 Just (CLibName LMainLibName) -> ""
205 Just (CLibName (LSubLibName name)) -> "l" </> prettyShow name
206 Just (CFLibName name) -> "f" </> prettyShow name
207 Just (CExeName name) -> "x" </> prettyShow name
208 Just (CTestName name) -> "t" </> prettyShow name
209 Just (CBenchName name) -> "b" </> prettyShow name
211 </> ( case distParamOptimization params of
212 NoOptimisation -> "noopt"
213 NormalOptimisation -> ""
214 MaximumOptimisation -> "opt"
216 </> ( let uid_str = prettyShow (distParamUnitId params)
217 in if uid_str == prettyShow (distParamComponentId params)
218 then ""
219 else uid_str
222 distUnpackedSrcRootDirectory :: FilePath
223 distUnpackedSrcRootDirectory = distDirectory </> "src"
225 distUnpackedSrcDirectory :: PackageId -> FilePath
226 distUnpackedSrcDirectory pkgid =
227 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
263 distHaddockOutputDir :: Maybe FilePath
264 distHaddockOutputDir = haddockOutputDir
266 defaultStoreDirLayout :: FilePath -> StoreDirLayout
267 defaultStoreDirLayout storeRoot =
268 StoreDirLayout{..}
269 where
270 storeDirectory :: CompilerId -> FilePath
271 storeDirectory compid =
272 storeRoot </> prettyShow compid
274 storePackageDirectory :: CompilerId -> UnitId -> FilePath
275 storePackageDirectory compid ipkgid =
276 storeDirectory compid </> prettyShow ipkgid
278 storePackageDBPath :: CompilerId -> FilePath
279 storePackageDBPath compid =
280 storeDirectory compid </> "package.db"
282 storePackageDB :: CompilerId -> PackageDB
283 storePackageDB compid =
284 SpecificPackageDB (storePackageDBPath compid)
286 storePackageDBStack :: CompilerId -> PackageDBStack
287 storePackageDBStack compid =
288 [GlobalPackageDB, storePackageDB compid]
290 storeIncomingDirectory :: CompilerId -> FilePath
291 storeIncomingDirectory compid =
292 storeDirectory compid </> "incoming"
294 storeIncomingLock :: CompilerId -> UnitId -> FilePath
295 storeIncomingLock compid unitid =
296 storeIncomingDirectory compid </> prettyShow unitid <.> "lock"
298 defaultCabalDirLayout :: IO CabalDirLayout
299 defaultCabalDirLayout =
300 mkCabalDirLayout Nothing Nothing
302 mkCabalDirLayout
303 :: Maybe FilePath
304 -- ^ Store directory. Must be absolute
305 -> Maybe FilePath
306 -- ^ Log directory
307 -> IO CabalDirLayout
308 mkCabalDirLayout mstoreDir mlogDir = do
309 cabalStoreDirLayout <-
310 defaultStoreDirLayout <$> maybe defaultStoreDir pure mstoreDir
311 cabalLogsDirectory <-
312 maybe defaultLogsDir pure mlogDir
313 pure $ CabalDirLayout{..}