[commit: haddock] master: Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) (ba8711a)

Simon Hengel sol at typeful.net
Tue Feb 12 23:40:20 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/haddock

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/ba8711a3b3bada2a099e9484296cbd04becbdbb4

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

commit ba8711a3b3bada2a099e9484296cbd04becbdbb4
Author: Kazu Yamamoto <kazu at iij.ad.jp>
Date:   Wed Feb 6 11:12:28 2013 +0900

    Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.)

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

 src/Haddock/Interface/AttachInstances.hs |   11 +++++------
 1 files changed, 5 insertions(+), 6 deletions(-)

diff --git a/src/Haddock/Interface/AttachInstances.hs b/src/Haddock/Interface/AttachInstances.hs
index 04c4e5e..dea01d5 100644
--- a/src/Haddock/Interface/AttachInstances.hs
+++ b/src/Haddock/Interface/AttachInstances.hs
@@ -32,6 +32,7 @@ import MonadUtils (liftIO)
 import Name
 import PrelNames
 import TcRnDriver (tcRnGetInfo)
+import TcType (tcSplitSigmaTy)
 import TyCon
 import TypeRep
 import TysPrim( funTyCon )
@@ -64,13 +65,13 @@ attachToExportItem expInfo iface ifaceMap instIfaceMap export =
               expItemInstances =
                 case mb_info of
                   Just (_, _, instances) ->
+{-
                     let insts = map (first synifyInstHead) $ sortImage (first instHead)
                                 [ (instanceSig i, getName i) | i <- instances ]
-{- FIXME
+-}
                     let insts = map (first synifyInstHead) $ sortImage (first instHead) $
                                 filter (\((_,_,cls,tys),_) -> not $ isInstanceHidden expInfo cls tys)
                                 [ (instanceHead' i, getName i) | i <- instances ]
--}
                     in [ (inst, lookupInstDoc name iface ifaceMap instIfaceMap)
                        | (inst, name) <- insts ]
                   Nothing -> []
@@ -100,14 +101,12 @@ lookupInstDoc name iface ifaceMap instIfaceMap =
 
 
 -- | Like GHC's 'instanceHead' but drops "silent" arguments.
-{- FIXME
 instanceHead' :: ClsInst -> ([TyVar], ThetaType, Class, [Type])
 instanceHead' ispec = (tvs, dropSilentArgs dfun theta, cls, tys)
   where
     dfun = is_dfun ispec
-    (tvs, theta, cls, tys) = instanceHead ispec
--}
-
+    (tvs, cls, tys) = instanceHead ispec
+    (_, theta, _) = tcSplitSigmaTy . idType . is_dfun $ ispec
 
 -- | Drop "silent" arguments. See GHC Note [Silent superclass
 -- arguments].





More information about the ghc-commits mailing list