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

On branch  : type-nats

http://hackage.haskell.org/trac/ghc/changeset/7655c718d56666a918c06f6d4e32d98482620b9c

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

commit 7655c718d56666a918c06f6d4e32d98482620b9c
Author: Iavor S. Diatchki <[email protected]>
Date:   Sat Jan 7 12:59:41 2012 -0800

    Go back to using an Integer as evidence, rather then just a Word.

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

 compiler/deSugar/DsBinds.lhs      |    9 +--------
 compiler/typecheck/TcInteract.lhs |    4 +---
 2 files changed, 2 insertions(+), 11 deletions(-)

diff --git a/compiler/deSugar/DsBinds.lhs b/compiler/deSugar/DsBinds.lhs
index b6e0969..7ff5e69 100644
--- a/compiler/deSugar/DsBinds.lhs
+++ b/compiler/deSugar/DsBinds.lhs
@@ -66,7 +66,6 @@ import FastString
 import Util
 
 import MonadUtils
-import Data.Word(Word)
 import Control.Monad(liftM)
 \end{code}
 
@@ -715,13 +714,7 @@ dsEvTerm (EvSuperClass d n)
     sc_sel_id  = classSCSelId cls n    -- Zero-indexed
     (cls, tys) = getClassPredTys (evVarPred d)    
 
--- It would be better to make an Integer expression here, but this would
--- require quite a bit of the surrounding code to be monadified.
--- In the intereset of simplicity (and keeping changes incremental) we
--- leave this for a later day.
-dsEvTerm (EvInteger n)
-  | n > fromIntegral (maxBound :: Word) = panic "dsEvTerm: Integer too big!"
-  | otherwise = return $ mkWordExprWord (fromInteger n)
+dsEvTerm (EvInteger n) = mkIntegerExpr n
 
 ---------------------------------------
 dsTcCoercion :: TcCoercion -> (Coercion -> CoreExpr) -> CoreExpr
diff --git a/compiler/typecheck/TcInteract.lhs 
b/compiler/typecheck/TcInteract.lhs
index 4da4c9f..e55816e 100644
--- a/compiler/typecheck/TcInteract.lhs
+++ b/compiler/typecheck/TcInteract.lhs
@@ -57,7 +57,6 @@ import Pair ( pSnd )
 import UniqFM
 import FastString ( sLit ) 
 import DynFlags
-import Data.Word(Word)
 \end{code}
 **********************************************************************
 *                                                                    * 
@@ -1775,8 +1774,7 @@ matchClassInst :: InertSet -> Class -> [Type] -> 
WantedLoc -> TcS LookupInstResu
 
 matchClassInst _ clas [ ty ] _
   | className clas == typeNatClassName
-  , Just n <- isNumberTy ty
-  , n <= fromIntegral (maxBound :: Word) = return (GenInst [] (EvInteger n))
+  , Just n <- isNumberTy ty = return (GenInst [] (EvInteger n))
 
 
 matchClassInst inerts clas tys loc



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to