@@ -52,6 +52,7 @@ import Development.IDE.Core.RuleTypes
52
52
import Development.IDE.Core.Shake hiding (Log , Priority ,
53
53
knownTargets , withHieDb )
54
54
import qualified Development.IDE.GHC.Compat as Compat
55
+ import qualified Development.IDE.GHC.Compat.Util as Compat
55
56
import Development.IDE.GHC.Compat.Core hiding (Target ,
56
57
TargetFile , TargetModule ,
57
58
Var , Warning , getOptions )
@@ -122,10 +123,11 @@ import GHC.Data.Bag
122
123
import GHC.Driver.Env (hsc_all_home_unit_ids )
123
124
import GHC.Driver.Errors.Types
124
125
import GHC.Driver.Make (checkHomeUnitsClosed )
125
- import GHC.Types.Error (errMsgDiagnostic )
126
+ import GHC.Types.Error (errMsgDiagnostic , singleMessage )
126
127
import GHC.Unit.State
127
128
#endif
128
129
130
+ import GHC.Data.Graph.Directed
129
131
import GHC.ResponseFile
130
132
131
133
data Log
@@ -810,6 +812,65 @@ setNameCache :: IORef NameCache -> HscEnv -> HscEnv
810
812
#endif
811
813
setNameCache nc hsc = hsc { hsc_NC = nc }
812
814
815
+ #if MIN_VERSION_ghc(9,3,0)
816
+ -- This function checks the important property that if both p and q are home units
817
+ -- then any dependency of p, which transitively depends on q is also a home unit.
818
+ -- GHC had an implementation of this function, but it was horribly inefficient
819
+ -- We should move back to the GHC implementation on compilers where
820
+ -- https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12162 is included
821
+ checkHomeUnitsClosed' :: UnitEnv -> OS. Set UnitId -> [DriverMessages ]
822
+ checkHomeUnitsClosed' ue home_id_set
823
+ | OS. null bad_unit_ids = []
824
+ | otherwise = [singleMessage $ GHC. mkPlainErrorMsgEnvelope rootLoc $ DriverHomePackagesNotClosed (OS. toList bad_unit_ids)]
825
+ where
826
+ bad_unit_ids = upwards_closure OS. \\ home_id_set
827
+ rootLoc = mkGeneralSrcSpan (Compat. fsLit " <command line>" )
828
+
829
+ graph :: Graph (Node UnitId UnitId )
830
+ graph = graphFromEdgedVerticesUniq graphNodes
831
+
832
+ -- downwards closure of graph
833
+ downwards_closure
834
+ = graphFromEdgedVerticesUniq [ DigraphNode uid uid (OS. toList deps)
835
+ | (uid, deps) <- Map. toList (allReachable graph node_key)]
836
+
837
+ inverse_closure = transposeG downwards_closure
838
+
839
+ upwards_closure = OS. fromList $ map node_key $ reachablesG inverse_closure [DigraphNode uid uid [] | uid <- OS. toList home_id_set]
840
+
841
+ all_unit_direct_deps :: UniqMap UnitId (OS. Set UnitId )
842
+ all_unit_direct_deps
843
+ = unitEnv_foldWithKey go emptyUniqMap $ ue_home_unit_graph ue
844
+ where
845
+ go rest this this_uis =
846
+ plusUniqMap_C OS. union
847
+ (addToUniqMap_C OS. union external_depends this (OS. fromList $ this_deps))
848
+ rest
849
+ where
850
+ external_depends = mapUniqMap (OS. fromList . unitDepends)
851
+ #if !MIN_VERSION_ghc(9,7,0)
852
+ $ listToUniqMap $ Map. toList
853
+ #endif
854
+
855
+ $ unitInfoMap this_units
856
+ this_units = homeUnitEnv_units this_uis
857
+ this_deps = [ Compat. toUnitId unit | (unit,Just _) <- explicitUnits this_units]
858
+
859
+ graphNodes :: [Node UnitId UnitId ]
860
+ graphNodes = go OS. empty home_id_set
861
+ where
862
+ go done todo
863
+ = case OS. minView todo of
864
+ Nothing -> []
865
+ Just (uid, todo')
866
+ | OS. member uid done -> go done todo'
867
+ | otherwise -> case lookupUniqMap all_unit_direct_deps uid of
868
+ Nothing -> pprPanic " uid not found" (Compat. ppr (uid, all_unit_direct_deps))
869
+ Just depends ->
870
+ let todo'' = (depends OS. \\ done) `OS.union` todo'
871
+ in DigraphNode uid uid (OS. toList depends) : go (OS. insert uid done) todo''
872
+ #endif
873
+
813
874
-- | Create a mapping from FilePaths to HscEnvEqs
814
875
-- This combines all the components we know about into
815
876
-- an appropriate session, which is a multi component
@@ -838,11 +899,7 @@ newComponentCache recorder exts cradlePath _cfp hsc_env old_cis new_cis = do
838
899
Compat. initUnits dfs hsc_env
839
900
840
901
#if MIN_VERSION_ghc(9,3,0)
841
- let closure_errs = checkHomeUnitsClosed (hsc_unit_env hscEnv') (hsc_all_home_unit_ids hscEnv') pkg_deps
842
- pkg_deps = do
843
- home_unit_id <- uids
844
- home_unit_env <- maybeToList $ unitEnv_lookup_maybe home_unit_id $ hsc_HUG hscEnv'
845
- map (home_unit_id,) (map (Compat. toUnitId . fst ) $ explicitUnits $ homeUnitEnv_units home_unit_env)
902
+ let closure_errs = checkHomeUnitsClosed' (hsc_unit_env hscEnv') (hsc_all_home_unit_ids hscEnv')
846
903
multi_errs = map (ideErrorWithSource (Just " cradle" ) (Just DiagnosticSeverity_Warning ) _cfp . T. pack . Compat. printWithoutUniques) closure_errs
847
904
bad_units = OS. fromList $ concat $ do
848
905
x <- bagToList $ mapBag errMsgDiagnostic $ unionManyBags $ map Compat. getMessages closure_errs
0 commit comments