@@ -25,7 +25,6 @@ module Distribution.Client.ProjectPlanning.Types
2525 , elabExeDependencies
2626 , elabOrderExeDependencies
2727 , elabSetupLibDependencies
28- , elabSetupExeDependencies
2928 , elabPkgConfigDependencies
3029 , elabInplaceDependencyBuildCacheFiles
3130 , elabRequiresRegistration
@@ -581,6 +580,15 @@ elabDistDirParams shared elab =
581580 where
582581 Toolchain {toolchainCompiler, toolchainPlatform} = getStage (pkgConfigToolchains shared) (elabStage elab)
583582
583+ --
584+ -- Order dependencies
585+ --
586+ -- Order dependencies are identified by their 'UnitId' and only used to define the
587+ -- dependency relationships in the build graph. In particular they do not provide
588+ -- any other information needed to build the component or package. We can consider
589+ -- UnitId as a opaque identifier.
590+ --
591+
584592-- | The full set of dependencies which dictate what order we
585593-- need to build things in the install plan: "order dependencies"
586594-- balls everything together. This is mostly only useful for
@@ -592,64 +600,67 @@ elabDistDirParams shared elab =
592600-- Note: this method DOES include setup deps.
593601elabOrderDependencies :: ElaboratedConfiguredPackage -> [WithStage UnitId ]
594602elabOrderDependencies elab =
595- elabOrderLibDependencies elab ++ elabOrderExeDependencies elab
603+ elabOrderLibDependencies elab <> elabOrderExeDependencies elab
596604
597605-- | The result includes setup dependencies
598606elabOrderLibDependencies :: ElaboratedConfiguredPackage -> [WithStage UnitId ]
599607elabOrderLibDependencies elab =
600- ordNub $
601- [ fmap (newSimpleUnitId . confInstId) dep
602- | (dep, _promised) <- elabLibDependencies elab ++ elabSetupLibDependencies elab
603- ]
608+ case elabPkgOrComp elab of
609+ ElabPackage pkg ->
610+ -- Note: flatDeps include the setup dependencies too
611+ ordNub $ CD. flatDeps (pkgOrderLibDependencies pkg)
612+ ElabComponent comp ->
613+ map (WithStage (elabStage elab)) (compOrderLibDependencies comp)
604614
605615-- | The result includes setup dependencies
606616elabOrderExeDependencies :: ElaboratedConfiguredPackage -> [WithStage UnitId ]
607617elabOrderExeDependencies elab =
608- -- Compare with elabOrderLibDependencies. The setup dependencies here do not need
609- -- any special attention because the stage is already included in pkgExeDependencies.
610- map (fmap (newSimpleUnitId . confInstId)) $
611- case elabPkgOrComp elab of
612- ElabPackage pkg -> CD. flatDeps (pkgExeDependencies pkg)
613- ElabComponent comp -> compExeDependencies comp
618+ case elabPkgOrComp elab of
619+ ElabPackage pkg ->
620+ ordNub $ CD. flatDeps (pkgOrderExeDependencies pkg)
621+ ElabComponent comp ->
622+ map (fmap fromConfiguredId) (compExeDependencies comp)
614623
615- -- | The library dependencies (i.e., the libraries we depend on, NOT
616- -- the dependencies of the library), NOT including setup dependencies.
617- -- These are passed to the @Setup@ script via @--dependency@ or @--promised-dependency@.
624+ -- | See 'elabOrderDependencies'. This gives the unflattened version,
625+ -- which can be useful in some circumstances.
626+ pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [WithStage UnitId ]
627+ pkgOrderDependencies pkg =
628+ pkgOrderLibDependencies pkg <> pkgOrderExeDependencies pkg
629+
630+ pkgOrderLibDependencies :: ElaboratedPackage -> ComponentDeps [WithStage UnitId ]
631+ pkgOrderLibDependencies pkg =
632+ CD. fromList
633+ [ (comp, map (WithStage stage . fromConfiguredId . fst ) deps)
634+ | (comp, deps) <- CD. toList (pkgLibDependencies pkg)
635+ , let stage = if comp == CD. ComponentSetup
636+ then prevStage (pkgStage pkg)
637+ else pkgStage pkg
638+ ]
639+
640+ pkgOrderExeDependencies :: ElaboratedPackage -> ComponentDeps [WithStage UnitId ]
641+ pkgOrderExeDependencies pkg =
642+ fmap (map (fmap fromConfiguredId))
643+ $ pkgExeDependencies pkg
644+
645+ fromConfiguredId :: ConfiguredId -> UnitId
646+ fromConfiguredId = newSimpleUnitId . confInstId
647+
648+ --- | Library dependencies.
649+ ---
650+ --- These are identified by their 'ConfiguredId' and are passed to the @Setup@
651+ --- script via @--dependency@ or @--promised-dependency@.
652+ --- Note that setup dependencies (meaning the library dependencies of the setup
653+ -- script) are not included here, they are handled separately.
618654elabLibDependencies :: ElaboratedConfiguredPackage -> [(WithStage ConfiguredId , Bool )]
619655elabLibDependencies elab =
656+ -- Library dependencies are always in the same stage as the component/package we are
657+ -- building.
658+ map (\ (cid, promised) -> (WithStage (elabStage elab) cid, promised)) $
620659 case elabPkgOrComp elab of
621660 ElabPackage pkg ->
622- ordNub [ (WithStage (pkgStage pkg) cid, promised)
623- | (cid, promised) <- CD. nonSetupDeps (pkgLibDependencies pkg)
624- ]
661+ ordNub $ CD. nonSetupDeps (pkgLibDependencies pkg)
625662 ElabComponent comp ->
626- [ (WithStage (elabStage elab) c, promised)
627- | (c, promised) <- compLibDependencies comp
628- ]
629-
630- -- | The setup dependencies (the library dependencies of the setup executable;
631- -- note that it is not legal for setup scripts to have executable
632- -- dependencies at the moment.)
633- elabSetupLibDependencies :: ElaboratedConfiguredPackage -> [(WithStage ConfiguredId , Bool )]
634- elabSetupLibDependencies elab =
635- case elabPkgOrComp elab of
636- ElabPackage pkg ->
637- ordNub [ (WithStage (prevStage (pkgStage pkg)) cid, promised)
638- | (cid, promised) <- CD. setupDeps (pkgLibDependencies pkg)
639- ]
640- -- TODO: Custom setups not supported for components yet. When
641- -- they are, need to do this differently
642- ElabComponent _ -> []
643-
644- -- | This would not be allowed actually. See comment on elabSetupLibDependencies.
645- elabSetupExeDependencies :: ElaboratedConfiguredPackage -> [WithStage ComponentId ]
646- elabSetupExeDependencies elab =
647- map (fmap confInstId) $
648- case elabPkgOrComp elab of
649- ElabPackage pkg -> CD. setupDeps (pkgExeDependencies pkg)
650- -- TODO: Custom setups not supported for components yet. When
651- -- they are, need to do this differently
652- ElabComponent _ -> []
663+ compLibDependencies comp
653664
654665-- | The executable dependencies (i.e., the executables we depend on);
655666-- these are the executables we must add to the PATH before we invoke
@@ -658,7 +669,7 @@ elabExeDependencies :: ElaboratedConfiguredPackage -> [WithStage ComponentId]
658669elabExeDependencies elab =
659670 map (fmap confInstId) $
660671 case elabPkgOrComp elab of
661- ElabPackage pkg -> CD. nonSetupDeps (pkgExeDependencies pkg)
672+ ElabPackage pkg -> ordNub $ CD. nonSetupDeps (pkgExeDependencies pkg)
662673 ElabComponent comp -> compExeDependencies comp
663674
664675-- | This returns the paths of all the executables we depend on; we
@@ -668,14 +679,33 @@ elabExeDependencies elab =
668679elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath ]
669680elabExeDependencyPaths elab =
670681 case elabPkgOrComp elab of
671- ElabPackage pkg -> map snd $ CD. nonSetupDeps (pkgExeDependencyPaths pkg)
682+ ElabPackage pkg -> ordNub $ map snd $ CD. nonSetupDeps (pkgExeDependencyPaths pkg)
672683 ElabComponent comp -> map snd (compExeDependencyPaths comp)
673684
674685elabPkgConfigDependencies :: ElaboratedConfiguredPackage -> [(PkgconfigName , Maybe PkgconfigVersion )]
675- elabPkgConfigDependencies ElaboratedConfiguredPackage {elabPkgOrComp = ElabPackage pkg} =
676- pkgPkgConfigDependencies pkg
677- elabPkgConfigDependencies ElaboratedConfiguredPackage {elabPkgOrComp = ElabComponent comp} =
678- compPkgConfigDependencies comp
686+ elabPkgConfigDependencies elab =
687+ case elabPkgOrComp elab of
688+ ElabPackage pkg -> pkgPkgConfigDependencies pkg
689+ ElabComponent comp -> compPkgConfigDependencies comp
690+
691+ -- | The setup dependencies (i.e. the library dependencies of the setup executable)
692+ -- Note that it is not legal for setup scripts to have executable dependencies.
693+ -- TODO: In that case we should probably not have this function at all, and
694+ -- only use pkgSetupLibDependencies
695+ elabSetupLibDependencies :: ElaboratedConfiguredPackage -> [WithStage ConfiguredId ]
696+ elabSetupLibDependencies elab =
697+ case elabPkgOrComp elab of
698+ ElabPackage pkg -> pkgSetupLibDependencies pkg
699+ -- Custom setups not supported for components.
700+ ElabComponent _ -> []
701+
702+ pkgSetupLibDependencies :: ElaboratedPackage -> [WithStage ConfiguredId ]
703+ pkgSetupLibDependencies pkg =
704+ map (WithStage stage . fst )
705+ $ ordNub $ CD. setupDeps (pkgLibDependencies pkg)
706+ where
707+ stage = prevStage (pkgStage pkg)
708+
679709
680710-- | The cache files of all our inplace dependencies which,
681711-- when updated, require us to rebuild. See #4202 for
@@ -750,7 +780,7 @@ data ElaboratedComponent = ElaboratedComponent
750780 , compOrderLibDependencies :: [UnitId ]
751781 -- ^ The UnitIds of the libraries (identifying elaborated packages/
752782 -- components) that must be built before this project. This
753- -- is used purely for ordering purposes. It can contain both
783+ -- is used purely for ordering purposes. It can contain both
754784 -- references to definite and indefinite packages; an indefinite
755785 -- UnitId indicates that we must typecheck that indefinite package
756786 -- before we can build this one.
@@ -833,19 +863,6 @@ whyNotPerComponent = \case
833863 CuzNoBuildableComponents -> " there are no buildable components"
834864 CuzDisablePerComponent -> " you passed --disable-per-component"
835865
836- -- | See 'elabOrderDependencies'. This gives the unflattened version,
837- -- which can be useful in some circumstances.
838- pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [WithStage UnitId ]
839- pkgOrderDependencies pkg =
840- fmap
841- (map (\ (cid, _) -> WithStage (pkgStage pkg) (newSimpleUnitId $ confInstId cid)))
842- (pkgLibDependencies pkg)
843- <>
844- fmap
845- (map (fmap (newSimpleUnitId . confInstId)))
846- (pkgExeDependencies pkg)
847-
848-
849866-- | This is used in the install plan to indicate how the package will be
850867-- built.
851868data BuildStyle
0 commit comments