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

Commit 3b746c8

Browse files
harpocratessjakobi
authored andcommitted
Remove unused arguments and fields (#911)
1 parent c798cf4 commit 3b746c8

File tree

2 files changed

+24
-55
lines changed

2 files changed

+24
-55
lines changed

haddock-api/src/Haddock/Interface/Create.hs

Lines changed: 24 additions & 50 deletions
Original file line numberDiff line numberDiff line change
@@ -110,8 +110,7 @@ createInterface mod_iface flags modMap instIfaceMap = do
110110
++ map getName fam_instances
111111
instanceMap = M.fromList (map (getSrcSpan &&& id) localInsts)
112112

113-
let maps = (docMap, argMap, instanceMap)
114-
allWarnings = M.unions (warningMap : map ifaceWarningMap (M.elems modMap))
113+
let allWarnings = M.unions (warningMap : map ifaceWarningMap (M.elems modMap))
115114

116115
-- Locations of all TH splices
117116
-- TODO: We use the splice info in 'Haddock.Backends.Xhtml.Layout.links' to
@@ -122,12 +121,12 @@ createInterface mod_iface flags modMap instIfaceMap = do
122121

123122
-- The MAIN functionality: compute the export items which will
124123
-- each be the actual documentation of this module.
125-
exportItems <- mkExportItems is_sig modMap pkgName mdl sem_mdl allWarnings renamer
126-
exportedNames maps fixMap splices
124+
exportItems <- mkExportItems modMap pkgName mdl allWarnings renamer
125+
docMap argMap fixMap splices
127126
(docs_named_chunks mod_iface_docs)
128127
(docs_structure mod_iface_docs) instIfaceMap
129128

130-
let !visibleNames = mkVisibleNames maps exportItems opts
129+
let !visibleNames = mkVisibleNames instanceMap exportItems opts
131130

132131
-- Measure haddock documentation coverage.
133132
let prunedExportItems0 = pruneExportItems exportItems
@@ -157,7 +156,6 @@ createInterface mod_iface flags modMap instIfaceMap = do
157156
, ifaceRnExportItems = []
158157
, ifaceExports = exportedNames
159158
, ifaceVisibleExports = visibleNames
160-
, ifaceDeclMap = M.empty -- TODO: get rid of this
161159
, ifaceFixMap = fixMap
162160
, ifaceInstances = instances
163161
, ifaceFamInstances = fam_instances
@@ -270,8 +268,6 @@ parseOption "not-home" = return (Just OptNotHome)
270268
parseOption "show-extensions" = return (Just OptShowExtensions)
271269
parseOption other = tell ["Unrecognised option: " ++ other] >> return Nothing
272270

273-
type Maps = (DocMap Name, ArgMap Name, InstMap)
274-
275271
-- | Extract a map of fixity declarations only
276272
mkFixMap :: [Name] -> [(OccName, Fixity)] -> FixMap
277273
mkFixMap exps occFixs =
@@ -281,24 +277,22 @@ mkFixMap exps occFixs =
281277
expsOccEnv = mkOccEnv (map (nameOccName &&& id) exps)
282278

283279
mkExportItems
284-
:: Bool -- is it a signature
285-
-> IfaceMap
280+
:: IfaceMap
286281
-> Maybe Package -- this package
287282
-> Module -- this module
288-
-> Module -- semantic module
289283
-> WarningMap
290284
-> Renamer
291-
-> [Name] -- exported names (orig)
292-
-> Maps
285+
-> DocMap Name -- docs (keyed by 'Name's)
286+
-> ArgMap Name -- docs for arguments (keyed by 'Name's)
293287
-> FixMap
294288
-> [SrcSpan] -- splice locations
295289
-> Map String HsDoc' -- named chunks
296290
-> DocStructure
297291
-> InstIfaceMap
298292
-> ErrMsgGhc [ExportItem GhcRn]
299293
mkExportItems
300-
is_sig modMap mbPkgName thisMod semMod warnings renamer exportedNames
301-
maps fixMap splices namedChunks dsItems instIfaceMap =
294+
modMap mbPkgName thisMod warnings renamer
295+
docMap argMap fixMap splices namedChunks dsItems instIfaceMap =
302296
concat <$> traverse lookupExport dsItems
303297
where
304298
lookupExport :: DocStructureItem -> ErrMsgGhc [ExportItem GhcRn]
@@ -329,23 +323,21 @@ mkExportItems
329323
pure (map ExportModule unrestricted_mods ++ avail_exps)
330324

331325
availExport avail =
332-
availExportItem is_sig modMap thisMod semMod warnings exportedNames
333-
maps fixMap splices instIfaceMap avail
326+
availExportItem modMap thisMod warnings
327+
docMap argMap fixMap splices instIfaceMap avail
334328

335-
availExportItem :: Bool -- is it a signature
336-
-> IfaceMap
329+
availExportItem :: IfaceMap
337330
-> Module -- this module
338-
-> Module -- semantic module
339331
-> WarningMap
340-
-> [Name] -- exported names (orig)
341-
-> Maps
332+
-> DocMap Name -- docs (keyed by 'Name's)
333+
-> ArgMap Name -- docs for arguments (keyed by 'Name's)
342334
-> FixMap
343335
-> [SrcSpan] -- splice locations
344336
-> InstIfaceMap
345337
-> AvailInfo
346338
-> ErrMsgGhc [ExportItem GhcRn]
347-
availExportItem is_sig modMap thisMod semMod warnings exportedNames
348-
(docMap, argMap, _) fixMap splices instIfaceMap
339+
availExportItem modMap thisMod warnings
340+
docMap argMap fixMap splices instIfaceMap
349341
availInfo = declWith availInfo
350342
where
351343
declWith :: AvailInfo -> ErrMsgGhc [ ExportItem GhcRn ]
@@ -482,32 +474,14 @@ hiDecl t = do
482474
lookupDocs :: AvailInfo -> WarningMap -> DocMap Name -> ArgMap Name
483475
-> (DocForDecl Name, [(Name, DocForDecl Name)])
484476
lookupDocs avail warnings docMap argMap =
485-
let n = availName avail in
486-
let lookupArgDoc x = M.findWithDefault M.empty x argMap in
487-
let doc = (lookupDoc n, lookupArgDoc n) in
488-
let subDocs = [ (s, (lookupDoc s, lookupArgDoc s))
489-
| s <- availSubordinates avail
490-
] in
491-
(doc, subDocs)
477+
( lookupDocForDecl (availName avail)
478+
, [ (s, lookupDocForDecl s) | s <- availSubordinates avail ]
479+
)
492480
where
493-
lookupDoc name = Documentation (M.lookup name docMap) (M.lookup name warnings)
494-
481+
lookupDoc x = Documentation (M.lookup x docMap) (M.lookup x warnings)
482+
lookupArgDoc x = M.findWithDefault M.empty x argMap
483+
lookupDocForDecl x = (lookupDoc x, lookupArgDoc x)
495484

496-
-- Note [1]:
497-
------------
498-
-- It is unnecessary to document a subordinate by itself at the top level if
499-
-- any of its parents is also documented. Furthermore, if the subordinate is a
500-
-- record field or a class method, documenting it under its parent
501-
-- indicates its special status.
502-
--
503-
-- A user might expect that it should show up separately, so we issue a
504-
-- warning. It's a fine opportunity to also tell the user she might want to
505-
-- export the subordinate through the parent export item for clarity.
506-
--
507-
-- The code removes top-level subordinates also when the parent is exported
508-
-- through a 'module' export. I think that is fine.
509-
--
510-
-- (For more information, see Trac #69)
511485

512486
-- | Sometimes the declaration we want to export is not the "main" declaration:
513487
-- it might be an individual record selector or a class method. In these
@@ -651,8 +625,8 @@ pruneExportItems = filter hasDoc
651625
hasDoc _ = True
652626

653627

654-
mkVisibleNames :: Maps -> [ExportItem GhcRn] -> [DocOption] -> [Name]
655-
mkVisibleNames (_, _, instMap) exports opts
628+
mkVisibleNames :: InstMap -> [ExportItem GhcRn] -> [DocOption] -> [Name]
629+
mkVisibleNames instMap exports opts
656630
| OptHide `elem` opts = []
657631
| otherwise = let ns = concatMap exportName exports
658632
in seqList ns `seq` ns

haddock-api/src/Haddock/Types.hs

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -93,11 +93,6 @@ data Interface = Interface
9393
-- | Haddock options for this module (prune, not-home, etc).
9494
, ifaceOptions :: ![DocOption]
9595

96-
-- | Declarations originating from the module. Excludes declarations without
97-
-- names (instances and stand-alone documentation comments). Includes
98-
-- names of subordinate declarations mapped to their parent declarations.
99-
, ifaceDeclMap :: !(Map Name [LHsDecl GhcRn])
100-
10196
-- | Documentation of declarations originating from the module (including
10297
-- subordinates).
10398
, ifaceDocMap :: !(DocMap Name)

0 commit comments

Comments
 (0)