1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 {-# LANGUAGE NamedFieldPuns #-}
4 {-# LANGUAGE RecordWildCards #-}
6 -- | Functions to calculate nix-style hashes for package ids.
8 -- The basic idea is simple, hash the combination of:
10 -- * the package tarball
11 -- * the ids of all the direct dependencies
12 -- * other local configuration (flags, profiling, etc)
13 module Distribution
.Client
.PackageHash
14 ( -- * Calculating package hashes
15 PackageHashInputs
(..)
16 , PackageHashConfigInputs
(..)
18 , hashedInstalledPackageId
19 , hashPackageHashInputs
20 , renderPackageHashInputs
22 -- ** Platform-specific variations
23 , hashedInstalledPackageIdLong
24 , hashedInstalledPackageIdShort
27 import Distribution
.Client
.Compat
.Prelude
30 import Distribution
.Client
.HashValue
31 import Distribution
.Client
.Types
34 import Distribution
.Package
36 , PackageIdentifier
(..)
40 import Distribution
.Simple
.Compiler
43 , OptimisationLevel
(..)
45 , ProfDetailLevel
(..)
48 import Distribution
.Simple
.InstallDirs
52 import qualified Distribution
.Solver
.Types
.ComponentDeps
as CD
53 import Distribution
.System
58 import Distribution
.Types
.Flag
62 import Distribution
.Types
.PkgconfigVersion
(PkgconfigVersion
)
64 import qualified Data
.ByteString
.Lazy
.Char8
as LBS
65 import qualified Data
.Map
as Map
66 import qualified Data
.Set
as Set
68 -------------------------------
69 -- Calculating package hashes
72 -- | Calculate a 'InstalledPackageId' for a package using our nix-style
73 -- inputs hashing method.
75 -- Note that due to path length limitations on Windows, this function uses
76 -- a different method on Windows that produces shorted package ids.
77 -- See 'hashedInstalledPackageIdLong' vs 'hashedInstalledPackageIdShort'.
78 hashedInstalledPackageId
:: PackageHashInputs
-> InstalledPackageId
79 hashedInstalledPackageId
80 | buildOS
== Windows
= hashedInstalledPackageIdShort
81 | buildOS
== OSX
= hashedInstalledPackageIdVeryShort
82 |
otherwise = hashedInstalledPackageIdLong
84 -- | Calculate a 'InstalledPackageId' for a package using our nix-style
85 -- inputs hashing method.
87 -- This produces large ids with big hashes. It is only suitable for systems
88 -- without significant path length limitations (ie not Windows).
89 hashedInstalledPackageIdLong
:: PackageHashInputs
-> InstalledPackageId
90 hashedInstalledPackageIdLong
91 pkghashinputs
@PackageHashInputs
{pkgHashPkgId
, pkgHashComponent
} =
93 prettyShow pkgHashPkgId
-- to be a bit user friendly
94 ++ maybe "" displayComponent pkgHashComponent
96 ++ showHashValue
(hashPackageHashInputs pkghashinputs
)
98 displayComponent
:: CD
.Component
-> String
99 displayComponent CD
.ComponentLib
= ""
100 displayComponent
(CD
.ComponentSubLib s
) = "-l-" ++ prettyShow s
101 displayComponent
(CD
.ComponentFLib s
) = "-f-" ++ prettyShow s
102 displayComponent
(CD
.ComponentExe s
) = "-e-" ++ prettyShow s
103 displayComponent
(CD
.ComponentTest s
) = "-t-" ++ prettyShow s
104 displayComponent
(CD
.ComponentBench s
) = "-b-" ++ prettyShow s
105 displayComponent CD
.ComponentSetup
= "-setup"
107 -- | On Windows we have serious problems with path lengths. Windows imposes a
108 -- maximum path length of 260 chars, and even if we can use the windows long
109 -- path APIs ourselves, we cannot guarantee that ghc, gcc, ld, ar, etc etc all
112 -- So our only choice is to limit the lengths of the paths, and the only real
113 -- way to do that is to limit the size of the 'InstalledPackageId's that we
114 -- generate. We do this by truncating the package names and versions and also
115 -- by truncating the hash sizes.
117 -- Truncating the package names and versions is technically ok because they are
118 -- just included for human convenience, the full source package id is included
121 -- Truncating the hash size is disappointing but also technically ok. We
122 -- rely on the hash primarily for collision avoidance not for any security
123 -- properties (at least for now).
124 hashedInstalledPackageIdShort
:: PackageHashInputs
-> InstalledPackageId
125 hashedInstalledPackageIdShort pkghashinputs
@PackageHashInputs
{pkgHashPkgId
} =
130 [ truncateStr
14 (prettyShow name
)
131 , truncateStr
8 (prettyShow version
)
132 , showHashValue
(truncateHash
20 (hashPackageHashInputs pkghashinputs
))
135 PackageIdentifier name version
= pkgHashPkgId
137 -- Truncate a string, with a visual indication that it is truncated.
140 |
otherwise = take (n
- 1) s
++ "_"
142 -- | On macOS we shorten the name very aggressively. The mach-o linker on
143 -- macOS has a limited load command size, to which the name of the library
144 -- as well as its relative path (\@rpath) entry count. To circumvent this,
145 -- on macOS the libraries are not stored as
146 -- @store/<libraryname>/libHS<libraryname>.dylib@
147 -- where libraryname contains the libraries name, version and abi hash, but in
148 -- @store/lib/libHS<very short libraryname>.dylib@
149 -- where the very short library name drops all vowels from the package name,
150 -- and truncates the hash to 4 bytes.
152 -- We therefore we only need one \@rpath entry to @store/lib@ instead of one
153 -- \@rpath entry for each library. And the reduced library name saves some
156 -- This however has two major drawbacks:
157 -- 1) Packages can collide more easily due to the shortened hash.
158 -- 2) The libraries are *not* prefix relocatable anymore as they all end up
159 -- in the same @store/lib@ folder.
161 -- The ultimate solution would have to include generating proxy dynamic
162 -- libraries on macOS, such that the proxy libraries and the linked libraries
163 -- stay under the load command limit, and the recursive linker is still able
164 -- to link all of them.
165 hashedInstalledPackageIdVeryShort
:: PackageHashInputs
-> InstalledPackageId
166 hashedInstalledPackageIdVeryShort pkghashinputs
@PackageHashInputs
{pkgHashPkgId
} =
170 [ filter (not . flip elem "aeiou") (prettyShow name
)
172 , showHashValue
(truncateHash
4 (hashPackageHashInputs pkghashinputs
))
175 PackageIdentifier name version
= pkgHashPkgId
177 -- | All the information that contributes to a package's hash, and thus its
178 -- 'InstalledPackageId'.
179 data PackageHashInputs
= PackageHashInputs
180 { pkgHashPkgId
:: PackageId
181 , pkgHashComponent
:: Maybe CD
.Component
182 , pkgHashSourceHash
:: PackageSourceHash
183 , pkgHashPkgConfigDeps
:: Set
(PkgconfigName
, Maybe PkgconfigVersion
)
184 , pkgHashDirectDeps
:: Set InstalledPackageId
185 , pkgHashOtherConfig
:: PackageHashConfigInputs
188 type PackageSourceHash
= HashValue
190 -- | Those parts of the package configuration that contribute to the
192 data PackageHashConfigInputs
= PackageHashConfigInputs
193 { pkgHashCompilerId
:: CompilerId
194 , pkgHashPlatform
:: Platform
195 , pkgHashFlagAssignment
:: FlagAssignment
-- complete not partial
196 , pkgHashConfigureScriptArgs
:: [String] -- just ./configure for build-type Configure
197 , pkgHashVanillaLib
:: Bool
198 , pkgHashSharedLib
:: Bool
199 , pkgHashDynExe
:: Bool
200 , pkgHashFullyStaticExe
:: Bool
201 , pkgHashGHCiLib
:: Bool
202 , pkgHashProfLib
:: Bool
203 , pkgHashProfExe
:: Bool
204 , pkgHashProfLibDetail
:: ProfDetailLevel
205 , pkgHashProfExeDetail
:: ProfDetailLevel
206 , pkgHashCoverage
:: Bool
207 , pkgHashOptimization
:: OptimisationLevel
208 , pkgHashSplitObjs
:: Bool
209 , pkgHashSplitSections
:: Bool
210 , pkgHashStripLibs
:: Bool
211 , pkgHashStripExes
:: Bool
212 , pkgHashDebugInfo
:: DebugInfoLevel
213 , pkgHashProgramArgs
:: Map
String [String]
214 , pkgHashExtraLibDirs
:: [FilePath]
215 , pkgHashExtraLibDirsStatic
:: [FilePath]
216 , pkgHashExtraFrameworkDirs
:: [FilePath]
217 , pkgHashExtraIncludeDirs
:: [FilePath]
218 , pkgHashProgPrefix
:: Maybe PathTemplate
219 , pkgHashProgSuffix
:: Maybe PathTemplate
220 , pkgHashPackageDbs
:: [Maybe PackageDB
]
222 pkgHashDocumentation
:: Bool
223 , pkgHashHaddockHoogle
:: Bool
224 , pkgHashHaddockHtml
:: Bool
225 , pkgHashHaddockHtmlLocation
:: Maybe String
226 , pkgHashHaddockForeignLibs
:: Bool
227 , pkgHashHaddockExecutables
:: Bool
228 , pkgHashHaddockTestSuites
:: Bool
229 , pkgHashHaddockBenchmarks
:: Bool
230 , pkgHashHaddockInternal
:: Bool
231 , pkgHashHaddockCss
:: Maybe FilePath
232 , pkgHashHaddockLinkedSource
:: Bool
233 , pkgHashHaddockQuickJump
:: Bool
234 , pkgHashHaddockContents
:: Maybe PathTemplate
235 , pkgHashHaddockIndex
:: Maybe PathTemplate
236 , pkgHashHaddockBaseUrl
:: Maybe String
237 , pkgHashHaddockLib
:: Maybe String
238 , pkgHashHaddockOutputDir
:: Maybe FilePath
239 -- TODO: [required eventually] pkgHashToolsVersions ?
240 -- TODO: [required eventually] pkgHashToolsExtraOptions ?
244 -- | Calculate the overall hash to be used for an 'InstalledPackageId'.
245 hashPackageHashInputs
:: PackageHashInputs
-> HashValue
246 hashPackageHashInputs
= hashValue
. renderPackageHashInputs
248 -- | Render a textual representation of the 'PackageHashInputs'.
250 -- The 'hashValue' of this text is the overall package hash.
251 renderPackageHashInputs
:: PackageHashInputs
-> LBS
.ByteString
252 renderPackageHashInputs
258 , pkgHashPkgConfigDeps
259 , pkgHashOtherConfig
=
260 PackageHashConfigInputs
{..}
262 -- The purpose of this somewhat laboured rendering (e.g. why not just
263 -- use show?) is so that existing package hashes do not change
264 -- unnecessarily when new configuration inputs are added into the hash.
266 -- In particular, the assumption is that when a new configuration input
267 -- is included into the hash, that existing packages will typically get
268 -- the default value for that feature. So if we avoid adding entries with
269 -- the default value then most of the time adding new features will not
270 -- change the hashes of existing packages and so fewer packages will need
273 -- TODO: [nice to have] ultimately we probably want to put this config info
274 -- into the ghc-pkg db. At that point this should probably be changed to
275 -- use the config file infrastructure so it can be read back in again.
279 [ entry
"pkgid" prettyShow pkgHashPkgId
280 , mentry
"component" show pkgHashComponent
281 , entry
"src" showHashValue pkgHashSourceHash
290 Just v
-> " " ++ prettyShow v
302 , -- and then all the config
303 entry
"compilerid" prettyShow pkgHashCompilerId
304 , entry
"platform" prettyShow pkgHashPlatform
305 , opt
"flags" mempty showFlagAssignment pkgHashFlagAssignment
306 , opt
"configure-script" [] unwords pkgHashConfigureScriptArgs
307 , opt
"vanilla-lib" True prettyShow pkgHashVanillaLib
308 , opt
"shared-lib" False prettyShow pkgHashSharedLib
309 , opt
"dynamic-exe" False prettyShow pkgHashDynExe
310 , opt
"fully-static-exe" False prettyShow pkgHashFullyStaticExe
311 , opt
"ghci-lib" False prettyShow pkgHashGHCiLib
312 , opt
"prof-lib" False prettyShow pkgHashProfLib
313 , opt
"prof-exe" False prettyShow pkgHashProfExe
314 , opt
"prof-lib-detail" ProfDetailDefault showProfDetailLevel pkgHashProfLibDetail
315 , opt
"prof-exe-detail" ProfDetailDefault showProfDetailLevel pkgHashProfExeDetail
316 , opt
"hpc" False prettyShow pkgHashCoverage
317 , opt
"optimisation" NormalOptimisation
(show . fromEnum) pkgHashOptimization
318 , opt
"split-objs" False prettyShow pkgHashSplitObjs
319 , opt
"split-sections" False prettyShow pkgHashSplitSections
320 , opt
"stripped-lib" False prettyShow pkgHashStripLibs
321 , opt
"stripped-exe" True prettyShow pkgHashStripExes
322 , opt
"debug-info" NormalDebugInfo
(show . fromEnum) pkgHashDebugInfo
323 , opt
"extra-lib-dirs" [] unwords pkgHashExtraLibDirs
324 , opt
"extra-lib-dirs-static" [] unwords pkgHashExtraLibDirsStatic
325 , opt
"extra-framework-dirs" [] unwords pkgHashExtraFrameworkDirs
326 , opt
"extra-include-dirs" [] unwords pkgHashExtraIncludeDirs
327 , opt
"prog-prefix" Nothing
(maybe "" fromPathTemplate
) pkgHashProgPrefix
328 , opt
"prog-suffix" Nothing
(maybe "" fromPathTemplate
) pkgHashProgSuffix
329 , opt
"package-dbs" [] (unwords . map show) pkgHashPackageDbs
330 , opt
"documentation" False prettyShow pkgHashDocumentation
331 , opt
"haddock-hoogle" False prettyShow pkgHashHaddockHoogle
332 , opt
"haddock-html" False prettyShow pkgHashHaddockHtml
333 , opt
"haddock-html-location" Nothing
(fromMaybe "") pkgHashHaddockHtmlLocation
334 , opt
"haddock-foreign-libraries" False prettyShow pkgHashHaddockForeignLibs
335 , opt
"haddock-executables" False prettyShow pkgHashHaddockExecutables
336 , opt
"haddock-tests" False prettyShow pkgHashHaddockTestSuites
337 , opt
"haddock-benchmarks" False prettyShow pkgHashHaddockBenchmarks
338 , opt
"haddock-internal" False prettyShow pkgHashHaddockInternal
339 , opt
"haddock-css" Nothing
(fromMaybe "") pkgHashHaddockCss
340 , opt
"haddock-hyperlink-source" False prettyShow pkgHashHaddockLinkedSource
341 , opt
"haddock-quickjump" False prettyShow pkgHashHaddockQuickJump
342 , opt
"haddock-contents-location" Nothing
(maybe "" fromPathTemplate
) pkgHashHaddockContents
343 , opt
"haddock-index-location" Nothing
(maybe "" fromPathTemplate
) pkgHashHaddockIndex
344 , opt
"haddock-base-url" Nothing
(fromMaybe "") pkgHashHaddockBaseUrl
345 , opt
"haddock-lib" Nothing
(fromMaybe "") pkgHashHaddockLib
346 , opt
"haddock-output-dir" Nothing
(fromMaybe "") pkgHashHaddockOutputDir
348 ++ Map
.foldrWithKey
(\prog args acc
-> opt
(prog
++ "-options") [] unwords args
: acc
) [] pkgHashProgramArgs
350 entry key format
value = Just
(key
++ ": " ++ format
value)
351 mentry key format
value = fmap (\v -> key
++ ": " ++ format v
) value
352 opt key def format
value
353 |
value == def
= Nothing
354 |
otherwise = entry key format
value