[Git][ghc/ghc][master] Fix documentation on type families not being extracted

Marge Bot gitlab at gitlab.haskell.org
Thu Jun 4 08:36:51 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
2bd3929a by Luke Lau at 2020-06-04T04:36:41-04:00
Fix documentation on type families not being extracted

It looks like the location of the Names used for CoAxioms on type
families are now located at their type constructors. Previously, Docs.hs
thought the Names were located in the RHS, so the RealSrcSpan in the
instanceMap and getInstLoc didn't match up. Fixes #18241

- - - - -


3 changed files:

- compiler/GHC/HsToCore/Docs.hs
- testsuite/tests/showIface/DocsInHiFile.hs
- testsuite/tests/showIface/DocsInHiFile1.stdout


Changes:

=====================================
compiler/GHC/HsToCore/Docs.hs
=====================================
@@ -97,13 +97,7 @@ mkMaps instances decls =
     instanceMap = M.fromList [(l, n) | n <- instances, RealSrcSpan l _ <- [getSrcSpan n] ]
 
     names :: RealSrcSpan -> HsDecl GhcRn -> [Name]
-    names l (InstD _ d) = maybeToList $ -- See Note [1].
-      case d of
-              TyFamInstD _ _ -> M.lookup l instanceMap
-                -- The CoAx's loc is the whole line, but only
-                -- for TFs
-              _ -> lookupSrcSpan (getInstLoc d) instanceMap
-
+    names _ (InstD _ d) = maybeToList $ lookupSrcSpan (getInstLoc d) instanceMap
     names l (DerivD {}) = maybeToList (M.lookup l instanceMap) -- See Note [1].
     names _ decl = getMainDeclBinder decl
 
@@ -145,14 +139,16 @@ sigNameNoLoc _                             = []
 getInstLoc :: InstDecl (GhcPass p) -> SrcSpan
 getInstLoc = \case
   ClsInstD _ (ClsInstDecl { cid_poly_ty = ty }) -> getLoc (hsSigType ty)
+  -- The Names of data and type family instances have their SrcSpan's attached
+  -- to the *type constructor*. For example, the Name "D:R:Foo:Int" would have
+  -- its SrcSpan attached here:
+  --   type family Foo a
+  --   type instance Foo Int = Bool
+  --                 ^^^
   DataFamInstD _ (DataFamInstDecl
     { dfid_eqn = HsIB { hsib_body = FamEqn { feqn_tycon = L l _ }}}) -> l
   TyFamInstD _ (TyFamInstDecl
-    -- Since CoAxioms' Names refer to the whole line for type family instances
-    -- in particular, we need to dig a bit deeper to pull out the entire
-    -- equation. This does not happen for data family instances, for some
-    -- reason.
-    { tfid_eqn = HsIB { hsib_body = FamEqn { feqn_rhs = L l _ }}}) -> l
+    { tfid_eqn = HsIB { hsib_body = FamEqn { feqn_tycon = L l _ }}}) -> l
 
 -- | Get all subordinate declarations inside a declaration, and their docs.
 -- A subordinate declaration is something like the associate type or data


=====================================
testsuite/tests/showIface/DocsInHiFile.hs
=====================================
@@ -1,3 +1,4 @@
+{-# LANGUAGE TypeFamilies #-}
 {-| `elem`, 'print',
 `Unknown',
 '<>', ':=:', 'Bool'
@@ -35,3 +36,8 @@ class P f where
 -- | Another datatype...
 data D'
 -- ^ ...with two docstrings.
+
+-- | A type family
+type family F a
+-- | A type family instance
+type instance F Int = Bool


=====================================
testsuite/tests/showIface/DocsInHiFile1.stdout
=====================================
@@ -22,6 +22,10 @@ declaration docs:
     " Another datatype...
 
  ...with two docstrings."
+  D:R:FInt:
+    " A type family instance"
+  F:
+    " A type family"
 arg docs:
   add:
     0:



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2bd3929ad1b06b01c1d22d513902507eefadc131

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2bd3929ad1b06b01c1d22d513902507eefadc131
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200604/8fb1e464/attachment-0001.html>


More information about the ghc-commits mailing list