@@ -52,6 +52,7 @@ import Development.IDE.Core.RuleTypes
5252import Development.IDE.Core.Shake hiding (Log , Priority ,
5353 knownTargets , withHieDb )
5454import qualified Development.IDE.GHC.Compat as Compat
55+ import qualified Development.IDE.GHC.Compat.Util as Compat
5556import Development.IDE.GHC.Compat.Core hiding (Target ,
5657 TargetFile , TargetModule ,
5758 Var , Warning , getOptions )
@@ -122,10 +123,11 @@ import GHC.Data.Bag
122123import GHC.Driver.Env (hsc_all_home_unit_ids )
123124import GHC.Driver.Errors.Types
124125import GHC.Driver.Make (checkHomeUnitsClosed )
125- import GHC.Types.Error (errMsgDiagnostic )
126+ import GHC.Types.Error (errMsgDiagnostic , singleMessage )
126127import GHC.Unit.State
127128#endif
128129
130+ import GHC.Data.Graph.Directed
129131import GHC.ResponseFile
130132
131133data Log
@@ -798,6 +800,58 @@ setNameCache :: IORef NameCache -> HscEnv -> HscEnv
798800#endif
799801setNameCache nc hsc = hsc { hsc_NC = nc }
800802
803+ -- This function checks then important property that if both p and q are home units
804+ -- then any dependency of p, which transitively depends on q is also a home unit.
805+ -- GHC had an implementation of this function, but it was horribly inefficient
806+ -- We should move back to the GHC implementation on compilers where
807+ -- https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12162 is included
808+ checkHomeUnitsClosed' :: UnitEnv -> OS. Set UnitId -> [DriverMessages ]
809+ checkHomeUnitsClosed' ue home_id_set
810+ | OS. null bad_unit_ids = []
811+ | otherwise = [singleMessage $ GHC. mkPlainErrorMsgEnvelope rootLoc $ DriverHomePackagesNotClosed (OS. toList bad_unit_ids)]
812+ where
813+ bad_unit_ids = upwards_closure OS. \\ home_id_set
814+ rootLoc = mkGeneralSrcSpan (Compat. fsLit " <command line>" )
815+
816+ graph :: Graph (Node UnitId UnitId )
817+ graph = graphFromEdgedVerticesUniq graphNodes
818+
819+ -- downwards closure of graph
820+ downwards_closure
821+ = graphFromEdgedVerticesUniq [ DigraphNode uid uid (OS. toList deps)
822+ | (uid, deps) <- Map. toList (allReachable graph node_key)]
823+
824+ inverse_closure = transposeG downwards_closure
825+
826+ upwards_closure = OS. fromList $ map node_key $ reachablesG inverse_closure [DigraphNode uid uid [] | uid <- OS. toList home_id_set]
827+
828+ all_unit_direct_deps :: UniqMap UnitId (OS. Set UnitId )
829+ all_unit_direct_deps
830+ = unitEnv_foldWithKey go emptyUniqMap $ ue_home_unit_graph ue
831+ where
832+ go rest this this_uis =
833+ plusUniqMap_C OS. union
834+ (addToUniqMap_C OS. union external_depends this (OS. fromList $ this_deps))
835+ rest
836+ where
837+ external_depends = mapUniqMap (OS. fromList . unitDepends) (unitInfoMap this_units)
838+ this_units = homeUnitEnv_units this_uis
839+ this_deps = [ Compat. toUnitId unit | (unit,Just _) <- explicitUnits this_units]
840+
841+ graphNodes :: [Node UnitId UnitId ]
842+ graphNodes = go OS. empty home_id_set
843+ where
844+ go done todo
845+ = case OS. minView todo of
846+ Nothing -> []
847+ Just (uid, todo')
848+ | OS. member uid done -> go done todo'
849+ | otherwise -> case lookupUniqMap all_unit_direct_deps uid of
850+ Nothing -> pprPanic " uid not found" (Compat. ppr (uid, all_unit_direct_deps))
851+ Just depends ->
852+ let todo'' = (depends OS. \\ done) `OS.union` todo'
853+ in DigraphNode uid uid (OS. toList depends) : go (OS. insert uid done) todo''
854+
801855-- | Create a mapping from FilePaths to HscEnvEqs
802856-- This combines all the components we know about into
803857-- an appropriate session, which is a multi component
@@ -826,11 +880,7 @@ newComponentCache recorder exts cradlePath _cfp hsc_env old_cis new_cis = do
826880 Compat. initUnits dfs hsc_env
827881
828882#if MIN_VERSION_ghc(9,3,0)
829- let closure_errs = checkHomeUnitsClosed (hsc_unit_env hscEnv') (hsc_all_home_unit_ids hscEnv') pkg_deps
830- pkg_deps = do
831- home_unit_id <- uids
832- home_unit_env <- maybeToList $ unitEnv_lookup_maybe home_unit_id $ hsc_HUG hscEnv'
833- map (home_unit_id,) (map (Compat. toUnitId . fst ) $ explicitUnits $ homeUnitEnv_units home_unit_env)
883+ let closure_errs = checkHomeUnitsClosed' (hsc_unit_env hscEnv') (hsc_all_home_unit_ids hscEnv')
834884 multi_errs = map (ideErrorWithSource (Just " cradle" ) (Just DiagnosticSeverity_Warning ) _cfp . T. pack . Compat. printWithoutUniques) closure_errs
835885 bad_units = OS. fromList $ concat $ do
836886 x <- bagToList $ mapBag errMsgDiagnostic $ unionManyBags $ map Compat. getMessages closure_errs
0 commit comments