Merge pull request #10599 from cabalism/typo/depency
[cabal.git] / Cabal / src / Distribution / Simple / Register.hs
blob76e7528a6c20c6416784ce05b9c6dccefc2025ae
1 {-# LANGUAGE DataKinds #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE RankNTypes #-}
5 -----------------------------------------------------------------------------
7 -- |
8 -- Module : Distribution.Simple.Register
9 -- Copyright : Isaac Jones 2003-2004
10 -- License : BSD3
12 -- Maintainer : cabal-devel@haskell.org
13 -- Portability : portable
15 -- This module deals with registering and unregistering packages. There are a
16 -- couple ways it can do this, one is to do it directly. Another is to generate
17 -- a script that can be run later to do it. The idea here being that the user
18 -- is shielded from the details of what command to use for package registration
19 -- for a particular compiler. In practice this aspect was not especially
20 -- popular so we also provide a way to simply generate the package registration
21 -- file which then must be manually passed to @ghc-pkg@. It is possible to
22 -- generate registration information for where the package is to be installed,
23 -- or alternatively to register the package in place in the build tree. The
24 -- latter is occasionally handy, and will become more important when we try to
25 -- build multi-package systems.
27 -- This module does not delegate anything to the per-compiler modules but just
28 -- mixes it all in this module, which is rather unsatisfactory. The script
29 -- generation and the unregister feature are not well used or tested.
30 module Distribution.Simple.Register
31 ( register
32 , unregister
33 , internalPackageDBPath
34 , initPackageDB
35 , doesPackageDBExist
36 , createPackageDB
37 , deletePackageDB
38 , abiHash
39 , invokeHcPkg
40 , registerPackage
41 , HcPkg.RegisterOptions (..)
42 , HcPkg.defaultRegisterOptions
43 , generateRegistrationInfo
44 , inplaceInstalledPackageInfo
45 , absoluteInstalledPackageInfo
46 , generalInstalledPackageInfo
47 ) where
49 import Distribution.Compat.Prelude
50 import Prelude ()
52 import Distribution.Types.ComponentLocalBuildInfo
53 import Distribution.Types.LocalBuildInfo
54 import Distribution.Types.TargetInfo
56 import Distribution.Simple.BuildPaths
57 import Distribution.Simple.BuildTarget
58 import Distribution.Simple.LocalBuildInfo
60 import qualified Distribution.Simple.GHC as GHC
61 import qualified Distribution.Simple.GHCJS as GHCJS
62 import qualified Distribution.Simple.HaskellSuite as HaskellSuite
63 import qualified Distribution.Simple.PackageIndex as Index
64 import qualified Distribution.Simple.UHC as UHC
66 import Distribution.Backpack.DescribeUnitId
67 import Distribution.Compat.Graph (IsNode (nodeKey))
68 import Distribution.InstalledPackageInfo (InstalledPackageInfo)
69 import qualified Distribution.InstalledPackageInfo as IPI
70 import Distribution.License (licenseFromSPDX, licenseToSPDX)
71 import Distribution.Package
72 import Distribution.PackageDescription
73 import Distribution.Pretty
74 import Distribution.Simple.Compiler
75 import Distribution.Simple.Errors
76 import Distribution.Simple.Flag
77 import Distribution.Simple.Program
78 import qualified Distribution.Simple.Program.HcPkg as HcPkg
79 import Distribution.Simple.Program.Script
80 import Distribution.Simple.Setup.Common
81 import Distribution.Simple.Setup.Register
82 import Distribution.Simple.Utils
83 import Distribution.System
84 import Distribution.Utils.MapAccum
85 import Distribution.Utils.Path
86 import Distribution.Verbosity as Verbosity
87 import Distribution.Version
88 import System.Directory
89 import System.FilePath (isAbsolute)
91 import qualified Data.ByteString.Lazy.Char8 as BS.Char8
93 -- -----------------------------------------------------------------------------
94 -- Registration
96 register
97 :: PackageDescription
98 -> LocalBuildInfo
99 -> RegisterFlags
100 -- ^ Install in the user's database?; verbose
101 -> IO ()
102 register pkg_descr lbi0 flags = do
103 -- Duncan originally asked for us to not register/install files
104 -- when there was no public library. But with per-component
105 -- configure, we legitimately need to install internal libraries
106 -- so that we can get them. So just unconditionally install.
107 let verbosity = fromFlag $ registerVerbosity flags
108 targets <- readTargetInfos verbosity pkg_descr lbi0 $ registerTargets flags
110 -- It's important to register in build order, because ghc-pkg
111 -- will complain if a dependency is not registered.
112 let componentsToRegister =
113 neededTargetsInBuildOrder' pkg_descr lbi0 (map nodeKey targets)
115 (_, ipi_mbs) <-
116 mapAccumM `flip` installedPkgs lbi0 `flip` componentsToRegister $ \index tgt ->
117 case targetComponent tgt of
118 CLib lib -> do
119 let clbi = targetCLBI tgt
120 lbi = lbi0{installedPkgs = index}
121 ipi <- generateOne pkg_descr lib lbi clbi flags
122 return (Index.insert ipi index, Just ipi)
123 _ -> return (index, Nothing)
125 registerAll pkg_descr lbi0 flags (catMaybes ipi_mbs)
127 generateOne
128 :: PackageDescription
129 -> Library
130 -> LocalBuildInfo
131 -> ComponentLocalBuildInfo
132 -> RegisterFlags
133 -> IO InstalledPackageInfo
134 generateOne pkg lib lbi clbi regFlags =
136 absPackageDBs <- absolutePackageDBPaths mbWorkDir packageDbs
137 installedPkgInfo <-
138 generateRegistrationInfo
139 verbosity
143 clbi
144 inplace
145 reloc
146 distPref
147 (registrationPackageDB absPackageDBs)
148 info verbosity (IPI.showInstalledPackageInfo installedPkgInfo)
149 return installedPkgInfo
150 where
151 common = registerCommonFlags regFlags
152 inplace = fromFlag (regInPlace regFlags)
153 reloc = relocatable lbi
154 -- FIXME: there's really no guarantee this will work.
155 -- registering into a totally different db stack can
156 -- fail if dependencies cannot be satisfied.
157 packageDbs =
158 nub $
159 withPackageDB lbi
160 ++ maybeToList (flagToMaybe (regPackageDB regFlags))
161 distPref = fromFlag $ setupDistPref common
162 verbosity = fromFlag $ setupVerbosity common
163 mbWorkDir = flagToMaybe $ setupWorkingDir common
165 registerAll
166 :: PackageDescription
167 -> LocalBuildInfo
168 -> RegisterFlags
169 -> [InstalledPackageInfo]
170 -> IO ()
171 registerAll pkg lbi regFlags ipis =
173 when (fromFlag (regPrintId regFlags)) $ do
174 for_ ipis $ \installedPkgInfo ->
175 -- Only print the public library's IPI
176 when
177 ( packageId installedPkgInfo == packageId pkg
178 && IPI.sourceLibName installedPkgInfo == LMainLibName
180 $ putStrLn (prettyShow (IPI.installedUnitId installedPkgInfo))
182 -- Three different modes:
183 case () of
185 | modeGenerateRegFile -> writeRegistrationFileOrDirectory
186 | modeGenerateRegScript -> writeRegisterScript
187 | otherwise -> do
188 for_ ipis $ \ipi -> do
189 setupMessage'
190 verbosity
191 "Registering"
192 (packageId pkg)
193 (CLibName (IPI.sourceLibName ipi))
194 (Just (IPI.instantiatedWith ipi))
195 registerPackage
196 verbosity
197 (compiler lbi)
198 (withPrograms lbi)
199 (mbWorkDirLBI lbi)
200 packageDbs
202 HcPkg.defaultRegisterOptions
203 where
204 modeGenerateRegFile = isJust (flagToMaybe (regGenPkgConf regFlags))
205 regFile =
206 interpretSymbolicPathLBI lbi $
207 fromMaybe
208 (makeSymbolicPath (prettyShow (packageId pkg) <.> "conf"))
209 (fromFlag (regGenPkgConf regFlags))
211 modeGenerateRegScript = fromFlag (regGenScript regFlags)
213 -- FIXME: there's really no guarantee this will work.
214 -- registering into a totally different db stack can
215 -- fail if dependencies cannot be satisfied.
216 packageDbs =
217 nub $
218 withPackageDB lbi
219 ++ maybeToList (flagToMaybe (regPackageDB regFlags))
220 common = registerCommonFlags regFlags
221 verbosity = fromFlag (setupVerbosity common)
222 mbWorkDir = mbWorkDirLBI lbi
224 writeRegistrationFileOrDirectory = do
225 -- Handles overwriting both directory and file
226 deletePackageDB regFile
227 case ipis of
228 [installedPkgInfo] -> do
229 info verbosity ("Creating package registration file: " ++ regFile)
230 writeUTF8File regFile (IPI.showInstalledPackageInfo installedPkgInfo)
231 _ -> do
232 info verbosity ("Creating package registration directory: " ++ regFile)
233 createDirectory regFile
234 let num_ipis = length ipis
235 lpad m xs = replicate (m - length ys) '0' ++ ys
236 where
237 ys = take m xs
238 number i = lpad (length (show num_ipis)) (show i)
239 for_ (zip ([1 ..] :: [Int]) ipis) $ \(i, installedPkgInfo) ->
240 writeUTF8File
241 (regFile </> (number i ++ "-" ++ prettyShow (IPI.installedUnitId installedPkgInfo)))
242 (IPI.showInstalledPackageInfo installedPkgInfo)
244 writeRegisterScript =
245 case compilerFlavor (compiler lbi) of
246 UHC -> notice verbosity "Registration scripts not needed for uhc"
247 _ ->
248 withHcPkg
249 verbosity
250 "Registration scripts are not implemented for this compiler"
251 (compiler lbi)
252 (withPrograms lbi)
253 (writeHcPkgRegisterScript verbosity mbWorkDir ipis packageDbs)
255 generateRegistrationInfo
256 :: Verbosity
257 -> PackageDescription
258 -> Library
259 -> LocalBuildInfo
260 -> ComponentLocalBuildInfo
261 -> Bool
262 -> Bool
263 -> SymbolicPath Pkg (Dir Dist)
264 -> PackageDB
265 -> IO InstalledPackageInfo
266 generateRegistrationInfo verbosity pkg lib lbi clbi inplace reloc distPref packageDb = do
267 inplaceDir <- absoluteWorkingDirLBI lbi
268 installedPkgInfo <-
269 if inplace
270 then -- NB: With an inplace installation, the user may run './Setup
271 -- build' to update the library files, without reregistering.
272 -- In this case, it is critical that the ABI hash not flip.
274 return
275 ( inplaceInstalledPackageInfo
276 inplaceDir
277 distPref
279 (mkAbiHash "inplace")
282 clbi
284 else do
285 abi_hash <- abiHash verbosity pkg distPref lbi lib clbi
286 if reloc
287 then
288 relocRegistrationInfo
289 verbosity
293 clbi
294 abi_hash
295 packageDb
296 else
297 return
298 ( absoluteInstalledPackageInfo
300 abi_hash
303 clbi
306 return installedPkgInfo
308 -- | Compute the 'AbiHash' of a library that we built inplace.
309 abiHash
310 :: Verbosity
311 -> PackageDescription
312 -> SymbolicPath Pkg (Dir Dist)
313 -> LocalBuildInfo
314 -> Library
315 -> ComponentLocalBuildInfo
316 -> IO AbiHash
317 abiHash verbosity pkg distPref lbi lib clbi =
318 case compilerFlavor comp of
319 GHC -> do
320 fmap mkAbiHash $ GHC.libAbiHash verbosity pkg lbi' lib clbi
321 GHCJS -> do
322 fmap mkAbiHash $ GHCJS.libAbiHash verbosity pkg lbi' lib clbi
323 _ -> return (mkAbiHash "")
324 where
325 comp = compiler lbi
326 lbi' =
328 { withPackageDB =
329 withPackageDB lbi
330 ++ [SpecificPackageDB (internalPackageDBPath lbi distPref)]
333 relocRegistrationInfo
334 :: Verbosity
335 -> PackageDescription
336 -> Library
337 -> LocalBuildInfo
338 -> ComponentLocalBuildInfo
339 -> AbiHash
340 -> PackageDB
341 -> IO InstalledPackageInfo
342 relocRegistrationInfo verbosity pkg lib lbi clbi abi_hash packageDb =
343 case (compilerFlavor (compiler lbi)) of
344 GHC -> do
345 fs <- GHC.pkgRoot verbosity lbi packageDb
346 return
347 ( relocatableInstalledPackageInfo
349 abi_hash
352 clbi
355 _ -> dieWithException verbosity RelocRegistrationInfo
357 initPackageDB :: Verbosity -> Compiler -> ProgramDb -> FilePath -> IO ()
358 initPackageDB verbosity comp progdb dbPath =
359 createPackageDB verbosity comp progdb False dbPath
361 -- | Create an empty package DB at the specified location.
362 createPackageDB
363 :: Verbosity
364 -> Compiler
365 -> ProgramDb
366 -> Bool
367 -> FilePath
368 -> IO ()
369 createPackageDB verbosity comp progdb preferCompat dbPath =
370 case compilerFlavor comp of
371 GHC -> HcPkg.init (GHC.hcPkgInfo progdb) verbosity preferCompat dbPath
372 GHCJS -> HcPkg.init (GHCJS.hcPkgInfo progdb) verbosity False dbPath
373 UHC -> return ()
374 HaskellSuite _ -> HaskellSuite.initPackageDB verbosity progdb dbPath
375 _ -> dieWithException verbosity CreatePackageDB
377 doesPackageDBExist :: FilePath -> IO Bool
378 doesPackageDBExist dbPath = do
379 -- currently one impl for all compiler flavours, but could change if needed
380 dir_exists <- doesDirectoryExist dbPath
381 if dir_exists
382 then return True
383 else doesFileExist dbPath
385 deletePackageDB :: FilePath -> IO ()
386 deletePackageDB dbPath = do
387 -- currently one impl for all compiler flavours, but could change if needed
388 dir_exists <- doesDirectoryExist dbPath
389 if dir_exists
390 then removeDirectoryRecursive dbPath
391 else do
392 file_exists <- doesFileExist dbPath
393 when file_exists $ removeFile dbPath
395 -- | Run @hc-pkg@ using a given package DB stack, directly forwarding the
396 -- provided command-line arguments to it.
397 invokeHcPkg
398 :: Verbosity
399 -> Compiler
400 -> ProgramDb
401 -> Maybe (SymbolicPath CWD (Dir Pkg))
402 -> PackageDBStack
403 -> [String]
404 -> IO ()
405 invokeHcPkg verbosity comp progdb mbWorkDir dbStack extraArgs =
406 withHcPkg
407 verbosity
408 "invokeHcPkg"
409 comp
410 progdb
411 (\hpi -> HcPkg.invoke hpi verbosity mbWorkDir dbStack extraArgs)
413 withHcPkg
414 :: Verbosity
415 -> String
416 -> Compiler
417 -> ProgramDb
418 -> (HcPkg.HcPkgInfo -> IO a)
419 -> IO a
420 withHcPkg verbosity name comp progdb f =
421 case compilerFlavor comp of
422 GHC -> f (GHC.hcPkgInfo progdb)
423 GHCJS -> f (GHCJS.hcPkgInfo progdb)
424 _ -> dieWithException verbosity $ WithHcPkg name
426 registerPackage
427 :: Verbosity
428 -> Compiler
429 -> ProgramDb
430 -> Maybe (SymbolicPath CWD (Dir from))
431 -> PackageDBStackS from
432 -> InstalledPackageInfo
433 -> HcPkg.RegisterOptions
434 -> IO ()
435 registerPackage verbosity comp progdb mbWorkDir packageDbs installedPkgInfo registerOptions =
436 case compilerFlavor comp of
437 GHC -> GHC.registerPackage verbosity progdb mbWorkDir packageDbs installedPkgInfo registerOptions
438 GHCJS -> GHCJS.registerPackage verbosity progdb mbWorkDir packageDbs installedPkgInfo registerOptions
439 HaskellSuite{} ->
440 HaskellSuite.registerPackage verbosity progdb packageDbs installedPkgInfo
442 | HcPkg.registerMultiInstance registerOptions ->
443 dieWithException verbosity RegisMultiplePkgNotSupported
444 UHC -> UHC.registerPackage verbosity mbWorkDir comp progdb packageDbs installedPkgInfo
445 _ -> dieWithException verbosity RegisteringNotImplemented
447 writeHcPkgRegisterScript
448 :: Verbosity
449 -> Maybe (SymbolicPath CWD (Dir Pkg))
450 -> [InstalledPackageInfo]
451 -> PackageDBStack
452 -> HcPkg.HcPkgInfo
453 -> IO ()
454 writeHcPkgRegisterScript verbosity mbWorkDir ipis packageDbs hpi = do
455 let genScript installedPkgInfo =
456 let invocation =
457 HcPkg.registerInvocation
459 Verbosity.normal
460 mbWorkDir
461 packageDbs
462 installedPkgInfo
463 HcPkg.defaultRegisterOptions
464 in invocationAsSystemScript buildOS invocation
465 scripts = map genScript ipis
466 -- TODO: Do something more robust here
467 regScript = unlines scripts
469 let out_file = interpretSymbolicPath mbWorkDir regScriptFileName
470 info verbosity ("Creating package registration script: " ++ out_file)
471 writeUTF8File out_file regScript
472 setFileExecutable out_file
474 regScriptFileName :: SymbolicPath Pkg File
475 regScriptFileName = case buildOS of
476 Windows -> makeSymbolicPath "register.bat"
477 _ -> makeSymbolicPath "register.sh"
479 -- -----------------------------------------------------------------------------
480 -- Making the InstalledPackageInfo
482 -- | Construct 'InstalledPackageInfo' for a library in a package, given a set
483 -- of installation directories.
484 generalInstalledPackageInfo
485 :: ([FilePath] -> [FilePath])
486 -- ^ Translate relative include dir paths to
487 -- absolute paths.
488 -> PackageDescription
489 -> AbiHash
490 -> Library
491 -> LocalBuildInfo
492 -> ComponentLocalBuildInfo
493 -> InstallDirs FilePath
494 -> InstalledPackageInfo
495 generalInstalledPackageInfo adjustRelIncDirs pkg abi_hash lib lbi clbi installDirs =
496 IPI.InstalledPackageInfo
497 { IPI.sourcePackageId = packageId pkg
498 , IPI.installedUnitId = componentUnitId clbi
499 , IPI.installedComponentId_ = componentComponentId clbi
500 , IPI.instantiatedWith = expectLibraryComponent (maybeComponentInstantiatedWith clbi)
501 , IPI.sourceLibName = libName lib
502 , IPI.compatPackageKey = expectLibraryComponent (maybeComponentCompatPackageKey clbi)
503 , -- If GHC >= 8.4 we register with SDPX, otherwise with legacy license
504 IPI.license =
505 if ghc84
506 then Left $ either id licenseToSPDX $ licenseRaw pkg
507 else Right $ either licenseFromSPDX id $ licenseRaw pkg
508 , IPI.copyright = copyright pkg
509 , IPI.maintainer = maintainer pkg
510 , IPI.author = author pkg
511 , IPI.stability = stability pkg
512 , IPI.homepage = homepage pkg
513 , IPI.pkgUrl = pkgUrl pkg
514 , IPI.synopsis = synopsis pkg
515 , IPI.description = description pkg
516 , IPI.category = category pkg
517 , IPI.abiHash = abi_hash
518 , IPI.indefinite = componentIsIndefinite clbi
519 , IPI.exposed = libExposed lib
520 , IPI.exposedModules =
521 expectLibraryComponent (maybeComponentExposedModules clbi)
522 -- add virtual modules into the list of exposed modules for the
523 -- package database as well.
524 ++ map (\name -> IPI.ExposedModule name Nothing) (virtualModules bi)
525 , IPI.hiddenModules = otherModules bi
526 , IPI.trusted = IPI.trusted IPI.emptyInstalledPackageInfo
527 , IPI.importDirs = [libdir installDirs | hasModules]
528 , IPI.libraryDirs = libdirs
529 , IPI.libraryDirsStatic = libdirsStatic
530 , IPI.libraryDynDirs = dynlibdirs
531 , IPI.dataDir = datadir installDirs
532 , IPI.hsLibraries =
533 ( if hasLibrary
534 then [getHSLibraryName (componentUnitId clbi)]
535 else []
537 ++ extraBundledLibs bi
538 , IPI.extraLibraries = extraLibs bi
539 , IPI.extraLibrariesStatic = extraLibsStatic bi
540 , IPI.extraGHCiLibraries = extraGHCiLibs bi
541 , IPI.includeDirs = absinc ++ adjustRelIncDirs relinc
542 , IPI.includes = map getSymbolicPath $ includes bi
543 , IPI.depends = depends
544 , IPI.abiDepends = [] -- due to #5465
545 , IPI.ccOptions = [] -- Note. NOT ccOptions bi!
546 -- We don't want cc-options to be propagated
547 -- to C compilations in other packages.
548 , IPI.cxxOptions = [] -- Also. NOT cxxOptions bi!
549 , IPI.ldOptions = ldOptions bi
550 , IPI.frameworks = map getSymbolicPath $ frameworks bi
551 , IPI.frameworkDirs = map getSymbolicPath $ extraFrameworkDirs bi
552 , IPI.haddockInterfaces = [haddockdir installDirs </> haddockLibraryPath pkg lib]
553 , IPI.haddockHTMLs = [htmldir installDirs]
554 , IPI.pkgRoot = Nothing
555 , IPI.libVisibility = libVisibility lib
557 where
558 ghc84 = case compilerId $ compiler lbi of
559 CompilerId GHC v -> v >= mkVersion [8, 4]
560 _ -> False
562 bi = libBuildInfo lib
563 -- TODO: unclear what the root cause of the
564 -- duplication is, but we nub it here for now:
565 depends = ordNub $ map fst (componentPackageDeps clbi)
566 (absinc, relinc) = partition isAbsolute (map getSymbolicPath $ includeDirs bi)
567 hasModules = not $ null (allLibModules lib clbi)
568 comp = compiler lbi
569 hasLibrary =
570 ( hasModules
571 || not (null (cSources bi))
572 || not (null (asmSources bi))
573 || not (null (cmmSources bi))
574 || not (null (cxxSources bi))
575 || (not (null (jsSources bi)) && hasJsSupport)
577 && not (componentIsIndefinite clbi)
578 hasJsSupport = case hostPlatform lbi of
579 Platform JavaScript _ -> True
580 _ -> False
581 extraLibDirs' = map getSymbolicPath $ extraLibDirs bi
582 libdirsStatic
583 | hasLibrary = libdir installDirs : extraLibDirsStaticOrFallback
584 | otherwise = extraLibDirsStaticOrFallback
585 where
586 -- If no static library dirs were given, the package likely makes no
587 -- distinction between fully static linking and otherwise.
588 -- Fall back to the normal library dirs in that case.
589 extraLibDirsStaticOrFallback = case extraLibDirsStatic bi of
590 [] -> extraLibDirs'
591 dirs -> map getSymbolicPath dirs
592 (libdirs, dynlibdirs)
593 | not hasLibrary =
594 (extraLibDirs', [])
595 -- the dynamic-library-dirs defaults to the library-dirs if not specified,
596 -- so this works whether the dynamic-library-dirs field is supported or not
598 | libraryDynDirSupported comp =
599 ( libdir installDirs : extraLibDirs'
600 , dynlibdir installDirs : extraLibDirs'
602 | otherwise =
603 (libdir installDirs : dynlibdir installDirs : extraLibDirs', [])
604 expectLibraryComponent (Just attribute) = attribute
605 expectLibraryComponent Nothing = (error "generalInstalledPackageInfo: Expected a library component, got something else.")
607 -- the compiler doesn't understand the dynamic-library-dirs field so we
608 -- add the dyn directory to the "normal" list in the library-dirs field
610 -- | Construct 'InstalledPackageInfo' for a library that is in place in the
611 -- build tree.
613 -- This function knows about the layout of in place packages.
614 inplaceInstalledPackageInfo
615 :: AbsolutePath (Dir Pkg)
616 -> SymbolicPath Pkg (Dir Dist)
617 -- ^ location of the dist tree
618 -> PackageDescription
619 -> AbiHash
620 -> Library
621 -> LocalBuildInfo
622 -> ComponentLocalBuildInfo
623 -> InstalledPackageInfo
624 inplaceInstalledPackageInfo inplaceDir distPref pkg abi_hash lib lbi clbi =
625 generalInstalledPackageInfo
626 adjustRelativeIncludeDirs
628 abi_hash
631 clbi
632 installDirs
633 where
634 i = interpretSymbolicPathAbsolute inplaceDir -- See Note [Symbolic paths] in Distribution.Utils.Path
635 adjustRelativeIncludeDirs = concatMap $ \d ->
636 [ i $ makeRelativePathEx d -- local include-dir
637 , i $ libTargetDir </> makeRelativePathEx d -- autogen include-dir
639 libTargetDir = componentBuildDir lbi clbi
640 installDirs =
641 (absoluteComponentInstallDirs pkg lbi (componentUnitId clbi) NoCopyDest)
642 { libdir = i libTargetDir
643 , dynlibdir = i libTargetDir
644 , datadir =
645 let rawDataDir = dataDir pkg
646 in if null $ getSymbolicPath rawDataDir
647 then i sameDirectory
648 else i rawDataDir
649 , docdir = i inplaceDocdir
650 , htmldir = inplaceHtmldir
651 , haddockdir = inplaceHtmldir
653 inplaceDocdir = distPref </> makeRelativePathEx "doc"
654 inplaceHtmldir = i $ inplaceDocdir </> makeRelativePathEx ("html" </> prettyShow (packageName pkg))
656 -- | Construct 'InstalledPackageInfo' for the final install location of a
657 -- library package.
659 -- This function knows about the layout of installed packages.
660 absoluteInstalledPackageInfo
661 :: PackageDescription
662 -> AbiHash
663 -> Library
664 -> LocalBuildInfo
665 -> ComponentLocalBuildInfo
666 -> InstalledPackageInfo
667 absoluteInstalledPackageInfo pkg abi_hash lib lbi clbi =
668 generalInstalledPackageInfo
669 adjustReativeIncludeDirs
671 abi_hash
674 clbi
675 installDirs
676 where
677 -- For installed packages we install all include files into one dir,
678 -- whereas in the build tree they may live in multiple local dirs.
679 adjustReativeIncludeDirs _
680 | null (installIncludes bi) = []
681 | otherwise = [includedir installDirs]
682 bi = libBuildInfo lib
683 installDirs = absoluteComponentInstallDirs pkg lbi (componentUnitId clbi) NoCopyDest
685 relocatableInstalledPackageInfo
686 :: PackageDescription
687 -> AbiHash
688 -> Library
689 -> LocalBuildInfo
690 -> ComponentLocalBuildInfo
691 -> SymbolicPath CWD ('Dir Pkg)
692 -> InstalledPackageInfo
693 relocatableInstalledPackageInfo pkg abi_hash lib lbi clbi pkgroot =
694 generalInstalledPackageInfo
695 adjustReativeIncludeDirs
697 abi_hash
700 clbi
701 installDirs
702 where
703 -- For installed packages we install all include files into one dir,
704 -- whereas in the build tree they may live in multiple local dirs.
705 adjustReativeIncludeDirs _
706 | null (installIncludes bi) = []
707 | otherwise = [includedir installDirs]
708 bi = libBuildInfo lib
710 installDirs =
711 fmap (("${pkgroot}" </>) . shortRelativePath (getSymbolicPath pkgroot)) $
712 absoluteComponentInstallDirs pkg lbi (componentUnitId clbi) NoCopyDest
714 -- -----------------------------------------------------------------------------
715 -- Unregistration
717 unregister :: PackageDescription -> LocalBuildInfo -> RegisterFlags -> IO ()
718 unregister pkg lbi regFlags = do
719 let pkgid = packageId pkg
720 common = registerCommonFlags regFlags
721 genScript = fromFlag (regGenScript regFlags)
722 verbosity = fromFlag (setupVerbosity common)
723 packageDb =
724 fromFlagOrDefault
725 (registrationPackageDB (withPackageDB lbi))
726 (regPackageDB regFlags)
727 mbWorkDir = mbWorkDirLBI lbi
728 unreg hpi =
729 let invocation =
730 HcPkg.unregisterInvocation
732 Verbosity.normal
733 mbWorkDir
734 packageDb
735 pkgid
736 in if genScript
737 then
738 writeFileAtomic
739 unregScriptFileName
740 (BS.Char8.pack $ invocationAsSystemScript buildOS invocation)
741 else runProgramInvocation verbosity invocation
742 setupMessage verbosity "Unregistering" pkgid
743 withHcPkg
744 verbosity
745 "unregistering is only implemented for GHC and GHCJS"
746 (compiler lbi)
747 (withPrograms lbi)
748 unreg
750 unregScriptFileName :: FilePath
751 unregScriptFileName = case buildOS of
752 Windows -> "unregister.bat"
753 _ -> "unregister.sh"
755 internalPackageDBPath :: LocalBuildInfo -> SymbolicPath Pkg (Dir Dist) -> SymbolicPath Pkg (Dir PkgDB)
756 internalPackageDBPath lbi distPref =
757 case compilerFlavor (compiler lbi) of
758 UHC -> UHC.inplacePackageDbPath lbi
759 _ -> distPref </> makeRelativePathEx "package.conf.inplace"