1 {-# LANGUAGE FlexibleContexts #-}
2 {-# LANGUAGE RankNTypes #-}
4 -----------------------------------------------------------------------------
6 -- Module : Distribution.Simple.Register
7 -- Copyright : Isaac Jones 2003-2004
10 -- Maintainer : cabal-devel@haskell.org
11 -- Portability : portable
13 -- This module deals with registering and unregistering packages. There are a
14 -- couple ways it can do this, one is to do it directly. Another is to generate
15 -- a script that can be run later to do it. The idea here being that the user
16 -- is shielded from the details of what command to use for package registration
17 -- for a particular compiler. In practice this aspect was not especially
18 -- popular so we also provide a way to simply generate the package registration
19 -- file which then must be manually passed to @ghc-pkg@. It is possible to
20 -- generate registration information for where the package is to be installed,
21 -- or alternatively to register the package in place in the build tree. The
22 -- latter is occasionally handy, and will become more important when we try to
23 -- build multi-package systems.
25 -- This module does not delegate anything to the per-compiler modules but just
26 -- mixes it all in in this module, which is rather unsatisfactory. The script
27 -- generation and the unregister feature are not well used or tested.
29 module Distribution
.Simple
.Register
(
33 internalPackageDBPath
,
43 HcPkg
.RegisterOptions
(..),
44 HcPkg
.defaultRegisterOptions
,
45 generateRegistrationInfo
,
46 inplaceInstalledPackageInfo
,
47 absoluteInstalledPackageInfo
,
48 generalInstalledPackageInfo
,
52 import Distribution
.Compat
.Prelude
54 import Distribution
.Types
.TargetInfo
55 import Distribution
.Types
.LocalBuildInfo
56 import Distribution
.Types
.ComponentLocalBuildInfo
58 import Distribution
.Simple
.LocalBuildInfo
59 import Distribution
.Simple
.BuildPaths
60 import Distribution
.Simple
.BuildTarget
62 import qualified Distribution
.Simple
.GHC
as GHC
63 import qualified Distribution
.Simple
.GHCJS
as GHCJS
64 import qualified Distribution
.Simple
.UHC
as UHC
65 import qualified Distribution
.Simple
.HaskellSuite
as HaskellSuite
66 import qualified Distribution
.Simple
.PackageIndex
as Index
68 import Distribution
.Backpack
.DescribeUnitId
69 import Distribution
.Simple
.Compiler
70 import Distribution
.Simple
.Program
71 import Distribution
.Simple
.Program
.Script
72 import qualified Distribution
.Simple
.Program
.HcPkg
as HcPkg
73 import Distribution
.Simple
.Setup
74 import Distribution
.PackageDescription
75 import Distribution
.Package
76 import Distribution
.License
(licenseToSPDX
, licenseFromSPDX
)
77 import qualified Distribution
.InstalledPackageInfo
as IPI
78 import Distribution
.InstalledPackageInfo
(InstalledPackageInfo
)
79 import Distribution
.Simple
.Utils
80 import Distribution
.Utils
.MapAccum
81 import Distribution
.System
82 import Distribution
.Text
83 import Distribution
.Types
.ComponentName
84 import Distribution
.Verbosity
as Verbosity
85 import Distribution
.Version
86 import Distribution
.Compat
.Graph
(IsNode
(nodeKey
))
88 import System
.FilePath ((</>), (<.>), isAbsolute
)
89 import System
.Directory
91 import Data
.List
(partition)
92 import qualified Data
.ByteString
.Lazy
.Char8
as BS
.Char8
94 -- -----------------------------------------------------------------------------
97 register
:: PackageDescription
-> LocalBuildInfo
98 -> RegisterFlags
-- ^Install in the user's database?; verbose
100 register pkg_descr lbi0 flags
=
101 -- Duncan originally asked for us to not register/install files
102 -- when there was no public library. But with per-component
103 -- configure, we legitimately need to install internal libraries
104 -- so that we can get them. So just unconditionally install.
108 targets
<- readTargetInfos verbosity pkg_descr lbi0
(regArgs 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
)
116 mapAccumM `
flip` installedPkgs lbi0 `
flip` componentsToRegister
$ \index tgt
->
117 case targetComponent tgt
of
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 verbosity
= fromFlag
(regVerbosity flags
)
129 generateOne
:: PackageDescription
-> Library
-> LocalBuildInfo
-> ComponentLocalBuildInfo
131 -> IO InstalledPackageInfo
132 generateOne pkg lib lbi clbi regFlags
134 absPackageDBs
<- absolutePackageDBPaths packageDbs
135 installedPkgInfo
<- generateRegistrationInfo
136 verbosity pkg lib lbi clbi inplace reloc distPref
137 (registrationPackageDB absPackageDBs
)
138 info verbosity
(IPI
.showInstalledPackageInfo installedPkgInfo
)
139 return installedPkgInfo
141 inplace
= fromFlag
(regInPlace regFlags
)
142 reloc
= relocatable lbi
143 -- FIXME: there's really no guarantee this will work.
144 -- registering into a totally different db stack can
145 -- fail if dependencies cannot be satisfied.
146 packageDbs
= nub $ withPackageDB lbi
147 ++ maybeToList (flagToMaybe
(regPackageDB regFlags
))
148 distPref
= fromFlag
(regDistPref regFlags
)
149 verbosity
= fromFlag
(regVerbosity regFlags
)
151 registerAll
:: PackageDescription
-> LocalBuildInfo
-> RegisterFlags
152 -> [InstalledPackageInfo
]
154 registerAll pkg lbi regFlags ipis
156 when (fromFlag
(regPrintId regFlags
)) $ do
157 for_ ipis
$ \installedPkgInfo
->
158 -- Only print the public library's IPI
159 when (packageId installedPkgInfo
== packageId pkg
160 && IPI
.sourceLibName installedPkgInfo
== Nothing
) $
161 putStrLn (display
(IPI
.installedUnitId installedPkgInfo
))
163 -- Three different modes:
165 _ | modeGenerateRegFile
-> writeRegistrationFileOrDirectory
166 | modeGenerateRegScript
-> writeRegisterScript
168 for_ ipis
$ \ipi
-> do
169 setupMessage
' verbosity
"Registering" (packageId pkg
)
170 (libraryComponentName
(IPI
.sourceLibName ipi
))
171 (Just
(IPI
.instantiatedWith ipi
))
172 registerPackage verbosity
(compiler lbi
) (withPrograms lbi
)
173 packageDbs ipi HcPkg
.defaultRegisterOptions
176 modeGenerateRegFile
= isJust (flagToMaybe
(regGenPkgConf regFlags
))
177 regFile
= fromMaybe (display
(packageId pkg
) <.> "conf")
178 (fromFlag
(regGenPkgConf regFlags
))
180 modeGenerateRegScript
= fromFlag
(regGenScript regFlags
)
182 -- FIXME: there's really no guarantee this will work.
183 -- registering into a totally different db stack can
184 -- fail if dependencies cannot be satisfied.
185 packageDbs
= nub $ withPackageDB lbi
186 ++ maybeToList (flagToMaybe
(regPackageDB regFlags
))
187 verbosity
= fromFlag
(regVerbosity regFlags
)
189 writeRegistrationFileOrDirectory
= do
190 -- Handles overwriting both directory and file
191 deletePackageDB regFile
193 [installedPkgInfo
] -> do
194 info verbosity
("Creating package registration file: " ++ regFile
)
195 writeUTF8File regFile
(IPI
.showInstalledPackageInfo installedPkgInfo
)
197 info verbosity
("Creating package registration directory: " ++ regFile
)
198 createDirectory regFile
199 let num_ipis
= length ipis
200 lpad m xs
= replicate (m
- length ys
) '0' ++ ys
202 number i
= lpad
(length (show num_ipis
)) (show i
)
203 for_
(zip ([1..] :: [Int]) ipis
) $ \(i
, installedPkgInfo
) ->
204 writeUTF8File
(regFile
</> (number i
++ "-" ++ display
(IPI
.installedUnitId installedPkgInfo
)))
205 (IPI
.showInstalledPackageInfo installedPkgInfo
)
207 writeRegisterScript
=
208 case compilerFlavor
(compiler lbi
) of
209 UHC
-> notice verbosity
"Registration scripts not needed for uhc"
210 _
-> withHcPkg verbosity
211 "Registration scripts are not implemented for this compiler"
212 (compiler lbi
) (withPrograms lbi
)
213 (writeHcPkgRegisterScript verbosity ipis packageDbs
)
216 generateRegistrationInfo
:: Verbosity
217 -> PackageDescription
220 -> ComponentLocalBuildInfo
225 -> IO InstalledPackageInfo
226 generateRegistrationInfo verbosity pkg lib lbi clbi inplace reloc distPref packageDb
= do
227 --TODO: eliminate pwd!
228 pwd
<- getCurrentDirectory
232 -- NB: With an inplace installation, the user may run './Setup
233 -- build' to update the library files, without reregistering.
234 -- In this case, it is critical that the ABI hash not flip.
235 then return (inplaceInstalledPackageInfo pwd distPref
236 pkg
(mkAbiHash
"inplace") lib lbi clbi
)
238 abi_hash
<- abiHash verbosity pkg distPref lbi lib clbi
240 then relocRegistrationInfo verbosity
241 pkg lib lbi clbi abi_hash packageDb
242 else return (absoluteInstalledPackageInfo
243 pkg abi_hash lib lbi clbi
)
246 return installedPkgInfo
248 -- | Compute the 'AbiHash' of a library that we built inplace.
250 -> PackageDescription
254 -> ComponentLocalBuildInfo
256 abiHash verbosity pkg distPref lbi lib clbi
=
257 case compilerFlavor comp
of
259 fmap mkAbiHash
$ GHC
.libAbiHash verbosity pkg lbi
' lib clbi
261 fmap mkAbiHash
$ GHCJS
.libAbiHash verbosity pkg lbi
' lib clbi
262 _
-> return (mkAbiHash
"")
266 withPackageDB
= withPackageDB lbi
267 ++ [SpecificPackageDB
(internalPackageDBPath lbi distPref
)]
270 relocRegistrationInfo
:: Verbosity
271 -> PackageDescription
274 -> ComponentLocalBuildInfo
277 -> IO InstalledPackageInfo
278 relocRegistrationInfo verbosity pkg lib lbi clbi abi_hash packageDb
=
279 case (compilerFlavor
(compiler lbi
)) of
280 GHC
-> do fs
<- GHC
.pkgRoot verbosity lbi packageDb
281 return (relocatableInstalledPackageInfo
282 pkg abi_hash lib lbi clbi fs
)
284 "Distribution.Simple.Register.relocRegistrationInfo: \
285 \not implemented for this compiler"
287 initPackageDB
:: Verbosity
-> Compiler
-> ProgramDb
-> FilePath -> IO ()
288 initPackageDB verbosity comp progdb dbPath
=
289 createPackageDB verbosity comp progdb
False dbPath
291 -- | Create an empty package DB at the specified location.
292 createPackageDB
:: Verbosity
-> Compiler
-> ProgramDb
-> Bool
294 createPackageDB verbosity comp progdb preferCompat dbPath
=
295 case compilerFlavor comp
of
296 GHC
-> HcPkg
.init (GHC
.hcPkgInfo progdb
) verbosity preferCompat dbPath
297 GHCJS
-> HcPkg
.init (GHCJS
.hcPkgInfo progdb
) verbosity
False dbPath
299 HaskellSuite _
-> HaskellSuite
.initPackageDB verbosity progdb dbPath
300 _
-> die
' verbosity
$
301 "Distribution.Simple.Register.createPackageDB: "
302 ++ "not implemented for this compiler"
304 doesPackageDBExist
:: FilePath -> NoCallStackIO
Bool
305 doesPackageDBExist dbPath
= do
306 -- currently one impl for all compiler flavours, but could change if needed
307 dir_exists
<- doesDirectoryExist dbPath
310 else doesFileExist dbPath
312 deletePackageDB
:: FilePath -> NoCallStackIO
()
313 deletePackageDB dbPath
= do
314 -- currently one impl for all compiler flavours, but could change if needed
315 dir_exists
<- doesDirectoryExist dbPath
317 then removeDirectoryRecursive dbPath
318 else do file_exists
<- doesFileExist dbPath
319 when file_exists
$ removeFile dbPath
321 -- | Run @hc-pkg@ using a given package DB stack, directly forwarding the
322 -- provided command-line arguments to it.
323 invokeHcPkg
:: Verbosity
-> Compiler
-> ProgramDb
-> PackageDBStack
325 invokeHcPkg verbosity comp progdb dbStack extraArgs
=
326 withHcPkg verbosity
"invokeHcPkg" comp progdb
327 (\hpi
-> HcPkg
.invoke hpi verbosity dbStack extraArgs
)
329 withHcPkg
:: Verbosity
-> String -> Compiler
-> ProgramDb
330 -> (HcPkg
.HcPkgInfo
-> IO a
) -> IO a
331 withHcPkg verbosity name comp progdb f
=
332 case compilerFlavor comp
of
333 GHC
-> f
(GHC
.hcPkgInfo progdb
)
334 GHCJS
-> f
(GHCJS
.hcPkgInfo progdb
)
335 _
-> die
' verbosity
("Distribution.Simple.Register." ++ name
++ ":\
336 \not implemented for this compiler")
338 registerPackage
:: Verbosity
342 -> InstalledPackageInfo
343 -> HcPkg
.RegisterOptions
345 registerPackage verbosity comp progdb packageDbs installedPkgInfo registerOptions
=
346 case compilerFlavor comp
of
347 GHC
-> GHC
.registerPackage verbosity progdb packageDbs installedPkgInfo registerOptions
348 GHCJS
-> GHCJS
.registerPackage verbosity progdb packageDbs installedPkgInfo registerOptions
350 HaskellSuite
.registerPackage verbosity progdb packageDbs installedPkgInfo
351 _ | HcPkg
.registerMultiInstance registerOptions
352 -> die
' verbosity
"Registering multiple package instances is not yet supported for this compiler"
353 UHC
-> UHC
.registerPackage verbosity comp progdb packageDbs installedPkgInfo
354 _
-> die
' verbosity
"Registering is not implemented for this compiler"
356 writeHcPkgRegisterScript
:: Verbosity
357 -> [InstalledPackageInfo
]
361 writeHcPkgRegisterScript verbosity ipis packageDbs hpi
= do
362 let genScript installedPkgInfo
=
363 let invocation
= HcPkg
.registerInvocation hpi Verbosity
.normal
364 packageDbs installedPkgInfo
365 HcPkg
.defaultRegisterOptions
366 in invocationAsSystemScript buildOS invocation
367 scripts
= map genScript ipis
368 -- TODO: Do something more robust here
369 regScript
= unlines scripts
371 info verbosity
("Creating package registration script: " ++ regScriptFileName
)
372 writeUTF8File regScriptFileName regScript
373 setFileExecutable regScriptFileName
375 regScriptFileName
:: FilePath
376 regScriptFileName
= case buildOS
of
377 Windows
-> "register.bat"
381 -- -----------------------------------------------------------------------------
382 -- Making the InstalledPackageInfo
384 -- | Construct 'InstalledPackageInfo' for a library in a package, given a set
385 -- of installation directories.
387 generalInstalledPackageInfo
388 :: ([FilePath] -> [FilePath]) -- ^ Translate relative include dir paths to
390 -> PackageDescription
394 -> ComponentLocalBuildInfo
395 -> InstallDirs
FilePath
396 -> InstalledPackageInfo
397 generalInstalledPackageInfo adjustRelIncDirs pkg abi_hash lib lbi clbi installDirs
=
398 IPI
.InstalledPackageInfo
{
399 IPI
.sourcePackageId
= packageId pkg
,
400 IPI
.installedUnitId
= componentUnitId clbi
,
401 IPI
.installedComponentId_
= componentComponentId clbi
,
402 IPI
.instantiatedWith
= componentInstantiatedWith clbi
,
403 IPI
.sourceLibName
= libName lib
,
404 IPI
.compatPackageKey
= componentCompatPackageKey clbi
,
405 -- If GHC >= 8.4 we register with SDPX, otherwise with legacy license
408 then Left
$ either id licenseToSPDX
$ licenseRaw pkg
409 else Right
$ either licenseFromSPDX
id $ licenseRaw pkg
,
410 IPI
.copyright
= copyright pkg
,
411 IPI
.maintainer
= maintainer pkg
,
412 IPI
.author
= author pkg
,
413 IPI
.stability
= stability pkg
,
414 IPI
.homepage
= homepage pkg
,
415 IPI
.pkgUrl
= pkgUrl pkg
,
416 IPI
.synopsis
= synopsis pkg
,
417 IPI
.description
= description pkg
,
418 IPI
.category
= category pkg
,
419 IPI
.abiHash
= abi_hash
,
420 IPI
.indefinite
= componentIsIndefinite clbi
,
421 IPI
.exposed
= libExposed lib
,
422 IPI
.exposedModules
= componentExposedModules clbi
423 -- add virtual modules into the list of exposed modules for the
424 -- package database as well.
425 ++ map (\name
-> IPI
.ExposedModule name Nothing
) (virtualModules bi
),
426 IPI
.hiddenModules
= otherModules bi
,
427 IPI
.trusted
= IPI
.trusted IPI
.emptyInstalledPackageInfo
,
428 IPI
.importDirs
= [ libdir installDirs | hasModules
],
429 IPI
.libraryDirs
= libdirs
,
430 IPI
.libraryDynDirs
= dynlibdirs
,
431 IPI
.dataDir
= datadir installDirs
,
432 IPI
.hsLibraries
= (if hasLibrary
433 then [getHSLibraryName
(componentUnitId clbi
)]
434 else []) ++ extraBundledLibs bi
,
435 IPI
.extraLibraries
= extraLibs bi
,
436 IPI
.extraGHCiLibraries
= extraGHCiLibs bi
,
437 IPI
.includeDirs
= absinc
++ adjustRelIncDirs relinc
,
438 IPI
.includes
= includes bi
,
439 IPI
.depends
= depends
,
440 IPI
.abiDepends
= [], -- due to #5465
441 IPI
.ccOptions
= [], -- Note. NOT ccOptions bi!
442 -- We don't want cc-options to be propagated
443 -- to C compilations in other packages.
444 IPI
.cxxOptions
= [], -- Also. NOT cxxOptions bi!
445 IPI
.ldOptions
= ldOptions bi
,
446 IPI
.frameworks
= frameworks bi
,
447 IPI
.frameworkDirs
= extraFrameworkDirs bi
,
448 IPI
.haddockInterfaces
= [haddockdir installDirs
</> haddockName pkg
],
449 IPI
.haddockHTMLs
= [htmldir installDirs
],
450 IPI
.pkgRoot
= Nothing
453 ghc84
= case compilerId
$ compiler lbi
of
454 CompilerId GHC v
-> v
>= mkVersion
[8, 4]
457 bi
= libBuildInfo lib
458 --TODO: unclear what the root cause of the
459 -- duplication is, but we nub it here for now:
460 depends
= ordNub
$ map fst (componentPackageDeps clbi
)
461 (absinc
, relinc
) = partition isAbsolute
(includeDirs bi
)
462 hasModules
= not $ null (allLibModules lib clbi
)
464 hasLibrary
= (hasModules ||
not (null (cSources bi
))
465 ||
not (null (asmSources bi
))
466 ||
not (null (cmmSources bi
))
467 ||
not (null (cxxSources bi
))
468 ||
(not (null (jsSources bi
)) &&
469 compilerFlavor comp
== GHCJS
))
470 && not (componentIsIndefinite clbi
)
471 (libdirs
, dynlibdirs
)
473 = (extraLibDirs bi
, [])
474 -- the dynamic-library-dirs defaults to the library-dirs if not specified,
475 -- so this works whether the dynamic-library-dirs field is supported or not
477 | libraryDynDirSupported comp
478 = (libdir installDirs
: extraLibDirs bi
,
479 dynlibdir installDirs
: extraLibDirs bi
)
482 = (libdir installDirs
: dynlibdir installDirs
: extraLibDirs bi
, [])
483 -- the compiler doesn't understand the dynamic-library-dirs field so we
484 -- add the dyn directory to the "normal" list in the library-dirs field
486 -- | Construct 'InstalledPackageInfo' for a library that is in place in the
489 -- This function knows about the layout of in place packages.
491 inplaceInstalledPackageInfo
:: FilePath -- ^ top of the build tree
492 -> FilePath -- ^ location of the dist tree
493 -> PackageDescription
497 -> ComponentLocalBuildInfo
498 -> InstalledPackageInfo
499 inplaceInstalledPackageInfo inplaceDir distPref pkg abi_hash lib lbi clbi
=
500 generalInstalledPackageInfo adjustRelativeIncludeDirs
501 pkg abi_hash lib lbi clbi installDirs
503 adjustRelativeIncludeDirs
= map (inplaceDir
</>)
504 libTargetDir
= componentBuildDir lbi clbi
506 (absoluteComponentInstallDirs pkg lbi
(componentUnitId clbi
) NoCopyDest
) {
507 libdir
= inplaceDir
</> libTargetDir
,
508 dynlibdir
= inplaceDir
</> libTargetDir
,
509 datadir
= inplaceDir
</> dataDir pkg
,
510 docdir
= inplaceDocdir
,
511 htmldir
= inplaceHtmldir
,
512 haddockdir
= inplaceHtmldir
514 inplaceDocdir
= inplaceDir
</> distPref
</> "doc"
515 inplaceHtmldir
= inplaceDocdir
</> "html" </> display
(packageName pkg
)
518 -- | Construct 'InstalledPackageInfo' for the final install location of a
521 -- This function knows about the layout of installed packages.
523 absoluteInstalledPackageInfo
:: PackageDescription
527 -> ComponentLocalBuildInfo
528 -> InstalledPackageInfo
529 absoluteInstalledPackageInfo pkg abi_hash lib lbi clbi
=
530 generalInstalledPackageInfo adjustReativeIncludeDirs
531 pkg abi_hash lib lbi clbi installDirs
533 -- For installed packages we install all include files into one dir,
534 -- whereas in the build tree they may live in multiple local dirs.
535 adjustReativeIncludeDirs _
536 |
null (installIncludes bi
) = []
537 |
otherwise = [includedir installDirs
]
538 bi
= libBuildInfo lib
539 installDirs
= absoluteComponentInstallDirs pkg lbi
(componentUnitId clbi
) NoCopyDest
542 relocatableInstalledPackageInfo
:: PackageDescription
546 -> ComponentLocalBuildInfo
548 -> InstalledPackageInfo
549 relocatableInstalledPackageInfo pkg abi_hash lib lbi clbi pkgroot
=
550 generalInstalledPackageInfo adjustReativeIncludeDirs
551 pkg abi_hash lib lbi clbi installDirs
553 -- For installed packages we install all include files into one dir,
554 -- whereas in the build tree they may live in multiple local dirs.
555 adjustReativeIncludeDirs _
556 |
null (installIncludes bi
) = []
557 |
otherwise = [includedir installDirs
]
558 bi
= libBuildInfo lib
560 installDirs
= fmap (("${pkgroot}" </>) . shortRelativePath pkgroot
)
561 $ absoluteComponentInstallDirs pkg lbi
(componentUnitId clbi
) NoCopyDest
563 -- -----------------------------------------------------------------------------
566 unregister
:: PackageDescription
-> LocalBuildInfo
-> RegisterFlags
-> IO ()
567 unregister pkg lbi regFlags
= do
568 let pkgid
= packageId pkg
569 genScript
= fromFlag
(regGenScript regFlags
)
570 verbosity
= fromFlag
(regVerbosity regFlags
)
571 packageDb
= fromFlagOrDefault
(registrationPackageDB
(withPackageDB lbi
))
572 (regPackageDB regFlags
)
574 let invocation
= HcPkg
.unregisterInvocation
575 hpi Verbosity
.normal packageDb pkgid
577 then writeFileAtomic unregScriptFileName
578 (BS
.Char8
.pack
$ invocationAsSystemScript buildOS invocation
)
579 else runProgramInvocation verbosity invocation
580 setupMessage verbosity
"Unregistering" pkgid
581 withHcPkg verbosity
"unregistering is only implemented for GHC and GHCJS"
582 (compiler lbi
) (withPrograms lbi
) unreg
584 unregScriptFileName
:: FilePath
585 unregScriptFileName
= case buildOS
of
586 Windows
-> "unregister.bat"
589 internalPackageDBPath
:: LocalBuildInfo
-> FilePath -> FilePath
590 internalPackageDBPath lbi distPref
=
591 case compilerFlavor
(compiler lbi
) of
592 UHC
-> UHC
.inplacePackageDbPath lbi
593 _
-> distPref
</> "package.conf.inplace"