Skip to content
Snippets Groups Projects
Commit b682041e authored by Alec Theriault's avatar Alec Theriault
Browse files

Fix bogus identifier defaulting

This avoids a situation in which an identifier would get defaulted to
a completely different identifier. Prior to this commit, the 'Bug1035'
test case would hyperlink 'Foo' into 'Bar'!

Fixes #1035.
parent a5199600
No related branches found
No related tags found
5 merge requests!38Make --no-tmp-comp-dir the default,!37Adapt to latest xhtml version, various optimizations,!31Support HsToken in DataDecl and ClassDecl,!12Drop orphan instance when defined upstream.,!10Haddock interfaces produced from `.hi` files
...@@ -19,7 +19,6 @@ module Haddock.Interface.LexParseRn ...@@ -19,7 +19,6 @@ module Haddock.Interface.LexParseRn
, processModuleHeader , processModuleHeader
) where ) where
import Avail
import Control.Arrow import Control.Arrow
import Control.Monad import Control.Monad
import Data.Functor (($>)) import Data.Functor (($>))
...@@ -200,10 +199,9 @@ ambiguous :: DynFlags ...@@ -200,10 +199,9 @@ ambiguous :: DynFlags
-> [GlobalRdrElt] -- ^ More than one @gre@s sharing the same `RdrName` above. -> [GlobalRdrElt] -- ^ More than one @gre@s sharing the same `RdrName` above.
-> ErrMsgM (Doc Name) -> ErrMsgM (Doc Name)
ambiguous dflags x gres = do ambiguous dflags x gres = do
let noChildren = map availName (gresToAvailInfo gres) let dflt = maximumBy (comparing (gre_lcl &&& isTyConName . gre_name)) gres
dflt = maximumBy (comparing (isLocalName &&& isTyConName)) noChildren
msg = "Warning: " ++ showNsRdrName dflags x ++ " is ambiguous. It is defined\n" ++ msg = "Warning: " ++ showNsRdrName dflags x ++ " is ambiguous. It is defined\n" ++
concatMap (\n -> " * " ++ defnLoc n ++ "\n") (map gre_name gres) ++ concatMap (\n -> " * " ++ defnLoc n ++ "\n") gres ++
" You may be able to disambiguate the identifier by qualifying it or\n" ++ " You may be able to disambiguate the identifier by qualifying it or\n" ++
" by specifying the type/value namespace explicitly.\n" ++ " by specifying the type/value namespace explicitly.\n" ++
" Defaulting to the one defined " ++ defnLoc dflt " Defaulting to the one defined " ++ defnLoc dflt
...@@ -212,12 +210,10 @@ ambiguous dflags x gres = do ...@@ -212,12 +210,10 @@ ambiguous dflags x gres = do
-- of the same name, but not the only constructor. -- of the same name, but not the only constructor.
-- For example, for @data D = C | D@, someone may want to reference the @D@ -- For example, for @data D = C | D@, someone may want to reference the @D@
-- constructor. -- constructor.
when (length noChildren > 1) $ tell [msg] when (length (gresToAvailInfo gres) > 1) $ tell [msg]
pure (DocIdentifier (x $> dflt)) pure (DocIdentifier (x $> gre_name dflt))
where where
isLocalName (nameSrcLoc -> RealSrcLoc {}) = True defnLoc = showSDoc dflags . pprNameDefnLoc . gre_name
isLocalName _ = False
defnLoc = showSDoc dflags . pprNameDefnLoc
-- | Handle value-namespaced names that cannot be for values. -- | Handle value-namespaced names that cannot be for values.
-- --
......
<html xmlns="http://www.w3.org/1999/xhtml"
><head
><meta http-equiv="Content-Type" content="text/html; charset=UTF-8"
/><meta name="viewport" content="width=device-width, initial-scale=1"
/><title
>Bug1035</title
><link href="#" rel="stylesheet" type="text/css" title="NewOcean"
/><link rel="stylesheet" type="text/css" href="#"
/><link rel="stylesheet" type="text/css" href="#"
/><script src="haddock-bundle.min.js" async="async" type="text/javascript"
></script
><script type="text/x-mathjax-config"
>MathJax.Hub.Config({ tex2jax: { processClass: &quot;mathjax&quot;, ignoreClass: &quot;.*&quot; } });</script
><script src="https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.5/MathJax.js?config=TeX-AMS-MML_HTMLorMML" type="text/javascript"
></script
></head
><body
><div id="package-header"
><span class="caption empty"
></span
><ul class="links" id="page-menu"
><li
><a href="#"
>Contents</a
></li
><li
><a href="#"
>Index</a
></li
></ul
></div
><div id="content"
><div id="module-header"
><table class="info"
><tr
><th
>Safe Haskell</th
><td
>Safe</td
></tr
></table
><p class="caption"
>Bug1035</p
></div
><div id="synopsis"
><details id="syn"
><summary
>Synopsis</summary
><ul class="details-toggle" data-details-id="syn"
><li class="src short"
><span class="keyword"
>data</span
> <a href="#"
>Foo</a
> = <a href="#"
>Bar</a
></li
><li class="src short"
><span class="keyword"
>data</span
> <a href="#"
>Bar</a
> = <a href="#"
>Foo</a
></li
><li class="src short"
><a href="#"
>foo</a
> :: ()</li
></ul
></details
></div
><div id="interface"
><h1
>Documentation</h1
><div class="top"
><p class="src"
><span class="keyword"
>data</span
> <a id="t:Foo" class="def"
>Foo</a
> <a href="#" class="selflink"
>#</a
></p
><div class="subs constructors"
><p class="caption"
>Constructors</p
><table
><tr
><td class="src"
><a id="v:Bar" class="def"
>Bar</a
></td
><td class="doc empty"
></td
></tr
></table
></div
></div
><div class="top"
><p class="src"
><span class="keyword"
>data</span
> <a id="t:Bar" class="def"
>Bar</a
> <a href="#" class="selflink"
>#</a
></p
><div class="subs constructors"
><p class="caption"
>Constructors</p
><table
><tr
><td class="src"
><a id="v:Foo" class="def"
>Foo</a
></td
><td class="doc empty"
></td
></tr
></table
></div
></div
><div class="top"
><p class="src"
><a id="v:foo" class="def"
>foo</a
> :: () <a href="#" class="selflink"
>#</a
></p
><div class="doc"
><p
>A link to <code
><a href="#" title="Bug1035"
>Bar</a
></code
></p
></div
></div
></div
></div
><div id="footer"
></div
></body
></html
>
\ No newline at end of file
module Bug1035 where
data Foo = Bar
data Bar = Foo
-- | A link to 'Bar'
foo :: ()
foo = ()
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