@@ -193,8 +193,8 @@ haddockWithGhc ghc args = handleTopExceptions $ do
193
193
unit_state <- hsc_units <$> getSession
194
194
195
195
forM_ (optShowInterfaceFile flags) $ \ path -> liftIO $ do
196
- mIfaceFile <- readInterfaceFiles freshNameCache [((" " , Nothing ), path)] noChecks
197
- forM_ mIfaceFile $ \ (_,_, ifaceFile) -> do
196
+ mIfaceFile <- readInterfaceFiles freshNameCache [((" " , Nothing ), Visible , path)] noChecks
197
+ forM_ mIfaceFile $ \ (_,_,_, ifaceFile) -> do
198
198
putMsg logger dflags $ renderJson (jsonInterfaceFile ifaceFile)
199
199
200
200
if not (null files) then do
@@ -254,35 +254,35 @@ withGhc flags action = do
254
254
255
255
256
256
readPackagesAndProcessModules :: [Flag ] -> [String ]
257
- -> Ghc ([(DocPaths , FilePath , InterfaceFile )], [Interface ], LinkEnv )
257
+ -> Ghc ([(DocPaths , Visibility , FilePath , InterfaceFile )], [Interface ], LinkEnv )
258
258
readPackagesAndProcessModules flags files = do
259
259
-- Get packages supplied with --read-interface.
260
260
let noChecks = Flag_BypassInterfaceVersonCheck `elem` flags
261
261
packages <- readInterfaceFiles nameCacheFromGhc (readIfaceArgs flags) noChecks
262
262
263
263
-- Create the interfaces -- this is the core part of Haddock.
264
- let ifaceFiles = map (\ (_, _, ifaceFile) -> ifaceFile) packages
264
+ let ifaceFiles = map (\ (_, _, _, ifaceFile) -> ifaceFile) packages
265
265
(ifaces, homeLinks) <- processModules (verbosity flags) files flags ifaceFiles
266
266
267
267
return (packages, ifaces, homeLinks)
268
268
269
269
270
270
renderStep :: Logger -> DynFlags -> UnitState -> [Flag ] -> SinceQual -> QualOption
271
- -> [(DocPaths , FilePath , InterfaceFile )] -> [Interface ] -> IO ()
271
+ -> [(DocPaths , Visibility , FilePath , InterfaceFile )] -> [Interface ] -> IO ()
272
272
renderStep logger dflags unit_state flags sinceQual nameQual pkgs interfaces = do
273
- updateHTMLXRefs (map (\ (docPath, _ifaceFilePath, ifaceFile) ->
273
+ updateHTMLXRefs (map (\ (docPath, _ifaceFilePath, _showModules, ifaceFile) ->
274
274
( case baseUrl flags of
275
275
Nothing -> fst docPath
276
276
Just url -> url </> packageName (ifUnitId ifaceFile)
277
277
, ifaceFile)) pkgs)
278
278
let
279
279
installedIfaces =
280
280
concatMap
281
- (\ (_, ifaceFilePath, ifaceFile)
282
- -> (ifaceFilePath,) <$> ifInstalledIfaces ifaceFile)
281
+ (\ (_, showModules, ifaceFilePath, ifaceFile)
282
+ -> (showModules, ifaceFilePath,) <$> ifInstalledIfaces ifaceFile)
283
283
pkgs
284
284
extSrcMap = Map. fromList $ do
285
- ((_, Just path), _, ifile) <- pkgs
285
+ ((_, Just path), _, _, ifile) <- pkgs
286
286
iface <- ifInstalledIfaces ifile
287
287
return (instMod iface, path)
288
288
render logger dflags unit_state flags sinceQual nameQual interfaces installedIfaces extSrcMap
@@ -296,7 +296,7 @@ renderStep logger dflags unit_state flags sinceQual nameQual pkgs interfaces = d
296
296
297
297
-- | Render the interfaces with whatever backend is specified in the flags.
298
298
render :: Logger -> DynFlags -> UnitState -> [Flag ] -> SinceQual -> QualOption -> [Interface ]
299
- -> [(FilePath , InstalledInterface )] -> Map Module FilePath -> IO ()
299
+ -> [(Visibility , FilePath , InstalledInterface )] -> Map Module FilePath -> IO ()
300
300
render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extSrcMap = do
301
301
302
302
let
@@ -318,8 +318,9 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS
318
318
visibleIfaces = [ i | i <- ifaces, OptHide `notElem` ifaceOptions i ]
319
319
320
320
-- /All/ visible interfaces including external package modules.
321
- allIfaces = map toInstalledIface ifaces ++ map snd installedIfaces
322
- allVisibleIfaces = [ i | i <- allIfaces, OptHide `notElem` instOptions i ]
321
+ allIfaces = map ((Visible ,) . toInstalledIface) ifaces
322
+ ++ map (\ (showModules,_,iface) -> (showModules,iface)) installedIfaces
323
+ allVisibleIfaces = [ i | (Visible , i) <- allIfaces, OptHide `notElem` instOptions i ]
323
324
324
325
pkgMod = fmap ifaceMod (listToMaybe ifaces)
325
326
pkgKey = fmap moduleUnit pkgMod
@@ -363,7 +364,7 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS
363
364
sourceUrls' = (srcBase, srcModule', pkgSrcMap', pkgSrcLMap')
364
365
365
366
installedMap :: Map Module InstalledInterface
366
- installedMap = Map. fromList [ (unwire (instMod iface), iface) | (_, iface) <- installedIfaces ]
367
+ installedMap = Map. fromList [ (unwire (instMod iface), iface) | (_, _, iface) <- installedIfaces ]
367
368
368
369
-- The user gives use base-4.9.0.0, but the InstalledInterface
369
370
-- records the *wired in* identity base. So untranslate it
@@ -419,7 +420,7 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS
419
420
ppJsonIndex odir sourceUrls' opt_wiki_urls
420
421
unicode Nothing qual
421
422
ifaces
422
- (nub $ map fst installedIfaces)
423
+ (nub $ map ( \ (_,a,_) -> a) installedIfaces)
423
424
424
425
when (Flag_Html `elem` flags) $ do
425
426
withTiming logger dflags' " ppHtml" (const () ) $ do
@@ -478,21 +479,21 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS
478
479
479
480
readInterfaceFiles :: MonadIO m
480
481
=> NameCacheAccessor m
481
- -> [(DocPaths , FilePath )]
482
+ -> [(DocPaths , Visibility , FilePath )]
482
483
-> Bool
483
- -> m [(DocPaths , FilePath , InterfaceFile )]
484
+ -> m [(DocPaths , Visibility , FilePath , InterfaceFile )]
484
485
readInterfaceFiles name_cache_accessor pairs bypass_version_check = do
485
486
catMaybes `liftM` mapM ({-# SCC readInterfaceFile #-} tryReadIface) pairs
486
487
where
487
488
-- try to read an interface, warn if we can't
488
- tryReadIface (paths, file) =
489
+ tryReadIface (paths, showModules, file) =
489
490
readInterfaceFile name_cache_accessor file bypass_version_check >>= \ case
490
491
Left err -> liftIO $ do
491
492
putStrLn (" Warning: Cannot read " ++ file ++ " :" )
492
493
putStrLn (" " ++ err)
493
494
putStrLn " Skipping this interface."
494
495
return Nothing
495
- Right f -> return (Just (paths, file, f))
496
+ Right f -> return (Just (paths, showModules, file, f))
496
497
497
498
498
499
-------------------------------------------------------------------------------
0 commit comments