Patrick pushed to branch wip/T26118-remove-hptallfaminstances-usage-during-upsweep at Glasgow Haskell Compiler / GHC

Commits:

2 changed files:

Changes:

  • compiler/GHC/Unit/Home/Graph.hs
    ... ... @@ -43,7 +43,6 @@ module GHC.Unit.Home.Graph
    43 43
     
    
    44 44
       -- * Very important queries
    
    45 45
       , allInstances
    
    46
    -  , allFamInstances
    
    47 46
       , allAnns
    
    48 47
       , allCompleteSigs
    
    49 48
     
    
    ... ... @@ -110,10 +109,6 @@ allInstances hug = foldr go (pure (emptyInstEnv, [])) hug where
    110 109
       go hue = liftA2 (\(a,b) (a',b') -> (a `unionInstEnv` a', b ++ b'))
    
    111 110
                       (hptAllInstances (homeUnitEnv_hpt hue))
    
    112 111
     
    
    113
    -allFamInstances :: HomeUnitGraph -> IO (ModuleEnv FamInstEnv)
    
    114
    -allFamInstances hug = foldr go (pure emptyModuleEnv) hug where
    
    115
    -  go hue = liftA2 plusModuleEnv (hptAllFamInstances (homeUnitEnv_hpt hue))
    
    116
    -
    
    117 112
     allAnns :: HomeUnitGraph -> IO AnnEnv
    
    118 113
     allAnns hug = foldr go (pure emptyAnnEnv) hug where
    
    119 114
       go hue = liftA2 plusAnnEnv (hptAllAnnotations (homeUnitEnv_hpt hue))
    

  • compiler/GHC/Unit/Home/PackageTable.hs
    ... ... @@ -41,7 +41,6 @@ module GHC.Unit.Home.PackageTable
    41 41
         -- * Queries about home modules
    
    42 42
       , hptCompleteSigs
    
    43 43
       , hptAllInstances
    
    44
    -  , hptAllFamInstances
    
    45 44
       , hptAllAnnotations
    
    46 45
     
    
    47 46
         -- ** More Traversal-based queries
    
    ... ... @@ -208,14 +207,6 @@ hptAllInstances hpt = do
    208 207
       let (insts, famInsts) = unzip hits
    
    209 208
       return (foldl' unionInstEnv emptyInstEnv insts, concat famInsts)
    
    210 209
     
    
    211
    --- | Find all the family instance declarations from the HPT
    
    212
    -hptAllFamInstances :: HomePackageTable -> IO (ModuleEnv FamInstEnv)
    
    213
    -hptAllFamInstances = fmap mkModuleEnv . concatHpt (\hmi -> [(hmiModule hmi, hmiFamInstEnv hmi)])
    
    214
    -  where
    
    215
    -    hmiModule     = mi_module . hm_iface
    
    216
    -    hmiFamInstEnv = extendFamInstEnvList emptyFamInstEnv
    
    217
    -                      . md_fam_insts . hm_details
    
    218
    -
    
    219 210
     -- | All annotations from the HPT
    
    220 211
     hptAllAnnotations :: HomePackageTable -> IO AnnEnv
    
    221 212
     hptAllAnnotations = fmap mkAnnEnv . concatHpt (md_anns . hm_details)