[Haskell] GHC / Hugs Disagree on Constraints

Dominic Steinitz dominic.steinitz at blueyonder.co.uk
Mon Oct 4 15:39:59 EDT 2004


This seems counter-intuitive. If I declare a type variable in the 
context of an instance, I'd expect to be able to use it in the body. Is 
there any reason for Haskell 98 doesn't allow you to do this?

More importantly is there a way round this? I have a fairly simple 
requirement: a new type is created out of two types which are elements 
of Bounded and I'd like to declare the new type as Bounded based on the 
values of maxBound for each of the constituent types. Doing what the 
compiler suggests of declaring maxBound::(Bounded b => b) isn't going to 
help.

Interestingly, Bits has a function bitSize :: Bits a => a -> Int rather 
than a value so this issue doesn't arise (although you have use 
irrefutable pattern matching).

Dominic.

Simon Peyton-Jones wrote:
> Hugs does support scoped type variables bound by *type sigs in
> patterns*, but not by class or instance declarations.  So when you say
> 	(maxBound :: b)
> you are really saying
> 	(maxBound :: forall b. b)
> and it's that universal quantification that has no Bounded b context.
> 
> That's why you need -fglasgow-exts to compile it with GHC, to get the
> scoped type variables.
> 
> I've gotten so used to scoped type variables that I couldn't see why it
> wasn't Haskell 98, until I tried to compile without -fglasgow-exts.
> Then GHC says
>    Key.hs:99:
>     Could not deduce (Bounded b) from the context ()
>       arising from use of `maxBound' at Key.hs:99
>     Probable fix:
> 	Add (Bounded b) to the expected type of an expression
>     When checking the type signature of the expression:
> 	  maxBound :: forall b. b
> 
> which does at least point to the error.
> 
> Simon
> 
> | -----Original Message-----
> | From: haskell-bounces at haskell.org [mailto:haskell-bounces at haskell.org]
> On Behalf Of Dominic
> | Steinitz
> | Sent: 02 October 2004 12:04
> | To: haskell at haskell.org
> | Subject: [Haskell] GHC / Hugs Disagree on Constraints
> | 
> | GHC accepts this with -fglasgow-exts
> | 
> | instance (Ord a, Bits a, Bounded a, Integral a, LargeWord a,
> |                   Bits b, Bounded b, Integral b, LargeWord b) =>
> |     Bounded (LargeKey a b) where
> |        minBound = 0
> |        maxBound =
> |           fromIntegral $
> |           (1 + fromIntegral (maxBound::b))*
> |              (1 + fromIntegral (maxBound::a)) - 1
> | 
> | Hugs rejects it with +N -98 with
> | 
> | ERROR "Codec/Encryption/LargeKey.hs":94 - Cannot justify constraints
> in
> | type annotation
> | *** Expression    : maxBound
> | *** Type          : b
> | *** Given context : ()
> | *** Constraints   : Bounded b
> | 
> | Since I've already declared b to be Bounded, it looks like a bug in
> Hugs.
> | 
> | Dominic.
> | 
> | ===============================================================
> | ========
> | 
> | module Codec.Encryption.LargeKey
> |     (Word128,Word192,Word256,LargeWord) where
> | 
> | import Data.Word
> | import Data.Bits
> | import Numeric
> | import Char
> | 
> | -- Keys have certain capabilities.
> | 
> | class LargeWord a where
> |     largeWordToInteger :: a -> Integer
> |     integerToLargeWord :: Integer -> a
> |     largeWordPlus :: a -> a -> a
> |     largeWordAnd :: a -> a -> a
> |     largeWordOr :: a -> a -> a
> |     largeWordShift :: a -> Int -> a
> |     largeWordXor :: a -> a -> a
> |     largeBitSize :: a -> Int
> | 
> | -- Word64 is a key in the obvious way.
> | 
> | instance LargeWord Word64 where
> |     largeWordToInteger = toInteger
> |     integerToLargeWord = fromInteger
> |     largeWordPlus = (+)
> |     largeWordAnd = (.&.)
> |     largeWordOr = (.|.)
> |     largeWordShift = shift
> |     largeWordXor = xor
> |     largeBitSize = bitSize
> | 
> | -- Define larger keys from smaller ones.
> | 
> | data LargeKey a b = LargeKey a b
> |     deriving (Eq, Ord)
> | 
> | instance (Ord a, Bits a, LargeWord a, Bits b, LargeWord b) =>
> |     LargeWord (LargeKey a b) where
> |        largeWordToInteger (LargeKey lo hi) =
> |           largeWordToInteger lo + (2^(bitSize lo)) *
> largeWordToInteger hi
> |        integerToLargeWord x =
> |           let (h,l) =  x `quotRem` (2^(bitSize lo))
> |               (lo,hi) = (integerToLargeWord l, integerToLargeWord h)
> in
> |                  LargeKey lo hi
> |        largeWordPlus (LargeKey alo ahi) (LargeKey blo bhi) =
> |           LargeKey lo' hi' where
> |              lo' = alo + blo
> |              hi' = ahi + bhi + if lo' < alo then 1 else 0
> |        largeWordAnd (LargeKey alo ahi) (LargeKey blo bhi) =
> |           LargeKey lo' hi' where
> |              lo' = alo .&. blo
> |              hi' = ahi .&. bhi
> |        largeWordOr (LargeKey alo ahi) (LargeKey blo bhi) =
> |           LargeKey lo' hi' where
> |              lo' = alo .|. blo
> |              hi' = ahi .|. bhi
> |        largeWordOr (LargeKey alo ahi) (LargeKey blo bhi) =
> |           LargeKey lo' hi' where
> |              lo' = alo .|. blo
> |              hi' = ahi .|. bhi
> |        largeWordXor (LargeKey alo ahi) (LargeKey blo bhi) =
> |           LargeKey lo' hi' where
> |              lo' = alo `xor` blo
> |              hi' = ahi `xor` bhi
> |        largeWordShift w 0 = w
> |        largeWordShift (LargeKey lo hi) x =
> |           if bitSize lo < bitSize hi
> |              then LargeKey (shift lo x)
> |                            (shift hi x .|. (shift (conv lo) (x -
> | (bitSize lo))))
> |              else LargeKey (shift lo x)
> |                            (shift hi x .|. (conv $ shift lo (x -
> | (bitSize lo))))
> |           where conv = integerToLargeWord . largeWordToInteger
> |        largeBitSize ~(LargeKey lo hi) = largeBitSize lo + largeBitSize
> hi
> | 
> | instance (Ord a, Bits a, LargeWord a, Bits b, LargeWord b) => Show
> | (LargeKey a b) where
> |     showsPrec p = showInt . largeWordToInteger
> | 
> | instance (Ord a, Bits a, LargeWord a, Bits b, LargeWord b) =>
> |     Num (LargeKey a b) where
> |        (+) = largeWordPlus
> |        fromInteger = integerToLargeWord
> | 
> | -- Larger keys are instances of Bits provided their constituents are
> keys.
> | 
> | instance (Ord a, Bits a, LargeWord a, Bits b, LargeWord b) =>
> |     Bits (LargeKey a b) where
> |        (.&.) = largeWordAnd
> |        (.|.) = largeWordOr
> |        xor = largeWordXor
> |        shift = largeWordShift
> |        bitSize = largeBitSize
> | 
> | instance (Ord a, Bits a, Bounded a, Integral a, LargeWord a,
> |                   Bits b, Bounded b, Integral b, LargeWord b) =>
> |     Bounded (LargeKey a b) where
> |        minBound = 0
> |        maxBound =
> |           fromIntegral $
> |           (1 + fromIntegral (maxBound::b))*
> |              (1 + fromIntegral (maxBound::a)) - 1
> | 
> | instance (Ord a, Bits a, LargeWord a, Ord b, Bits b, LargeWord b) =>
> |     Integral (LargeKey a b) where
> |        toInteger = largeWordToInteger
> | 
> | instance (Ord a, Bits a, LargeWord a, Ord b, Bits b, LargeWord b) =>
> |     Real (LargeKey a b)
> | 
> | instance Enum (LargeKey a b)
> | 
> | type Word96  = LargeKey Word32 Word64
> | type Word128 = LargeKey Word64 Word64
> | type Word160 = LargeKey Word32 Word128
> | type Word192 = LargeKey Word64 Word128
> | type Word224 = LargeKey Word32 Word192
> | type Word256 = LargeKey Word64 Word192
> | _______________________________________________
> | Haskell mailing list
> | Haskell at haskell.org
> | http://www.haskell.org/mailman/listinfo/haskell
> 
> 
> 



More information about the Haskell mailing list