Torsten Schmits pushed to branch wip/torsten.schmits/worker-debug at Glasgow Haskell Compiler / GHC

Commits:

1 changed file:

Changes:

  • compiler/GHC/Linker/Deps.hs
    ... ... @@ -156,9 +156,10 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
    156 156
               listToUDFM [(moduleName (mi_module (hm_iface m)), m) | m <- mmods]
    
    157 157
             link_libs =
    
    158 158
               uniqDSetToList (unionManyUniqDSets (init_pkg_set : pkgs))
    
    159
    +      deps <- oneshot_deps opts link_libs
    
    159 160
           pure $
    
    160 161
             LinkModules (LinkHomeModule <$> link_mods) :
    
    161
    -        (LinkLibrary <$> link_libs)
    
    162
    +        deps
    
    162 163
     
    
    163 164
         -- This code is used in `--make` mode to calculate the home package and unit dependencies
    
    164 165
         -- for a set of modules.
    
    ... ... @@ -168,15 +169,15 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
    168 169
     
    
    169 170
         -- It is also a matter of correctness to use the module graph so that dependencies between home units
    
    170 171
         -- is resolved correctly.
    
    171
    -    make_deps_loop :: (UniqDSet UnitId, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet UnitId, Set.Set NodeKey)
    
    172
    +    make_deps_loop :: (UniqDSet Module, Set.Set NodeKey) -> [ModNodeKeyWithUid] -> (UniqDSet Module, Set.Set NodeKey)
    
    172 173
         make_deps_loop found [] = found
    
    173 174
         make_deps_loop found@(found_units, found_mods) (nk:nexts)
    
    174 175
           | NodeKey_Module nk `Set.member` found_mods = make_deps_loop found nexts
    
    175 176
           | otherwise =
    
    176 177
             case fmap mkNodeKey <$> mgReachable mod_graph (NodeKey_Module nk) of
    
    177 178
               Nothing ->
    
    178
    -              let (ModNodeKeyWithUid _ uid) = nk
    
    179
    -              in make_deps_loop (addOneToUniqDSet found_units uid, found_mods) nexts
    
    179
    +              let (ModNodeKeyWithUid GWIB {gwib_mod} uid) = nk
    
    180
    +              in make_deps_loop (addOneToUniqDSet found_units (Module (RealUnit (Definite uid)) gwib_mod), found_mods) nexts
    
    180 181
               Just trans_deps ->
    
    181 182
                 let deps = Set.insert (NodeKey_Module nk) (Set.fromList trans_deps)
    
    182 183
                     -- See #936 and the ghci.prog007 test for why we have to continue traversing through
    
    ... ... @@ -195,7 +196,7 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
    195 196
               let iface = hm_iface hmi
    
    196 197
               case mi_hsc_src iface of
    
    197 198
                 HsBootFile -> throwProgramError opts $ link_boot_mod_error (mi_module iface)
    
    198
    -            _ -> pure (mkUniqDSet $ Set.toList $ dep_direct_pkgs (mi_deps iface), hmi)
    
    199
    +            _ -> pure ( mkUniqDSet $ [usg_mod | UsagePackageModule {usg_mod} <- mi_usages iface], hmi)
    
    199 200
             Nothing -> throwProgramError opts $
    
    200 201
               text "getLinkDeps: Home module not loaded" <+> ppr (gwib_mod gwib) <+> ppr uid
    
    201 202