Skip to content
Snippets Groups Projects
Commit 6e95f429 authored by Edward Z. Yang's avatar Edward Z. Yang Committed by Mateusz Kowalczyk
Browse files

Properly render package ID (not package key) in index, fixes #329.


Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>

Conflicts:
	haddock-api/src/Haddock/ModuleTree.hs
parent 08332912
No related branches found
No related tags found
No related merge requests found
......@@ -270,14 +270,14 @@ render dflags flags qual ifaces installedIfaces srcMap = do
copyHtmlBits odir libDir themes
when (Flag_GenContents `elem` flags) $ do
ppHtmlContents odir title pkgStr
ppHtmlContents dflags odir title pkgStr
themes opt_index_url sourceUrls' opt_wiki_urls
allVisibleIfaces True prologue pretty
(makeContentsQual qual)
copyHtmlBits odir libDir themes
when (Flag_Html `elem` flags) $ do
ppHtml title pkgStr visibleIfaces odir
ppHtml dflags title pkgStr visibleIfaces odir
prologue
themes sourceUrls' opt_wiki_urls
opt_contents_url opt_index_url unicode qual
......
......@@ -60,7 +60,8 @@ import Module
--------------------------------------------------------------------------------
ppHtml :: String
ppHtml :: DynFlags
-> String -- ^ Title
-> Maybe String -- ^ Package
-> [Interface]
-> FilePath -- ^ Destination directory
......@@ -75,7 +76,7 @@ ppHtml :: String
-> Bool -- ^ Output pretty html (newlines and indenting)
-> IO ()
ppHtml doctitle maybe_package ifaces odir prologue
ppHtml dflags doctitle maybe_package ifaces odir prologue
themes maybe_source_url maybe_wiki_url
maybe_contents_url maybe_index_url unicode
qual debug = do
......@@ -84,7 +85,7 @@ ppHtml doctitle maybe_package ifaces odir prologue
visible i = OptHide `notElem` ifaceOptions i
when (isNothing maybe_contents_url) $
ppHtmlContents odir doctitle maybe_package
ppHtmlContents dflags odir doctitle maybe_package
themes maybe_index_url maybe_source_url maybe_wiki_url
(map toInstalledIface visible_ifaces)
False -- we don't want to display the packages in a single-package contents
......@@ -239,7 +240,8 @@ moduleInfo iface =
ppHtmlContents
:: FilePath
:: DynFlags
-> FilePath
-> String
-> Maybe String
-> Themes
......@@ -250,10 +252,10 @@ ppHtmlContents
-> Bool
-> Qualification -- ^ How to qualify names
-> IO ()
ppHtmlContents odir doctitle _maybe_package
ppHtmlContents dflags odir doctitle _maybe_package
themes maybe_index_url
maybe_source_url maybe_wiki_url ifaces showPkgs prologue debug qual = do
let tree = mkModuleTree showPkgs
let tree = mkModuleTree dflags showPkgs
[(instMod iface, toInstalledDescription iface) | iface <- ifaces]
html =
headHtml doctitle Nothing themes +++
......
......@@ -15,18 +15,21 @@ module Haddock.ModuleTree ( ModuleTree(..), mkModuleTree ) where
import Haddock.Types ( MDoc )
import GHC ( Name )
import Module ( Module, moduleNameString, moduleName, modulePackageKey,
packageKeyString )
import Module ( Module, moduleNameString, moduleName, modulePackageKey )
import DynFlags ( DynFlags )
import Packages ( lookupPackage )
import PackageConfig ( sourcePackageIdString )
data ModuleTree = Node String Bool (Maybe String) (Maybe (MDoc Name)) [ModuleTree]
mkModuleTree :: Bool -> [(Module, Maybe (MDoc Name))] -> [ModuleTree]
mkModuleTree showPkgs mods =
mkModuleTree :: DynFlags -> Bool -> [(Module, Maybe (MDoc Name))] -> [ModuleTree]
mkModuleTree dflags showPkgs mods =
foldr fn [] [ (splitModule mdl, modPkg mdl, short) | (mdl, short) <- mods ]
where
modPkg mod_ | showPkgs = Just (packageKeyString (modulePackageKey mod_))
modPkg mod_ | showPkgs = fmap sourcePackageIdString
(lookupPackage dflags (modulePackageKey mod_))
| otherwise = Nothing
fn (mod_,pkg,short) = addToTrees mod_ pkg short
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment