Skip to content
Snippets Groups Projects
Commit 07c816c5 authored by waern's avatar waern
Browse files

Fix module reference bug.

parent 638683cb
No related branches found
No related tags found
No related merge requests found
...@@ -21,7 +21,6 @@ module Haddock.Backends.Xhtml.DocMarkup ( ...@@ -21,7 +21,6 @@ module Haddock.Backends.Xhtml.DocMarkup (
import Haddock.Backends.Xhtml.Names import Haddock.Backends.Xhtml.Names
import Haddock.Backends.Xhtml.Utils import Haddock.Backends.Xhtml.Utils
import Haddock.GhcUtils
import Haddock.Types import Haddock.Types
import Haddock.Utils import Haddock.Utils
...@@ -39,7 +38,7 @@ parHtmlMarkup qual ppId = Markup { ...@@ -39,7 +38,7 @@ parHtmlMarkup qual ppId = Markup {
markupIdentifier = thecode . ppId, markupIdentifier = thecode . ppId,
markupIdentifierUnchecked = thecode . ppUncheckedLink qual, markupIdentifierUnchecked = thecode . ppUncheckedLink qual,
markupModule = \m -> let (mdl,ref) = break (=='#') m markupModule = \m -> let (mdl,ref) = break (=='#') m
in ppModuleRef (mkModuleNoPackage mdl) ref, in ppModuleRef (mkModuleName mdl) ref,
markupEmphasis = emphasize, markupEmphasis = emphasize,
markupMonospaced = thecode, markupMonospaced = thecode,
markupUnorderedList = unordList, markupUnorderedList = unordList,
......
...@@ -127,9 +127,9 @@ ppModule mdl = anchor ! [href (moduleUrl mdl)] ...@@ -127,9 +127,9 @@ ppModule mdl = anchor ! [href (moduleUrl mdl)]
<< toHtml (moduleString mdl) << toHtml (moduleString mdl)
ppModuleRef :: Module -> String -> Html ppModuleRef :: ModuleName -> String -> Html
ppModuleRef mdl ref = anchor ! [href (moduleUrl mdl ++ ref)] ppModuleRef mdl ref = anchor ! [href (moduleHtmlFile' mdl ++ ref)]
<< toHtml (moduleString mdl) << toHtml (moduleNameString mdl)
-- NB: The ref parameter already includes the '#'. -- NB: The ref parameter already includes the '#'.
-- This function is only called from markupModule expanding a -- This function is only called from markupModule expanding a
-- DocModule, which doesn't seem to be ever be used. -- DocModule, which doesn't seem to be ever be used.
...@@ -61,10 +61,6 @@ unpackPackageId p ...@@ -61,10 +61,6 @@ unpackPackageId p
where str = packageIdString p where str = packageIdString p
mkModuleNoPackage :: String -> Module
mkModuleNoPackage str = mkModule (stringToPackageId "") (mkModuleName str)
lookupLoadedHomeModuleGRE :: GhcMonad m => ModuleName -> m (Maybe GlobalRdrEnv) lookupLoadedHomeModuleGRE :: GhcMonad m => ModuleName -> m (Maybe GlobalRdrEnv)
lookupLoadedHomeModuleGRE mod_name = withSession $ \hsc_env -> lookupLoadedHomeModuleGRE mod_name = withSession $ \hsc_env ->
case lookupUFM (hsc_HPT hsc_env) mod_name of case lookupUFM (hsc_HPT hsc_env) mod_name of
......
...@@ -3,5 +3,6 @@ import A ( A(..), test2 ) ...@@ -3,5 +3,6 @@ import A ( A(..), test2 )
-- | This link shouldn't work: 'other'. -- | This link shouldn't work: 'other'.
-- These links should work: 'A.other', 'Data.List.sortBy', 'test2', 'A.test2', 'Data.Maybe.fromMaybe'. -- These links should work: 'A.other', 'Data.List.sortBy', 'test2', 'A.test2', 'Data.Maybe.fromMaybe'.
-- Module link: "Prelude".
test :: Int test :: Int
test = 1 test = 1
...@@ -99,6 +99,9 @@ window.onload = function () {pageLoad();setSynopsis("mini_B.html");}; ...@@ -99,6 +99,9 @@ window.onload = function () {pageLoad();setSynopsis("mini_B.html");};
>fromMaybe</a >fromMaybe</a
></code ></code
>. >.
Module link: <a href=""
>Prelude</a
>.
</p </p
></div ></div
></div ></div
......
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