[commit: haddock] wip/landmine-param-family: Bring in PostRn instance (1f1f7d5)

git at git.haskell.org git at git.haskell.org
Wed Jul 8 08:30:08 UTC 2015


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

On branch  : wip/landmine-param-family
Link       : http://git.haskell.org/haddock.git/commitdiff/1f1f7d51a5c27a696bbef69a01c3c256a7619d3d

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

commit 1f1f7d51a5c27a696bbef69a01c3c256a7619d3d
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date:   Sat Aug 16 12:12:46 2014 +0200

    Bring in PostRn instance


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

1f1f7d51a5c27a696bbef69a01c3c256a7619d3d
 src/Haddock/Interface/Rename.hs | 3 +++
 1 file changed, 3 insertions(+)

diff --git a/src/Haddock/Interface/Rename.hs b/src/Haddock/Interface/Rename.hs
index a804f4a..7344591 100644
--- a/src/Haddock/Interface/Rename.hs
+++ b/src/Haddock/Interface/Rename.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE TypeFamilies #-}
 ----------------------------------------------------------------------------
 -- |
 -- Module      :  Haddock.Interface.Rename
@@ -20,6 +21,7 @@ import Haddock.Types
 import Bag (emptyBag)
 import GHC hiding (NoLink)
 import Name
+import NameSet
 
 import Control.Applicative
 import Control.Monad hiding (mapM)
@@ -453,6 +455,7 @@ renameClsInstD (ClsInstDecl { cid_overlap_mode = omode
                       , cid_sigs = []
                       , cid_tyfam_insts = lATs', cid_datafam_insts = lADTs' })
 
+type instance PostRn DocName NameSet  = NameSet
 
 renameTyFamInstD :: TyFamInstDecl Name -> RnM (TyFamInstDecl DocName)
 renameTyFamInstD (TyFamInstDecl { tfid_eqn = eqn })



More information about the ghc-commits mailing list