Skip to content

Commit 60cbabf

Browse files
committed
refactor(cabal-install): harmonise various dependency functions
1 parent 856fc22 commit 60cbabf

File tree

2 files changed

+84
-69
lines changed

2 files changed

+84
-69
lines changed

cabal-install/src/Distribution/Client/ProjectPlanning.hs

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1907,7 +1907,7 @@ elaborateInstallPlan
19071907
compExeDependencyPaths :: [(WithStage ConfiguredId, FilePath)]
19081908
compExeDependencyPaths =
19091909
-- External
1910-
[ (WithStage solverPkgStage confId, path)
1910+
[ (WithStage (stageOf pkg) confId, path)
19111911
| pkg <- external_exe_dep_pkgs
19121912
, let confId = configuredId pkg
19131913
, confSrcId confId /= pkgid
@@ -1963,7 +1963,6 @@ elaborateInstallPlan
19631963

19641964
cc = cc0{cc_ann_id = fmap (const cid) (cc_ann_id cc0)}
19651965

1966-
infoProgress $ hang (text "configured component:") 4 (dispConfiguredComponent cc)
19671966

19681967
-- 4. Perform mix-in linking
19691968
let lookup_uid def_uid =
@@ -1985,7 +1984,6 @@ elaborateInstallPlan
19851984
cc
19861985
-- ^ configured component
19871986

1988-
infoProgress $ hang (text "linked component:") 4 (dispLinkedComponent lc)
19891987
-- NB: elab is setup to be the correct form for an
19901988
-- indefinite library, or a definite library with no holes.
19911989
-- We will modify it in 'instantiateInstallPlan' to handle
@@ -3965,7 +3963,7 @@ setupHsScriptOptions
39653963
, useDependencies =
39663964
[ (confInstId cid, confSrcId cid)
39673965
-- TODO: we should filter for dependencies on libraries but that should be implicit in elabSetupLibDependencies
3968-
| (WithStage _ cid, _promised) <- elabSetupLibDependencies elab
3966+
| (WithStage _ cid) <- elabSetupLibDependencies elab
39693967
]
39703968
, useDependenciesExclusive = True
39713969
, useVersionMacros = elabSetupScriptStyle == SetupCustomExplicitDeps

cabal-install/src/Distribution/Client/ProjectPlanning/Types.hs

Lines changed: 82 additions & 65 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,6 @@ module Distribution.Client.ProjectPlanning.Types
2525
, elabExeDependencies
2626
, elabOrderExeDependencies
2727
, elabSetupLibDependencies
28-
, elabSetupExeDependencies
2928
, elabPkgConfigDependencies
3029
, elabInplaceDependencyBuildCacheFiles
3130
, elabRequiresRegistration
@@ -579,6 +578,15 @@ elabDistDirParams shared elab =
579578
where
580579
Toolchain{toolchainCompiler, toolchainPlatform} = getStage (pkgConfigToolchains shared) (elabStage elab)
581580

581+
--
582+
-- Order dependencies
583+
--
584+
-- Order dependencies are identified by their 'UnitId' and only used to define the
585+
-- dependency relationships in the build graph. In particular they do not provide
586+
-- any other information needed to build the component or package. We can consider
587+
-- UnitId as a opaque identifier.
588+
--
589+
582590
-- | The full set of dependencies which dictate what order we
583591
-- need to build things in the install plan: "order dependencies"
584592
-- balls everything together. This is mostly only useful for
@@ -590,64 +598,67 @@ elabDistDirParams shared elab =
590598
-- Note: this method DOES include setup deps.
591599
elabOrderDependencies :: ElaboratedConfiguredPackage -> [WithStage UnitId]
592600
elabOrderDependencies elab =
593-
elabOrderLibDependencies elab ++ elabOrderExeDependencies elab
601+
elabOrderLibDependencies elab <> elabOrderExeDependencies elab
594602

595603
-- | The result includes setup dependencies
596604
elabOrderLibDependencies :: ElaboratedConfiguredPackage -> [WithStage UnitId]
597605
elabOrderLibDependencies elab =
598-
ordNub $
599-
[ fmap (newSimpleUnitId . confInstId) dep
600-
| (dep, _promised) <- elabLibDependencies elab ++ elabSetupLibDependencies elab
601-
]
606+
case elabPkgOrComp elab of
607+
ElabPackage pkg ->
608+
-- Note: flatDeps include the setup dependencies too
609+
ordNub $ CD.flatDeps (pkgOrderLibDependencies pkg)
610+
ElabComponent comp ->
611+
map (WithStage (elabStage elab)) (compOrderLibDependencies comp)
602612

603613
-- | The result includes setup dependencies
604614
elabOrderExeDependencies :: ElaboratedConfiguredPackage -> [WithStage UnitId]
605615
elabOrderExeDependencies elab =
606-
-- Compare with elabOrderLibDependencies. The setup dependencies here do not need
607-
-- any special attention because the stage is already included in pkgExeDependencies.
608-
map (fmap (newSimpleUnitId . confInstId)) $
609-
case elabPkgOrComp elab of
610-
ElabPackage pkg -> CD.flatDeps (pkgExeDependencies pkg)
611-
ElabComponent comp -> compExeDependencies comp
616+
case elabPkgOrComp elab of
617+
ElabPackage pkg ->
618+
ordNub $ CD.flatDeps (pkgOrderExeDependencies pkg)
619+
ElabComponent comp ->
620+
map (fmap fromConfiguredId) (compExeDependencies comp)
612621

613-
-- | The library dependencies (i.e., the libraries we depend on, NOT
614-
-- the dependencies of the library), NOT including setup dependencies.
615-
-- These are passed to the @Setup@ script via @--dependency@ or @--promised-dependency@.
622+
-- | See 'elabOrderDependencies'. This gives the unflattened version,
623+
-- which can be useful in some circumstances.
624+
pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [WithStage UnitId]
625+
pkgOrderDependencies pkg =
626+
pkgOrderLibDependencies pkg <> pkgOrderExeDependencies pkg
627+
628+
pkgOrderLibDependencies :: ElaboratedPackage -> ComponentDeps [WithStage UnitId]
629+
pkgOrderLibDependencies pkg =
630+
CD.fromList
631+
[ (comp, map (WithStage stage . fromConfiguredId . fst) deps)
632+
| (comp, deps) <- CD.toList (pkgLibDependencies pkg)
633+
, let stage = if comp == CD.ComponentSetup
634+
then prevStage (pkgStage pkg)
635+
else pkgStage pkg
636+
]
637+
638+
pkgOrderExeDependencies :: ElaboratedPackage -> ComponentDeps [WithStage UnitId]
639+
pkgOrderExeDependencies pkg =
640+
fmap (map (fmap fromConfiguredId))
641+
$ pkgExeDependencies pkg
642+
643+
fromConfiguredId :: ConfiguredId -> UnitId
644+
fromConfiguredId = newSimpleUnitId . confInstId
645+
646+
--- | Library dependencies.
647+
---
648+
--- These are identified by their 'ConfiguredId' and are passed to the @Setup@
649+
--- script via @--dependency@ or @--promised-dependency@.
650+
--- Note that setup dependencies (meaning the library dependencies of the setup
651+
-- script) are not included here, they are handled separately.
616652
elabLibDependencies :: ElaboratedConfiguredPackage -> [(WithStage ConfiguredId, Bool)]
617653
elabLibDependencies elab =
654+
-- Library dependencies are always in the same stage as the component/package we are
655+
-- building.
656+
map (\(cid, promised) -> (WithStage (elabStage elab) cid, promised)) $
618657
case elabPkgOrComp elab of
619658
ElabPackage pkg ->
620-
ordNub [ (WithStage (pkgStage pkg) cid, promised)
621-
| (cid, promised) <- CD.nonSetupDeps (pkgLibDependencies pkg)
622-
]
659+
ordNub $ CD.nonSetupDeps (pkgLibDependencies pkg)
623660
ElabComponent comp ->
624-
[ (WithStage (elabStage elab) c, promised)
625-
| (c, promised) <- compLibDependencies comp
626-
]
627-
628-
-- | The setup dependencies (the library dependencies of the setup executable;
629-
-- note that it is not legal for setup scripts to have executable
630-
-- dependencies at the moment.)
631-
elabSetupLibDependencies :: ElaboratedConfiguredPackage -> [(WithStage ConfiguredId, Bool)]
632-
elabSetupLibDependencies elab =
633-
case elabPkgOrComp elab of
634-
ElabPackage pkg ->
635-
ordNub [ (WithStage (prevStage (pkgStage pkg)) cid, promised)
636-
| (cid, promised) <- CD.setupDeps (pkgLibDependencies pkg)
637-
]
638-
-- TODO: Custom setups not supported for components yet. When
639-
-- they are, need to do this differently
640-
ElabComponent _ -> []
641-
642-
-- | This would not be allowed actually. See comment on elabSetupLibDependencies.
643-
elabSetupExeDependencies :: ElaboratedConfiguredPackage -> [WithStage ComponentId]
644-
elabSetupExeDependencies elab =
645-
map (fmap confInstId) $
646-
case elabPkgOrComp elab of
647-
ElabPackage pkg -> CD.setupDeps (pkgExeDependencies pkg)
648-
-- TODO: Custom setups not supported for components yet. When
649-
-- they are, need to do this differently
650-
ElabComponent _ -> []
661+
compLibDependencies comp
651662

652663
-- | The executable dependencies (i.e., the executables we depend on);
653664
-- these are the executables we must add to the PATH before we invoke
@@ -656,7 +667,7 @@ elabExeDependencies :: ElaboratedConfiguredPackage -> [WithStage ComponentId]
656667
elabExeDependencies elab =
657668
map (fmap confInstId) $
658669
case elabPkgOrComp elab of
659-
ElabPackage pkg -> CD.nonSetupDeps (pkgExeDependencies pkg)
670+
ElabPackage pkg -> ordNub $ CD.nonSetupDeps (pkgExeDependencies pkg)
660671
ElabComponent comp -> compExeDependencies comp
661672

662673
-- | This returns the paths of all the executables we depend on; we
@@ -666,14 +677,33 @@ elabExeDependencies elab =
666677
elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath]
667678
elabExeDependencyPaths elab =
668679
case elabPkgOrComp elab of
669-
ElabPackage pkg -> map snd $ CD.nonSetupDeps (pkgExeDependencyPaths pkg)
680+
ElabPackage pkg -> ordNub $ map snd $ CD.nonSetupDeps (pkgExeDependencyPaths pkg)
670681
ElabComponent comp -> map snd (compExeDependencyPaths comp)
671682

672683
elabPkgConfigDependencies :: ElaboratedConfiguredPackage -> [(PkgconfigName, Maybe PkgconfigVersion)]
673-
elabPkgConfigDependencies ElaboratedConfiguredPackage{elabPkgOrComp = ElabPackage pkg} =
674-
pkgPkgConfigDependencies pkg
675-
elabPkgConfigDependencies ElaboratedConfiguredPackage{elabPkgOrComp = ElabComponent comp} =
676-
compPkgConfigDependencies comp
684+
elabPkgConfigDependencies elab =
685+
case elabPkgOrComp elab of
686+
ElabPackage pkg -> pkgPkgConfigDependencies pkg
687+
ElabComponent comp -> compPkgConfigDependencies comp
688+
689+
-- | The setup dependencies (i.e. the library dependencies of the setup executable)
690+
-- Note that it is not legal for setup scripts to have executable dependencies.
691+
-- TODO: In that case we should probably not have this function at all, and
692+
-- only use pkgSetupLibDependencies
693+
elabSetupLibDependencies :: ElaboratedConfiguredPackage -> [WithStage ConfiguredId]
694+
elabSetupLibDependencies elab =
695+
case elabPkgOrComp elab of
696+
ElabPackage pkg -> pkgSetupLibDependencies pkg
697+
-- Custom setups not supported for components.
698+
ElabComponent _ -> []
699+
700+
pkgSetupLibDependencies :: ElaboratedPackage -> [WithStage ConfiguredId]
701+
pkgSetupLibDependencies pkg =
702+
map (WithStage stage . fst)
703+
$ ordNub $ CD.setupDeps (pkgLibDependencies pkg)
704+
where
705+
stage = prevStage (pkgStage pkg)
706+
677707

678708
-- | The cache files of all our inplace dependencies which,
679709
-- when updated, require us to rebuild. See #4202 for
@@ -748,7 +778,7 @@ data ElaboratedComponent = ElaboratedComponent
748778
, compOrderLibDependencies :: [UnitId]
749779
-- ^ The UnitIds of the libraries (identifying elaborated packages/
750780
-- components) that must be built before this project. This
751-
-- is used purely for ordering purposes. It can contain both
781+
-- is used purely for ordering purposes. It can contain both
752782
-- references to definite and indefinite packages; an indefinite
753783
-- UnitId indicates that we must typecheck that indefinite package
754784
-- before we can build this one.
@@ -831,19 +861,6 @@ whyNotPerComponent = \case
831861
CuzNoBuildableComponents -> "there are no buildable components"
832862
CuzDisablePerComponent -> "you passed --disable-per-component"
833863

834-
-- | See 'elabOrderDependencies'. This gives the unflattened version,
835-
-- which can be useful in some circumstances.
836-
pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [WithStage UnitId]
837-
pkgOrderDependencies pkg =
838-
fmap
839-
(map (\(cid, _) -> WithStage (pkgStage pkg) (newSimpleUnitId $ confInstId cid)))
840-
(pkgLibDependencies pkg)
841-
<>
842-
fmap
843-
(map (fmap (newSimpleUnitId . confInstId)))
844-
(pkgExeDependencies pkg)
845-
846-
847864
-- | This is used in the install plan to indicate how the package will be
848865
-- built.
849866
data BuildStyle

0 commit comments

Comments
 (0)