@@ -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,66 +598,68 @@ elabDistDirParams shared elab =
590598-- Note: this method DOES include setup deps.
591599elabOrderDependencies :: ElaboratedConfiguredPackage -> [WithStage UnitId ]
592600elabOrderDependencies elab =
593- elabOrderLibDependencies elab ++ elabOrderExeDependencies elab
601+ elabOrderLibDependencies elab <> elabOrderExeDependencies elab
594602
595603-- | The result includes setup dependencies
596604elabOrderLibDependencies :: ElaboratedConfiguredPackage -> [WithStage UnitId ]
597605elabOrderLibDependencies 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
604614elabOrderExeDependencies :: ElaboratedConfiguredPackage -> [WithStage UnitId ]
605615elabOrderExeDependencies 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
612-
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@.
616- elabLibDependencies :: ElaboratedConfiguredPackage -> [(WithStage ConfiguredId , Bool )]
617- elabLibDependencies elab =
618616 case elabPkgOrComp elab of
619617 ElabPackage pkg ->
620- ordNub
621- [ (WithStage (pkgStage pkg) cid, promised)
622- | (cid, promised) <- CD. nonSetupDeps (pkgLibDependencies pkg)
623- ]
618+ ordNub $ CD. flatDeps (pkgOrderExeDependencies pkg)
624619 ElabComponent comp ->
625- [ (WithStage (elabStage elab) c, promised)
626- | (c, promised) <- compLibDependencies comp
627- ]
628-
629- -- | The setup dependencies (the library dependencies of the setup executable;
630- -- note that it is not legal for setup scripts to have executable
631- -- dependencies at the moment.)
632- elabSetupLibDependencies :: ElaboratedConfiguredPackage -> [(WithStage ConfiguredId , Bool )]
633- elabSetupLibDependencies elab =
634- case elabPkgOrComp elab of
635- ElabPackage pkg ->
636- ordNub
637- [ (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 _ -> []
620+ map (fmap fromConfiguredId) (compExeDependencies comp)
643621
644- -- | This would not be allowed actually. See comment on elabSetupLibDependencies.
645- elabSetupExeDependencies :: ElaboratedConfiguredPackage -> [WithStage ComponentId ]
646- elabSetupExeDependencies elab =
647- map (fmap confInstId) $
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 =
634+ if comp == CD. ComponentSetup
635+ then prevStage (pkgStage pkg)
636+ else pkgStage pkg
637+ ]
638+
639+ pkgOrderExeDependencies :: ElaboratedPackage -> ComponentDeps [WithStage UnitId ]
640+ pkgOrderExeDependencies pkg =
641+ fmap (map (fmap fromConfiguredId)) $
642+ pkgExeDependencies pkg
643+
644+ fromConfiguredId :: ConfiguredId -> UnitId
645+ fromConfiguredId = newSimpleUnitId . confInstId
646+
647+ --- | Library dependencies.
648+ ---
649+ --- These are identified by their 'ConfiguredId' and are passed to the @Setup@
650+ --- script via @--dependency@ or @--promised-dependency@.
651+ --- Note that setup dependencies (meaning the library dependencies of the setup
652+ -- script) are not included here, they are handled separately.
653+ elabLibDependencies :: ElaboratedConfiguredPackage -> [(WithStage ConfiguredId , Bool )]
654+ elabLibDependencies elab =
655+ -- Library dependencies are always in the same stage as the component/package we are
656+ -- building.
657+ map (\ (cid, promised) -> (WithStage (elabStage elab) cid, promised)) $
648658 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 _ -> []
659+ ElabPackage pkg ->
660+ ordNub $ CD. nonSetupDeps (pkgLibDependencies pkg)
661+ ElabComponent comp ->
662+ compLibDependencies comp
653663
654664-- | The executable dependencies (i.e., the executables we depend on);
655665-- these are the executables we must add to the PATH before we invoke
@@ -658,7 +668,7 @@ elabExeDependencies :: ElaboratedConfiguredPackage -> [WithStage ComponentId]
658668elabExeDependencies elab =
659669 map (fmap confInstId) $
660670 case elabPkgOrComp elab of
661- ElabPackage pkg -> CD. nonSetupDeps (pkgExeDependencies pkg)
671+ ElabPackage pkg -> ordNub $ CD. nonSetupDeps (pkgExeDependencies pkg)
662672 ElabComponent comp -> compExeDependencies comp
663673
664674-- | This returns the paths of all the executables we depend on; we
@@ -668,14 +678,33 @@ elabExeDependencies elab =
668678elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath ]
669679elabExeDependencyPaths elab =
670680 case elabPkgOrComp elab of
671- ElabPackage pkg -> map snd $ CD. nonSetupDeps (pkgExeDependencyPaths pkg)
681+ ElabPackage pkg -> ordNub $ map snd $ CD. nonSetupDeps (pkgExeDependencyPaths pkg)
672682 ElabComponent comp -> map snd (compExeDependencyPaths comp)
673683
674684elabPkgConfigDependencies :: ElaboratedConfiguredPackage -> [(PkgconfigName , Maybe PkgconfigVersion )]
675- elabPkgConfigDependencies ElaboratedConfiguredPackage {elabPkgOrComp = ElabPackage pkg} =
676- pkgPkgConfigDependencies pkg
677- elabPkgConfigDependencies ElaboratedConfiguredPackage {elabPkgOrComp = ElabComponent comp} =
678- compPkgConfigDependencies comp
685+ elabPkgConfigDependencies elab =
686+ case elabPkgOrComp elab of
687+ ElabPackage pkg -> pkgPkgConfigDependencies pkg
688+ ElabComponent comp -> compPkgConfigDependencies comp
689+
690+ -- | The setup dependencies (i.e. the library dependencies of the setup executable)
691+ -- Note that it is not legal for setup scripts to have executable dependencies.
692+ -- TODO: In that case we should probably not have this function at all, and
693+ -- only use pkgSetupLibDependencies
694+ elabSetupLibDependencies :: ElaboratedConfiguredPackage -> [WithStage ConfiguredId ]
695+ elabSetupLibDependencies elab =
696+ case elabPkgOrComp elab of
697+ ElabPackage pkg -> pkgSetupLibDependencies pkg
698+ -- Custom setups not supported for components.
699+ ElabComponent _ -> []
700+
701+ pkgSetupLibDependencies :: ElaboratedPackage -> [WithStage ConfiguredId ]
702+ pkgSetupLibDependencies pkg =
703+ map (WithStage stage . fst ) $
704+ ordNub $
705+ CD. setupDeps (pkgLibDependencies pkg)
706+ where
707+ stage = prevStage (pkgStage pkg)
679708
680709-- | The cache files of all our inplace dependencies which,
681710-- when updated, require us to rebuild. See #4202 for
@@ -750,7 +779,7 @@ data ElaboratedComponent = ElaboratedComponent
750779 , compOrderLibDependencies :: [UnitId ]
751780 -- ^ The UnitIds of the libraries (identifying elaborated packages/
752781 -- components) that must be built before this project. This
753- -- is used purely for ordering purposes. It can contain both
782+ -- is used purely for ordering purposes. It can contain both
754783 -- references to definite and indefinite packages; an indefinite
755784 -- UnitId indicates that we must typecheck that indefinite package
756785 -- before we can build this one.
@@ -833,17 +862,6 @@ whyNotPerComponent = \case
833862 CuzNoBuildableComponents -> " there are no buildable components"
834863 CuzDisablePerComponent -> " you passed --disable-per-component"
835864
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- <> fmap
844- (map (fmap (newSimpleUnitId . confInstId)))
845- (pkgExeDependencies pkg)
846-
847865-- | This is used in the install plan to indicate how the package will be
848866-- built.
849867data BuildStyle
0 commit comments