Skip to content
This repository was archived by the owner on Aug 3, 2024. It is now read-only.

Commit c0f06d5

Browse files
authored
Allow to hide interfaces when rendering multiple components (#1487)
This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package.
1 parent 2c27d15 commit c0f06d5

File tree

2 files changed

+38
-23
lines changed

2 files changed

+38
-23
lines changed

haddock-api/src/Haddock.hs

Lines changed: 19 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -193,8 +193,8 @@ haddockWithGhc ghc args = handleTopExceptions $ do
193193
unit_state <- hsc_units <$> getSession
194194

195195
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
198198
putMsg logger dflags $ renderJson (jsonInterfaceFile ifaceFile)
199199

200200
if not (null files) then do
@@ -254,35 +254,35 @@ withGhc flags action = do
254254

255255

256256
readPackagesAndProcessModules :: [Flag] -> [String]
257-
-> Ghc ([(DocPaths, FilePath, InterfaceFile)], [Interface], LinkEnv)
257+
-> Ghc ([(DocPaths, Visibility, FilePath, InterfaceFile)], [Interface], LinkEnv)
258258
readPackagesAndProcessModules flags files = do
259259
-- Get packages supplied with --read-interface.
260260
let noChecks = Flag_BypassInterfaceVersonCheck `elem` flags
261261
packages <- readInterfaceFiles nameCacheFromGhc (readIfaceArgs flags) noChecks
262262

263263
-- Create the interfaces -- this is the core part of Haddock.
264-
let ifaceFiles = map (\(_, _, ifaceFile) -> ifaceFile) packages
264+
let ifaceFiles = map (\(_, _, _, ifaceFile) -> ifaceFile) packages
265265
(ifaces, homeLinks) <- processModules (verbosity flags) files flags ifaceFiles
266266

267267
return (packages, ifaces, homeLinks)
268268

269269

270270
renderStep :: Logger -> DynFlags -> UnitState -> [Flag] -> SinceQual -> QualOption
271-
-> [(DocPaths, FilePath, InterfaceFile)] -> [Interface] -> IO ()
271+
-> [(DocPaths, Visibility, FilePath, InterfaceFile)] -> [Interface] -> IO ()
272272
renderStep logger dflags unit_state flags sinceQual nameQual pkgs interfaces = do
273-
updateHTMLXRefs (map (\(docPath, _ifaceFilePath, ifaceFile) ->
273+
updateHTMLXRefs (map (\(docPath, _ifaceFilePath, _showModules, ifaceFile) ->
274274
( case baseUrl flags of
275275
Nothing -> fst docPath
276276
Just url -> url </> packageName (ifUnitId ifaceFile)
277277
, ifaceFile)) pkgs)
278278
let
279279
installedIfaces =
280280
concatMap
281-
(\(_, ifaceFilePath, ifaceFile)
282-
-> (ifaceFilePath,) <$> ifInstalledIfaces ifaceFile)
281+
(\(_, showModules, ifaceFilePath, ifaceFile)
282+
-> (showModules,ifaceFilePath,) <$> ifInstalledIfaces ifaceFile)
283283
pkgs
284284
extSrcMap = Map.fromList $ do
285-
((_, Just path), _, ifile) <- pkgs
285+
((_, Just path), _, _, ifile) <- pkgs
286286
iface <- ifInstalledIfaces ifile
287287
return (instMod iface, path)
288288
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
296296

297297
-- | Render the interfaces with whatever backend is specified in the flags.
298298
render :: Logger -> DynFlags -> UnitState -> [Flag] -> SinceQual -> QualOption -> [Interface]
299-
-> [(FilePath, InstalledInterface)] -> Map Module FilePath -> IO ()
299+
-> [(Visibility, FilePath, InstalledInterface)] -> Map Module FilePath -> IO ()
300300
render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extSrcMap = do
301301

302302
let
@@ -318,8 +318,9 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS
318318
visibleIfaces = [ i | i <- ifaces, OptHide `notElem` ifaceOptions i ]
319319

320320
-- /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 ]
323324

324325
pkgMod = fmap ifaceMod (listToMaybe ifaces)
325326
pkgKey = fmap moduleUnit pkgMod
@@ -363,7 +364,7 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS
363364
sourceUrls' = (srcBase, srcModule', pkgSrcMap', pkgSrcLMap')
364365

365366
installedMap :: Map Module InstalledInterface
366-
installedMap = Map.fromList [ (unwire (instMod iface), iface) | (_, iface) <- installedIfaces ]
367+
installedMap = Map.fromList [ (unwire (instMod iface), iface) | (_, _, iface) <- installedIfaces ]
367368

368369
-- The user gives use base-4.9.0.0, but the InstalledInterface
369370
-- records the *wired in* identity base. So untranslate it
@@ -419,7 +420,7 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS
419420
ppJsonIndex odir sourceUrls' opt_wiki_urls
420421
unicode Nothing qual
421422
ifaces
422-
(nub $ map fst installedIfaces)
423+
(nub $ map (\(_,a,_) -> a) installedIfaces)
423424

424425
when (Flag_Html `elem` flags) $ do
425426
withTiming logger dflags' "ppHtml" (const ()) $ do
@@ -478,21 +479,21 @@ render logger dflags unit_state flags sinceQual qual ifaces installedIfaces extS
478479

479480
readInterfaceFiles :: MonadIO m
480481
=> NameCacheAccessor m
481-
-> [(DocPaths, FilePath)]
482+
-> [(DocPaths, Visibility, FilePath)]
482483
-> Bool
483-
-> m [(DocPaths, FilePath, InterfaceFile)]
484+
-> m [(DocPaths, Visibility, FilePath, InterfaceFile)]
484485
readInterfaceFiles name_cache_accessor pairs bypass_version_check = do
485486
catMaybes `liftM` mapM ({-# SCC readInterfaceFile #-} tryReadIface) pairs
486487
where
487488
-- try to read an interface, warn if we can't
488-
tryReadIface (paths, file) =
489+
tryReadIface (paths, showModules, file) =
489490
readInterfaceFile name_cache_accessor file bypass_version_check >>= \case
490491
Left err -> liftIO $ do
491492
putStrLn ("Warning: Cannot read " ++ file ++ ":")
492493
putStrLn (" " ++ err)
493494
putStrLn "Skipping this interface."
494495
return Nothing
495-
Right f -> return (Just (paths, file, f))
496+
Right f -> return (Just (paths, showModules, file, f))
496497

497498

498499
-------------------------------------------------------------------------------

haddock-api/src/Haddock/Options.hs

Lines changed: 19 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@
1515
module Haddock.Options (
1616
parseHaddockOpts,
1717
Flag(..),
18+
Visibility(..),
1819
getUsage,
1920
optTitle,
2021
outputDir,
@@ -361,18 +362,31 @@ ghcFlags flags = [ option | Flag_OptGhc option <- flags ]
361362
reexportFlags :: [Flag] -> [String]
362363
reexportFlags flags = [ option | Flag_Reexport option <- flags ]
363364

365+
data Visibility = Visible | Hidden
366+
deriving (Eq, Show)
364367

365-
readIfaceArgs :: [Flag] -> [(DocPaths, FilePath)]
368+
readIfaceArgs :: [Flag] -> [(DocPaths, Visibility, FilePath)]
366369
readIfaceArgs flags = [ parseIfaceOption s | Flag_ReadInterface s <- flags ]
367370
where
368-
parseIfaceOption :: String -> (DocPaths, FilePath)
371+
parseIfaceOption :: String -> (DocPaths, Visibility, FilePath)
369372
parseIfaceOption str =
370373
case break (==',') str of
371374
(fpath, ',':rest) ->
372375
case break (==',') rest of
373-
(src, ',':file) -> ((fpath, Just src), file)
374-
(file, _) -> ((fpath, Nothing), file)
375-
(file, _) -> (("", Nothing), file)
376+
(src, ',':rest') ->
377+
let src' = case src of
378+
"" -> Nothing
379+
_ -> Just src
380+
in
381+
case break (==',') rest' of
382+
(visibility, ',':file) | visibility == "hidden" ->
383+
((fpath, src'), Hidden, file)
384+
| otherwise ->
385+
((fpath, src'), Visible, file)
386+
(file, _) ->
387+
((fpath, src'), Visible, file)
388+
(file, _) -> ((fpath, Nothing), Visible, file)
389+
(file, _) -> (("", Nothing), Visible, file)
376390

377391

378392
-- | Like 'listToMaybe' but returns the last element instead of the first.

0 commit comments

Comments
 (0)