[commit: haddock] 2.17.3.1-spanfix, alexbiehl-patch-1, ghc-8.0, ghc-8.0-facebook, ghc-head, ghc-head1, haddock-quick, headdock-library-1.4.5, ie_avails, issue-303, issue-475, master, pr-filter-maps, pr/cabal-desc, travis, v2.17, v2.17.3, v2.18, wip-located-module-as, wip/D2418, wip/T11080-open-data-kinds, wip/T11430, wip/T12105, wip/T12105-2, wip/T12942, wip/T13163, wip/T3384, wip/embelleshed-rdr, wip/new-tree-one-param, wip/rae, wip/remove-frames, wip/remove-frames1, wip/revert-ttg-2017-11-20, wip/ttg-2017-10-13, wip/ttg-2017-10-31, wip/ttg-2017-11-06, wip/ttg2-2017-11-10, wip/ttg3-2017-11-12, wip/ttg4-constraints-2017-11-13: Have source links for orphan instances (dee8ef2)

git at git.haskell.org git at git.haskell.org
Mon Nov 20 20:55:36 UTC 2017


Repository : ssh://git@git.haskell.org/haddock

On branches: 2.17.3.1-spanfix,alexbiehl-patch-1,ghc-8.0,ghc-8.0-facebook,ghc-head,ghc-head1,haddock-quick,headdock-library-1.4.5,ie_avails,issue-303,issue-475,master,pr-filter-maps,pr/cabal-desc,travis,v2.17,v2.17.3,v2.18,wip-located-module-as,wip/D2418,wip/T11080-open-data-kinds,wip/T11430,wip/T12105,wip/T12105-2,wip/T12942,wip/T13163,wip/T3384,wip/embelleshed-rdr,wip/new-tree-one-param,wip/rae,wip/remove-frames,wip/remove-frames1,wip/revert-ttg-2017-11-20,wip/ttg-2017-10-13,wip/ttg-2017-10-31,wip/ttg-2017-11-06,wip/ttg2-2017-11-10,wip/ttg3-2017-11-12,wip/ttg4-constraints-2017-11-13
Link       : http://git.haskell.org/haddock.git/commitdiff/dee8ef2b918917a1469f35b24d7bd9f7caa59d62

>---------------------------------------------------------------

commit dee8ef2b918917a1469f35b24d7bd9f7caa59d62
Author: Oleg Grenrus <oleg.grenrus at iki.fi>
Date:   Mon Sep 28 07:21:11 2015 +0300

    Have source links for orphan instances


>---------------------------------------------------------------

dee8ef2b918917a1469f35b24d7bd9f7caa59d62
 haddock-api/src/Haddock/Interface.hs                 |  2 +-
 haddock-api/src/Haddock/Interface/AttachInstances.hs | 20 ++++++++------------
 2 files changed, 9 insertions(+), 13 deletions(-)

diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs
index 1bb04ed..8b04d76 100644
--- a/haddock-api/src/Haddock/Interface.hs
+++ b/haddock-api/src/Haddock/Interface.hs
@@ -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
diff --git a/haddock-api/src/Haddock/Interface/AttachInstances.hs b/haddock-api/src/Haddock/Interface/AttachInstances.hs
index c3e1275..5adee45 100644
--- a/haddock-api/src/Haddock/Interface/AttachInstances.hs
+++ b/haddock-api/src/Haddock/Interface/AttachInstances.hs
@@ -66,23 +66,13 @@ attachInstances expInfo ifaces instIfaceMap = mapM attach ifaces
                      , ifaceOrphanInstances = orphanInstances
                      }
 
-spanName :: NamedThing a => a -> InstHead e -> GenLocated SrcSpan e -> GenLocated SrcSpan e
-spanName s (InstHead { ihdClsName = clsn }) (L instL instn) =
-    let s1 = getSrcSpan s
-        sn = if srcSpanFileName_maybe s1 == srcSpanFileName_maybe instL
-                then instn
-                else clsn
-    in L (getSrcSpan s) sn
-
 attachOrphanInstances :: ExportInfo -> Interface -> IfaceMap -> InstIfaceMap -> [ClsInst] -> [DocInstance Name]
 attachOrphanInstances expInfo iface ifaceMap instIfaceMap cls_instances =
-  [ (synifyInstHead i, instLookup instDocMap n iface ifaceMap instIfaceMap, spanName n (synifyInstHead i) (L noSrcSpan n))
+  [ (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
   ]
-  where
-    -- spanName: attach the location to the name that is the same file as the instance location
 
 
 attachToExportItem :: ExportInfo -> Interface -> IfaceMap -> InstIfaceMap
@@ -128,7 +118,13 @@ attachToExportItem expInfo iface ifaceMap instIfaceMap export =
       ] }
 
     attachFixities e = e
-
+    -- spanName: attach the location to the name that is the same file as the instance location
+    spanName s (InstHead { ihdClsName = clsn }) (L instL instn) =
+        let s1 = getSrcSpan s
+            sn = if srcSpanFileName_maybe s1 == srcSpanFileName_maybe instL
+                    then instn
+                    else clsn
+        in L (getSrcSpan s) sn
     -- spanName on Either
     spanNameE s (Left e) _ =  L (getSrcSpan s) (Left e)
     spanNameE s (Right ok) linst =



More information about the ghc-commits mailing list