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

Generate docs for orphan instances #449

Merged
merged 5 commits into from
Dec 30, 2015
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
23 changes: 16 additions & 7 deletions haddock-api/src/Haddock/Backends/Xhtml.hs
Original file line number Diff line number Diff line change
Expand Up @@ -522,10 +522,10 @@ ppHtmlModuleMiniSynopsis odir _doctitle themes iface unicode qual debug = do

ifaceToHtml :: SourceURLs -> WikiURLs -> Interface -> Bool -> Qualification -> Html
ifaceToHtml maybe_source_url maybe_wiki_url iface unicode qual
= ppModuleContents qual exports +++
= ppModuleContents qual exports (not . null $ ifaceRnOrphanInstances iface) +++
description +++
synopsis +++
divInterface (maybe_doc_hdr +++ bdy)
divInterface (maybe_doc_hdr +++ bdy +++ orphans)
where
exports = numberSectionHeadings (ifaceRnExportItems iface)

Expand Down Expand Up @@ -564,6 +564,9 @@ ifaceToHtml maybe_source_url maybe_wiki_url iface unicode qual
foldr (+++) noHtml $
mapMaybe (processExport False linksInfo unicode qual) exports

orphans =
ppOrphanInstances linksInfo (ifaceRnOrphanInstances iface) False unicode qual

linksInfo = (maybe_source_url, maybe_wiki_url)


Expand Down Expand Up @@ -604,16 +607,22 @@ ppTyClBinderWithVarsMini mdl decl =
ns = tyvarNames $ tcdTyVars decl -- it's safe to use tcdTyVars, see code above
in ppTypeApp n [] ns (\is_infix -> ppNameMini is_infix mdl . nameOccName . getName) ppTyName

ppModuleContents :: Qualification -> [ExportItem DocName] -> Html
ppModuleContents qual exports
| null sections = noHtml
| otherwise = contentsDiv
ppModuleContents :: Qualification
-> [ExportItem DocName]
-> Bool -- ^ Orphans sections
-> Html
ppModuleContents qual exports orphan
| null sections && not orphan = noHtml
| otherwise = contentsDiv
where
contentsDiv = divTableOfContents << (
sectionName << "Contents" +++
unordList sections)
unordList (sections ++ orphanSection))

(sections, _leftovers{-should be []-}) = process 0 exports
orphanSection
| orphan = [ linkedAnchor "section.orphans" << "Orphan instances" ]
| otherwise = []

process :: Int -> [ExportItem DocName] -> ([Html],[ExportItem DocName])
process _ [] = ([], [])
Expand Down
33 changes: 26 additions & 7 deletions haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
module Haddock.Backends.Xhtml.Decl (
ppDecl,

ppTyName, ppTyFamHeader, ppTypeApp,
ppTyName, ppTyFamHeader, ppTypeApp, ppOrphanInstances,
tyvarNames
) where

Expand Down Expand Up @@ -545,22 +545,40 @@ ppInstances links origin instances splice unicode qual
instName = getOccString origin
instDecl :: Int -> DocInstance DocName -> (SubDecl,Located DocName)
instDecl no (inst, mdoc, loc) =
((ppInstHead links splice unicode qual mdoc origin no inst), loc)
((ppInstHead links splice unicode qual mdoc origin False no inst), loc)


ppOrphanInstances :: LinksInfo
-> [DocInstance DocName]
-> Splice -> Unicode -> Qualification
-> Html
ppOrphanInstances links instances splice unicode qual
= subOrphanInstances qual links True (zipWith instDecl [1..] instances)
where
instOrigin :: InstHead name -> InstOrigin name
instOrigin inst = OriginClass (ihdClsName inst)

instDecl :: Int -> DocInstance DocName -> (SubDecl,Located DocName)
instDecl no (inst, mdoc, loc) =
((ppInstHead links splice unicode qual mdoc (instOrigin inst) True no inst), loc)


ppInstHead :: LinksInfo -> Splice -> Unicode -> Qualification
-> Maybe (MDoc DocName)
-> InstOrigin DocName -> Int -> InstHead DocName
-> InstOrigin DocName
-> Bool -- ^ Is instance orphan
-> Int -- ^ Normal
-> InstHead DocName
-> SubDecl
ppInstHead links splice unicode qual mdoc origin no ihd@(InstHead {..}) =
ppInstHead links splice unicode qual mdoc origin orphan no ihd@(InstHead {..}) =
case ihdInstType of
ClassInst { .. } ->
( subInstHead iid $ ppContextNoLocs clsiCtx unicode qual <+> typ
, mdoc
, [subInstDetails iid ats sigs]
)
where
iid = instanceId origin no ihd
iid = instanceId origin no orphan ihd
sigs = ppInstanceSigs links splice unicode qual clsiSigs
ats = ppInstanceAssocTys links splice unicode qual clsiAssocTys
TypeInst rhs ->
Expand Down Expand Up @@ -599,8 +617,9 @@ lookupAnySubdoc :: Eq id1 => id1 -> [(id1, DocForDecl id2)] -> DocForDecl id2
lookupAnySubdoc n = fromMaybe noDocForDecl . lookup n


instanceId :: InstOrigin DocName -> Int -> InstHead DocName -> String
instanceId origin no ihd = concat
instanceId :: InstOrigin DocName -> Int -> Bool -> InstHead DocName -> String
instanceId origin no orphan ihd = concat $
[ "o:" | orphan ] ++
[ qual origin
, ":" ++ getOccString origin
, ":" ++ (occNameString . getOccName . ihdClsName) ihd
Expand Down
14 changes: 12 additions & 2 deletions haddock-api/src/Haddock/Backends/Xhtml/Layout.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ module Haddock.Backends.Xhtml.Layout (
subConstructors,
subEquations,
subFields,
subInstances, subInstHead, subInstDetails,
subInstances, subOrphanInstances, subInstHead, subInstDetails,
subMethods,
subMinimal,

Expand Down Expand Up @@ -200,7 +200,17 @@ subInstances qual nm lnks splice = maybe noHtml wrap . instTable
subCaption = paragraph ! collapseControl id_ True "caption" << "Instances"
id_ = makeAnchorId $ "i:" ++ nm



subOrphanInstances :: Qualification
-> LinksInfo -> Bool
-> [(SubDecl,Located DocName)] -> Html
subOrphanInstances qual lnks splice = maybe noHtml wrap . instTable
where
wrap = ((h1 << "Orphan instances") +++)
instTable = fmap (thediv ! collapseSection id_ True [] <<) . subTableSrc qual lnks splice
id_ = makeAnchorId $ "orphans"


subInstHead :: String -- ^ Instance unique id (for anchor generation)
-> Html -- ^ Header content (instance name and type)
-> Html
Expand Down
2 changes: 1 addition & 1 deletion haddock-api/src/Haddock/Interface.hs
Original file line number Diff line number Diff line change
Expand Up @@ -228,7 +228,7 @@ buildHomeLinks ifaces = foldl upd Map.empty (reverse ifaces)
foldl' keep_old old_env exported_names
| otherwise = foldl' keep_new old_env exported_names
where
exported_names = ifaceVisibleExports iface
exported_names = ifaceVisibleExports iface ++ map getName (ifaceInstances iface)
mdl = ifaceMod iface
keep_old env n = Map.insertWith (\_ old -> old) n mdl env
keep_new env n = Map.insert n mdl env
Expand Down
13 changes: 12 additions & 1 deletion haddock-api/src/Haddock/Interface/AttachInstances.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,18 @@ attachInstances expInfo ifaces instIfaceMap = mapM attach ifaces
attach iface = do
newItems <- mapM (attachToExportItem expInfo iface ifaceMap instIfaceMap)
(ifaceExportItems iface)
return $ iface { ifaceExportItems = newItems }
let orphanInstances = attachOrphanInstances expInfo iface ifaceMap instIfaceMap (ifaceInstances iface)
return $ iface { ifaceExportItems = newItems
, ifaceOrphanInstances = orphanInstances
}

attachOrphanInstances :: ExportInfo -> Interface -> IfaceMap -> InstIfaceMap -> [ClsInst] -> [DocInstance Name]
attachOrphanInstances expInfo iface ifaceMap instIfaceMap cls_instances =
[ (synifyInstHead i, instLookup instDocMap n iface ifaceMap instIfaceMap, (L (getSrcSpan n) n))
| let is = [ (instanceHead' i, getName i) | i <- cls_instances, isOrphan (is_orphan i) ]
, (i@(_,_,cls,tys), n) <- sortBy (comparing $ first instHead) is
, not $ isInstanceHidden expInfo cls tys
]


attachToExportItem :: ExportInfo -> Interface -> IfaceMap -> InstIfaceMap
Expand Down
2 changes: 2 additions & 0 deletions haddock-api/src/Haddock/Interface/Create.hs
Original file line number Diff line number Diff line change
Expand Up @@ -148,6 +148,8 @@ createInterface tm flags modMap instIfaceMap = do
, ifaceModuleAliases = aliases
, ifaceInstances = instances
, ifaceFamInstances = fam_instances
, ifaceOrphanInstances = [] -- Filled in `attachInstances`
, ifaceRnOrphanInstances = [] -- Filled in `renameInterface`
, ifaceHaddockCoverage = coverage
, ifaceWarningMap = warningMap
, ifaceTokenizedSrc = tokenizedSrc
Expand Down
25 changes: 16 additions & 9 deletions haddock-api/src/Haddock/Interface/Rename.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,13 +47,16 @@ renameInterface dflags renamingEnv warnings iface =

(rnArgMap, missingNames3) = runRnFM localEnv (mapM (mapM renameDoc) (ifaceArgMap iface))

(finalModuleDoc, missingNames4)
(renamedOrphanInstances, missingNames4)
= runRnFM localEnv (mapM renameDocInstance (ifaceOrphanInstances iface))

(finalModuleDoc, missingNames5)
= runRnFM localEnv (renameDocumentation (ifaceDoc iface))

-- combine the missing names and filter out the built-ins, which would
-- otherwise allways be missing.
-- otherwise always be missing.
missingNames = nub $ filter isExternalName -- XXX: isExternalName filters out too much
(missingNames1 ++ missingNames2 ++ missingNames3 ++ missingNames4)
(missingNames1 ++ missingNames2 ++ missingNames3 ++ missingNames4 ++ missingNames5)

-- filter out certain built in type constructors using their string
-- representation. TODO: use the Name constants from the GHC API.
Expand All @@ -72,7 +75,8 @@ renameInterface dflags renamingEnv warnings iface =
return $ iface { ifaceRnDoc = finalModuleDoc,
ifaceRnDocMap = rnDocMap,
ifaceRnArgMap = rnArgMap,
ifaceRnExportItems = renamedExportItems }
ifaceRnExportItems = renamedExportItems,
ifaceRnOrphanInstances = renamedOrphanInstances}


--------------------------------------------------------------------------------
Expand Down Expand Up @@ -504,6 +508,13 @@ renameDataFamInstD (DataFamInstDecl { dfid_tycon = tc, dfid_pats = pats_w_bndrs,
= HsWB pats' PlaceHolder PlaceHolder PlaceHolder
, dfid_defn = defn', dfid_fvs = placeHolderNames }) }

renameDocInstance :: DocInstance Name -> RnM (DocInstance DocName)
renameDocInstance (inst, idoc, L l n) = do
inst' <- renameInstHead inst
n' <- rename n
idoc' <- mapM renameDoc idoc
return (inst', idoc',L l n')

renameExportItem :: ExportItem Name -> RnM (ExportItem DocName)
renameExportItem item = case item of
ExportModule mdl -> return (ExportModule mdl)
Expand All @@ -514,11 +525,7 @@ renameExportItem item = case item of
decl' <- renameLDecl decl
doc' <- renameDocForDecl doc
subs' <- mapM renameSub subs
instances' <- forM instances $ \(inst, idoc, L l n) -> do
inst' <- renameInstHead inst
n' <- rename n
idoc' <- mapM renameDoc idoc
return (inst', idoc',L l n')
instances' <- forM instances renameDocInstance
fixities' <- forM fixities $ \(name, fixity) -> do
name' <- lookupRn name
return (name', fixity)
Expand Down
4 changes: 4 additions & 0 deletions haddock-api/src/Haddock/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,10 @@ data Interface = Interface
, ifaceInstances :: ![ClsInst]
, ifaceFamInstances :: ![FamInst]

-- | Orphan instances
, ifaceOrphanInstances :: ![DocInstance Name]
, ifaceRnOrphanInstances :: ![DocInstance DocName]

-- | The number of haddockable and haddocked items in the module, as a
-- tuple. Haddockable items are the exports and the module itself.
, ifaceHaddockCoverage :: !(Int, Int)
Expand Down