Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/4f27b5710232be868121cce5191c062999107327

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

commit 4f27b5710232be868121cce5191c062999107327
Author: Simon Peyton Jones <[email protected]>
Date:   Tue Jan 8 09:02:48 2013 +0000

    Comment out IsEven, isEven, and friends, because the type is ambiguous
    
    It will become un-ambiguous when Iavor teaches the type inference
    engine to prove more things, but until then this stuff is not useful.

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

 GHC/TypeLits.hs |   16 ++++++++++++----
 1 files changed, 12 insertions(+), 4 deletions(-)

diff --git a/GHC/TypeLits.hs b/GHC/TypeLits.hs
index ed1f205..befda8e 100644
--- a/GHC/TypeLits.hs
+++ b/GHC/TypeLits.hs
@@ -34,7 +34,9 @@ module GHC.TypeLits
 
     -- * Destructing type-nat singletons.
   , isZero, IsZero(..)
-  , isEven, IsEven(..)
+
+-- Commented out; see definition below; SLPJ Jan 13
+--  , isEven, IsEven(..)
 
 
     -- * Matching on type-nats
@@ -51,7 +53,7 @@ import GHC.Base(String)
 import GHC.Read(Read(..))
 import GHC.Show(Show(..))
 import Unsafe.Coerce(unsafeCoerce)
-import Data.Bits(testBit,shiftR)
+-- import Data.Bits(testBit,shiftR)
 import Data.Maybe(Maybe(..))
 import Data.List((++))
 
@@ -193,9 +195,16 @@ instance Show (IsZero n) where
   show IsZero     = "0"
   show (IsSucc n) = "(" ++ show n ++ " + 1)"
 
+{- ----------------------------------------------------------------------------
+
+This IsEven code is commented out for now.  The trouble is that the 
+IsEven constructor has an ambiguous type, at least until (+) becomes
+suitably injective. 
+
 data IsEven :: Nat -> * where
   IsEvenZero :: IsEven 0
   IsEven     :: !(Sing (n+1)) -> IsEven (2 * n + 2)
+  IsEven     :: !(Sing (n)) -> IsEven (2 * n + 1)
   IsOdd      :: !(Sing n)     -> IsEven (2 * n + 1)
 
 isEven :: Sing n -> IsEven n
@@ -208,8 +217,7 @@ instance Show (IsEven n) where
   show (IsEven x) = "(2 * " ++ show x ++ ")"
   show (IsOdd  x) = "(2 * " ++ show x ++ " + 1)"
 
-
---------------------------------------------------------------------------------
+------------------------------------------------------------------------------ 
-}
 
 -- | Unary implemenation of natural numbers.
 -- Used both at the type and at the value level.



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

Reply via email to