1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 {-# LANGUAGE DuplicateRecordFields #-}
4 {-# LANGUAGE FlexibleContexts #-}
5 {-# LANGUAGE NamedFieldPuns #-}
6 {-# LANGUAGE PatternSynonyms #-}
7 {-# LANGUAGE RankNTypes #-}
9 module Distribution
.Types
.LocalBuildInfo
15 , componentEnabledSpec
51 -- * Convenience accessors
54 , localCompatPackageKey
63 -- * Build targets of the 'LocalBuildInfo'.
65 -- NB: the primes mean that they take a 'PackageDescription'
66 -- which may not match 'localPkgDescr' in 'LocalBuildInfo'.
67 -- More logical types would drop this argument, but
68 -- at the moment, this is the ONLY supported function, because
69 -- 'localPkgDescr' is not guaranteed to match. At some point
70 -- we will fix it and then we can use the (free) unprimed
71 -- namespace for the correct commands.
73 -- See https://github.com/haskell/cabal/issues/3606 for more
76 , componentNameTargets
'
78 , allTargetsInBuildOrder
'
79 , withAllTargetsInBuildOrder
'
80 , neededTargetsInBuildOrder
'
81 , withNeededTargetsInBuildOrder
'
84 -- * Functions you SHOULD NOT USE (yet), but are defined here to
86 -- prevent someone from accidentally defining them
88 , componentNameTargets
90 , allTargetsInBuildOrder
91 , withAllTargetsInBuildOrder
92 , neededTargetsInBuildOrder
93 , withNeededTargetsInBuildOrder
96 import Distribution
.Compat
.Prelude
99 import Distribution
.Types
.ComponentId
100 import Distribution
.Types
.ComponentLocalBuildInfo
101 import Distribution
.Types
.ComponentRequestedSpec
102 import qualified Distribution
.Types
.LocalBuildConfig
as LBC
103 import Distribution
.Types
.PackageDescription
104 import Distribution
.Types
.PackageId
105 import Distribution
.Types
.TargetInfo
106 import Distribution
.Types
.UnitId
108 import Distribution
.PackageDescription
109 import Distribution
.Pretty
110 import Distribution
.Simple
.Compiler
111 import Distribution
.Simple
.Flag
112 import Distribution
.Simple
.InstallDirs
hiding
113 ( absoluteInstallDirs
114 , prefixRelativeInstallDirs
117 import Distribution
.Simple
.PackageIndex
118 import Distribution
.Simple
.Program
119 import Distribution
.Simple
.Setup
.Config
120 import Distribution
.System
122 import qualified Data
.Map
as Map
123 import Distribution
.Compat
.Graph
(Graph
)
124 import qualified Distribution
.Compat
.Graph
as Graph
125 import System
.FilePath ((</>))
127 -- | Data cached after configuration step. See also
128 -- 'Distribution.Simple.Setup.ConfigFlags'.
129 data LocalBuildInfo
= NewLocalBuildInfo
130 { localBuildDescr
:: LBC
.LocalBuildDescr
131 -- ^ Information about a package determined by Cabal
132 -- after the configuration step.
133 , localBuildConfig
:: LBC
.LocalBuildConfig
134 -- ^ Information about a package configuration
135 -- that can be modified by the user at configuration time.
137 deriving (Generic
, Read, Show, Typeable
)
139 {-# COMPLETE LocalBuildInfo #-}
141 -- | This pattern synonym is for backwards compatibility, to adapt
142 -- to 'LocalBuildInfo' being split into 'LocalBuildDescr' and 'LocalBuildConfig'.
143 pattern LocalBuildInfo
146 -> ComponentRequestedSpec
148 -> InstallDirTemplates
152 -> Graph ComponentLocalBuildInfo
153 -> Map ComponentName
[ComponentLocalBuildInfo
]
154 -> Map
(PackageName
, ComponentName
) ComponentId
155 -> InstalledPackageIndex
156 -> PackageDescription
180 pattern LocalBuildInfo
183 , componentEnabledSpec
185 , installDirTemplates
220 { packageBuildDescr
=
221 LBC
.PackageBuildDescr
224 , componentEnabledSpec
228 , installDirTemplates
233 , componentBuildDescr
=
234 LBC
.ComponentBuildDescr
270 instance Binary LocalBuildInfo
271 instance Structured LocalBuildInfo
273 -------------------------------------------------------------------------------
274 -- Accessor functions
276 buildDir
:: LocalBuildInfo
-> FilePath
278 buildDirPBD
$ LBC
.packageBuildDescr
$ localBuildDescr lbi
280 buildDirPBD
:: LBC
.PackageBuildDescr
-> FilePath
281 buildDirPBD
(LBC
.PackageBuildDescr
{configFlags
= cfg
}) =
282 configFlagsBuildDir cfg
284 configFlagsBuildDir
:: ConfigFlags
-> FilePath
285 configFlagsBuildDir cfg
= fromFlag
(configDistPref cfg
) </> "build"
287 cabalFilePath
:: LocalBuildInfo
-> Maybe FilePath
288 cabalFilePath
(LocalBuildInfo
{configFlags
= cfg
}) =
289 flagToMaybe
(configCabalFilePath cfg
)
291 progPrefix
, progSuffix
:: LocalBuildInfo
-> PathTemplate
292 progPrefix
(LocalBuildInfo
{configFlags
= cfg
}) =
293 fromFlag
$ configProgPrefix cfg
294 progSuffix
(LocalBuildInfo
{configFlags
= cfg
}) =
295 fromFlag
$ configProgSuffix cfg
297 -- TODO: Get rid of these functions, as much as possible. They are
298 -- a bit useful in some cases, but you should be very careful!
300 -- | Extract the 'ComponentId' from the public library component of a
301 -- 'LocalBuildInfo' if it exists, or make a fake component ID based
302 -- on the package ID.
303 localComponentId
:: LocalBuildInfo
-> ComponentId
304 localComponentId lbi
=
305 case componentNameCLBIs lbi
(CLibName LMainLibName
) of
306 [LibComponentLocalBuildInfo
{componentComponentId
= cid
}] ->
308 _
-> mkComponentId
(prettyShow
(localPackage lbi
))
310 -- | Extract the 'PackageIdentifier' of a 'LocalBuildInfo'.
311 -- This is a "safe" use of 'localPkgDescr'
312 localPackage
:: LocalBuildInfo
-> PackageId
313 localPackage
(LocalBuildInfo
{localPkgDescr
= pkg
}) = package pkg
315 -- | Extract the 'UnitId' from the library component of a
316 -- 'LocalBuildInfo' if it exists, or make a fake unit ID based on
318 localUnitId
:: LocalBuildInfo
-> UnitId
320 case componentNameCLBIs lbi
(CLibName LMainLibName
) of
321 [LibComponentLocalBuildInfo
{componentUnitId
= uid
}] ->
323 _
-> mkLegacyUnitId
$ localPackage lbi
325 -- | Extract the compatibility package key from the public library component of a
326 -- 'LocalBuildInfo' if it exists, or make a fake package key based
327 -- on the package ID.
328 localCompatPackageKey
:: LocalBuildInfo
-> String
329 localCompatPackageKey lbi
=
330 case componentNameCLBIs lbi
(CLibName LMainLibName
) of
331 [LibComponentLocalBuildInfo
{componentCompatPackageKey
= pk
}] ->
333 _
-> prettyShow
(localPackage lbi
)
335 -- | Convenience function to generate a default 'TargetInfo' from a
336 -- 'ComponentLocalBuildInfo'. The idea is to call this once, and then
337 -- use 'TargetInfo' everywhere else. Private to this module.
338 mkTargetInfo
:: PackageDescription
-> LocalBuildInfo
-> ComponentLocalBuildInfo
-> TargetInfo
339 mkTargetInfo pkg_descr _lbi clbi
=
342 , -- NB: @pkg_descr@, not @localPkgDescr lbi@!
346 (componentLocalName clbi
)
349 -- | Return all 'TargetInfo's associated with 'ComponentName'.
350 -- In the presence of Backpack there may be more than one!
351 -- Has a prime because it takes a 'PackageDescription' argument
352 -- which may disagree with 'localPkgDescr' in 'LocalBuildInfo'.
353 componentNameTargets
' :: PackageDescription
-> LocalBuildInfo
-> ComponentName
-> [TargetInfo
]
354 componentNameTargets
' pkg_descr lbi
@(LocalBuildInfo
{componentNameMap
= comps
}) cname
=
355 case Map
.lookup cname comps
of
356 Just clbis
-> map (mkTargetInfo pkg_descr lbi
) clbis
359 unitIdTarget
' :: PackageDescription
-> LocalBuildInfo
-> UnitId
-> Maybe TargetInfo
360 unitIdTarget
' pkg_descr lbi
@(LocalBuildInfo
{componentGraph
= compsGraph
}) uid
=
361 case Graph
.lookup uid compsGraph
of
362 Just clbi
-> Just
(mkTargetInfo pkg_descr lbi clbi
)
365 -- | Return all 'ComponentLocalBuildInfo's associated with 'ComponentName'.
366 -- In the presence of Backpack there may be more than one!
367 componentNameCLBIs
:: LocalBuildInfo
-> ComponentName
-> [ComponentLocalBuildInfo
]
368 componentNameCLBIs
(LocalBuildInfo
{componentNameMap
= comps
}) cname
=
369 case Map
.lookup cname comps
of
373 -- TODO: Maybe cache topsort (Graph can do this)
375 -- | Return the list of default 'TargetInfo's associated with a
376 -- configured package, in the order they need to be built.
377 -- Has a prime because it takes a 'PackageDescription' argument
378 -- which may disagree with 'localPkgDescr' in 'LocalBuildInfo'.
379 allTargetsInBuildOrder
' :: PackageDescription
-> LocalBuildInfo
-> [TargetInfo
]
380 allTargetsInBuildOrder
' pkg_descr lbi
@(LocalBuildInfo
{componentGraph
= compsGraph
}) =
381 map (mkTargetInfo pkg_descr lbi
) (Graph
.revTopSort compsGraph
)
383 -- | Execute @f@ for every 'TargetInfo' in the package, respecting the
384 -- build dependency order. (TODO: We should use Shake!)
385 -- Has a prime because it takes a 'PackageDescription' argument
386 -- which may disagree with 'localPkgDescr' in 'LocalBuildInfo'.
387 withAllTargetsInBuildOrder
' :: PackageDescription
-> LocalBuildInfo
-> (TargetInfo
-> IO ()) -> IO ()
388 withAllTargetsInBuildOrder
' pkg_descr lbi f
=
389 sequence_ [f target | target
<- allTargetsInBuildOrder
' pkg_descr lbi
]
391 -- | Return the list of all targets needed to build the @uids@, in
392 -- the order they need to be built.
393 -- Has a prime because it takes a 'PackageDescription' argument
394 -- which may disagree with 'localPkgDescr' in 'LocalBuildInfo'.
395 neededTargetsInBuildOrder
' :: PackageDescription
-> LocalBuildInfo
-> [UnitId
] -> [TargetInfo
]
396 neededTargetsInBuildOrder
' pkg_descr lbi
@(LocalBuildInfo
{componentGraph
= compsGraph
}) uids
=
397 case Graph
.closure compsGraph uids
of
398 Nothing
-> error $ "localBuildPlan: missing uids " ++ intercalate
", " (map prettyShow uids
)
399 Just clos
-> map (mkTargetInfo pkg_descr lbi
) (Graph
.revTopSort
(Graph
.fromDistinctList clos
))
401 -- | Execute @f@ for every 'TargetInfo' needed to build @uid@s, respecting
402 -- the build dependency order.
403 -- Has a prime because it takes a 'PackageDescription' argument
404 -- which may disagree with 'localPkgDescr' in 'LocalBuildInfo'.
405 withNeededTargetsInBuildOrder
' :: PackageDescription
-> LocalBuildInfo
-> [UnitId
] -> (TargetInfo
-> IO ()) -> IO ()
406 withNeededTargetsInBuildOrder
' pkg_descr lbi uids f
=
407 sequence_ [f target | target
<- neededTargetsInBuildOrder
' pkg_descr lbi uids
]
409 -- | Is coverage enabled for test suites? In practice, this requires library
410 -- and executable profiling to be enabled.
411 testCoverage
:: LocalBuildInfo
-> Bool
412 testCoverage
(LocalBuildInfo
{exeCoverage
= exes
, libCoverage
= libs
}) =
415 -------------------------------------------------------------------------------
416 -- Stub functions to prevent someone from accidentally defining them
418 {-# WARNING componentNameTargets, unitIdTarget, allTargetsInBuildOrder, withAllTargetsInBuildOrder, neededTargetsInBuildOrder, withNeededTargetsInBuildOrder "By using this function, you may be introducing a bug where you retrieve a 'Component' which does not have 'HookedBuildInfo' applied to it. See the documentation for 'HookedBuildInfo' for an explanation of the issue. If you have a 'PackageDescription' handy (NOT from the 'LocalBuildInfo'), try using the primed version of the function, which takes it as an extra argument." #-}
419 componentNameTargets
:: LocalBuildInfo
-> ComponentName
-> [TargetInfo
]
420 componentNameTargets lbi
@(LocalBuildInfo
{localPkgDescr
= pkg
}) =
421 componentNameTargets
' pkg lbi
422 unitIdTarget
:: LocalBuildInfo
-> UnitId
-> Maybe TargetInfo
423 unitIdTarget lbi
@(LocalBuildInfo
{localPkgDescr
= pkg
}) =
424 unitIdTarget
' pkg lbi
425 allTargetsInBuildOrder
:: LocalBuildInfo
-> [TargetInfo
]
426 allTargetsInBuildOrder lbi
@(LocalBuildInfo
{localPkgDescr
= pkg
}) =
427 allTargetsInBuildOrder
' pkg lbi
428 withAllTargetsInBuildOrder
:: LocalBuildInfo
-> (TargetInfo
-> IO ()) -> IO ()
429 withAllTargetsInBuildOrder lbi
@(LocalBuildInfo
{localPkgDescr
= pkg
}) =
430 withAllTargetsInBuildOrder
' pkg lbi
431 neededTargetsInBuildOrder
:: LocalBuildInfo
-> [UnitId
] -> [TargetInfo
]
432 neededTargetsInBuildOrder lbi
@(LocalBuildInfo
{localPkgDescr
= pkg
}) =
433 neededTargetsInBuildOrder
' pkg lbi
434 withNeededTargetsInBuildOrder
:: LocalBuildInfo
-> [UnitId
] -> (TargetInfo
-> IO ()) -> IO ()
435 withNeededTargetsInBuildOrder lbi
@(LocalBuildInfo
{localPkgDescr
= pkg
}) =
436 withNeededTargetsInBuildOrder
' pkg lbi