[commit: ghc] typeable-with-kinds: Remove warnings (b909149)

git at git.haskell.org git at git.haskell.org
Wed Feb 11 02:14:15 UTC 2015


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

On branch  : typeable-with-kinds
Link       : http://ghc.haskell.org/trac/ghc/changeset/b909149233bc0298ddbcb789f8d0597cad3e9c3c/ghc

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

commit b909149233bc0298ddbcb789f8d0597cad3e9c3c
Author: Iavor S. Diatchki <diatchki at galois.com>
Date:   Tue Feb 10 17:33:06 2015 -0800

    Remove warnings


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

b909149233bc0298ddbcb789f8d0597cad3e9c3c
 compiler/typecheck/TcInteract.hs | 10 ++++------
 1 file changed, 4 insertions(+), 6 deletions(-)

diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs
index 1a01441..53ef0e6 100644
--- a/compiler/typecheck/TcInteract.hs
+++ b/compiler/typecheck/TcInteract.hs
@@ -1639,9 +1639,7 @@ matchClassInst _ clas [ ty ] _
     = panicTcS (text "Unexpected evidence for" <+> ppr (className clas)
                      $$ vcat (map (ppr . idType) (classMethods clas)))
 
-
-
-matchClassInst inerts clas [k,t] loc
+matchClassInst _ clas [k,t] loc
   | className clas == typeableClassName = matchTypeableClass clas k t loc
 
 matchClassInst inerts clas tys loc
@@ -1796,8 +1794,8 @@ matchTypeableClass clas k t loc
   | isForAllTy k                               = return NoInstance
   | Just (tc, ks_tys) <- splitTyConApp_maybe t = doTyConApp tc ks_tys
   | Just (f,kt)       <- splitAppTy_maybe t    = doTyApp f kt
-  | Just n            <- isNumLitTy t          = mkEv [] (EvTypeableTyLit t)
-  | Just s            <- isStrLitTy t          = mkEv [] (EvTypeableTyLit t)
+  | Just _            <- isNumLitTy t          = mkEv [] (EvTypeableTyLit t)
+  | Just _            <- isStrLitTy t          = mkEv [] (EvTypeableTyLit t)
   | otherwise                                  = return NoInstance
 
   where
@@ -1831,7 +1829,7 @@ matchTypeableClass clas k t loc
   -- Representation for concrete kinds.  We just use the kind itself,
   -- but first check to make sure that it is "simple" (i.e., made entirely
   -- out of kind constructors).
-  kindRep ki = do (kc,ks) <- splitTyConApp_maybe ki
+  kindRep ki = do (_,ks) <- splitTyConApp_maybe ki
                   mapM_ kindRep ks
                   return ki
 



More information about the ghc-commits mailing list