[commit: ghc] master: Remove unused parameter to `EvTypeableTyCon` (75ef8b3)

git at git.haskell.org git at git.haskell.org
Thu Mar 19 22:33:50 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/75ef8b3b56f0b33c6be782b59a55b853565ea5f4/ghc

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

commit 75ef8b3b56f0b33c6be782b59a55b853565ea5f4
Author: Iavor S. Diatchki <diatchki at galois.com>
Date:   Thu Mar 19 15:33:50 2015 -0700

    Remove unused parameter to `EvTypeableTyCon`


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

75ef8b3b56f0b33c6be782b59a55b853565ea5f4
 compiler/deSugar/DsBinds.hs      | 7 +++----
 compiler/typecheck/TcEvidence.hs | 7 +++----
 compiler/typecheck/TcHsSyn.hs    | 2 +-
 compiler/typecheck/TcInteract.hs | 2 +-
 4 files changed, 8 insertions(+), 10 deletions(-)

diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs
index 079cfbf..488ffa3 100644
--- a/compiler/deSugar/DsBinds.hs
+++ b/compiler/deSugar/DsBinds.hs
@@ -894,7 +894,7 @@ dsEvTypeable ev =
      (ty, rep) <-
         case ev of
 
-          EvTypeableTyCon tc ks ts ->
+          EvTypeableTyCon tc ks ->
             do ctr       <- dsLookupGlobalId mkPolyTyConAppName
                mkTyCon   <- dsLookupGlobalId mkTyConName
                dflags    <- getDynFlags
@@ -913,10 +913,9 @@ dsEvTypeable ev =
                tcRep     <- tyConRep dflags mkTyCon tc
 
                kReps     <- mapM kindRep ks
-               tReps     <- mapM (getRep tyCl) ts
 
-               return ( mkTyConApp tc (ks ++ map snd ts)
-                      , mkRep tcRep kReps tReps
+               return ( mkTyConApp tc ks
+                      , mkRep tcRep kReps []
                       )
 
           EvTypeableTyApp t1 t2 ->
diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs
index 3eb5a31..bec2415 100644
--- a/compiler/typecheck/TcEvidence.hs
+++ b/compiler/typecheck/TcEvidence.hs
@@ -735,7 +735,7 @@ data EvTerm
 
 -- | Instructions on how to make a 'Typeable' dictionary.
 data EvTypeable
-  = EvTypeableTyCon TyCon [Kind] [(EvTerm, Type)]
+  = EvTypeableTyCon TyCon [Kind]
     -- ^ Dicitionary for concrete type constructors.
 
   | EvTypeableTyApp (EvTerm,Type) (EvTerm,Type)
@@ -1015,7 +1015,7 @@ evVarsOfCallStack cs = case cs of
 evVarsOfTypeable :: EvTypeable -> VarSet
 evVarsOfTypeable ev =
   case ev of
-    EvTypeableTyCon _ _ es -> evVarsOfTerms (map fst es)
+    EvTypeableTyCon _ _    -> emptyVarSet
     EvTypeableTyApp e1 e2  -> evVarsOfTerms (map fst [e1,e2])
     EvTypeableTyLit _      -> emptyVarSet
 
@@ -1102,8 +1102,7 @@ instance Outputable EvCallStack where
 instance Outputable EvTypeable where
   ppr ev =
     case ev of
-      EvTypeableTyCon tc ks ts -> parens (ppr tc <+> sep (map ppr ks) <+>
-                                                     sep (map (ppr . fst) ts))
+      EvTypeableTyCon tc ks    -> parens (ppr tc <+> sep (map ppr ks))
       EvTypeableTyApp t1 t2    -> parens (ppr (fst t1) <+> ppr (fst t2))
       EvTypeableTyLit x        -> ppr x
 
diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs
index e4fb33e..45f384a 100644
--- a/compiler/typecheck/TcHsSyn.hs
+++ b/compiler/typecheck/TcHsSyn.hs
@@ -1256,7 +1256,7 @@ zonkEvTerm _   (EvLit l)          = return (EvLit l)
 zonkEvTerm env (EvTypeable ev) =
   fmap EvTypeable $
   case ev of
-    EvTypeableTyCon tc ks ts -> EvTypeableTyCon tc ks `fmap` mapM zonk ts
+    EvTypeableTyCon tc ks    -> return (EvTypeableTyCon tc ks)
     EvTypeableTyApp t1 t2    -> do e1 <- zonk t1
                                    e2 <- zonk t2
                                    return (EvTypeableTyApp e1 e2)
diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs
index 5f54130..e83709c 100644
--- a/compiler/typecheck/TcInteract.hs
+++ b/compiler/typecheck/TcInteract.hs
@@ -1857,7 +1857,7 @@ matchTypeableClass clas k t loc
   doTyCon tc ks =
     case mapM kindRep ks of
       Nothing    -> return NoInstance
-      Just kReps -> mkSimpEv (EvTypeableTyCon tc kReps [])
+      Just kReps -> mkSimpEv (EvTypeableTyCon tc kReps)
 
   {- Representation for an application of a type to a type-or-kind.
   This may happen when the type expression starts with a type variable.



More information about the ghc-commits mailing list