From 2ead72cca37742fa7fd195738d0a2e1bcc06def2 Mon Sep 17 00:00:00 2001
From: Zubin Duggal <zubin@cmi.ac.in>
Date: Tue, 9 Jun 2020 17:06:26 +0530
Subject: [PATCH] Export everything from HsToCore.

This lets us reuse these functions in haddock, avoiding synchronization bugs.

Also fixed some divergences with haddock in that file

Updates haddock submodule
---
 compiler/GHC/HsToCore/Docs.hs | 9 +++++++--
 utils/haddock                 | 2 +-
 2 files changed, 8 insertions(+), 3 deletions(-)

diff --git a/compiler/GHC/HsToCore/Docs.hs b/compiler/GHC/HsToCore/Docs.hs
index 2cbc95c7b81..50f8f87aca1 100644
--- a/compiler/GHC/HsToCore/Docs.hs
+++ b/compiler/GHC/HsToCore/Docs.hs
@@ -3,10 +3,11 @@
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE ViewPatterns #-}
+{-# LANGUAGE BangPatterns #-}
 
 {-# OPTIONS_GHC -Wno-incomplete-record-updates #-}
 
-module GHC.HsToCore.Docs (extractDocs) where
+module GHC.HsToCore.Docs where
 
 import GHC.Prelude
 import GHC.Data.Bag
@@ -147,6 +148,9 @@ getInstLoc = \case
   --                 ^^^
   DataFamInstD _ (DataFamInstDecl
     { dfid_eqn = HsIB { hsib_body = FamEqn { feqn_tycon = L l _ }}}) -> l
+  -- 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.
   TyFamInstD _ (TyFamInstDecl
     { tfid_eqn = HsIB { hsib_body = FamEqn { feqn_tycon = L l _ }}}) -> l
 
@@ -214,6 +218,7 @@ conArgDocs con = case getConArgs con of
     go n = M.fromList . catMaybes . zipWith f [n..]
       where
         f n (HsDocTy _ _ lds) = Just (n, unLoc lds)
+        f n (HsBangTy _ _ (L _ (HsDocTy _ _ lds))) = Just (n, unLoc lds)
         f _ _ = Nothing
 
     ret = case con of
@@ -251,7 +256,7 @@ nubByName f ns = go emptyNameSet ns
     go _ [] = []
     go s (x:xs)
       | y `elemNameSet` s = go s xs
-      | otherwise         = let s' = extendNameSet s y
+      | otherwise         = let !s' = extendNameSet s y
                             in x : go s' xs
       where
         y = f x
diff --git a/utils/haddock b/utils/haddock
index 02a1def8d14..45add0d8a39 160000
--- a/utils/haddock
+++ b/utils/haddock
@@ -1 +1 @@
-Subproject commit 02a1def8d147da88a0433726590f8586f486c760
+Subproject commit 45add0d8a39172d17e822b762508685d7b433639
-- 
GitLab