Re: [Haskell] GHC / Hugs Disagree on Constraints

2004-10-10 Thread oleg
Dominic Steinitz wrote: > Did you get the first solution to work? When I tried it with hugs -98 I got Yes, in the process discovering some interesting behavior of Hugs. Here's the complete code that works with Hugs > module Foo where > > class Bits a > > instance (Ord a, Bits a, Bounded a, Inte

Re: [Haskell] GHC / Hugs Disagree on Constraints

2004-10-09 Thread Dominic Steinitz
[EMAIL PROTECTED] wrote: 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

Re: [Haskell] GHC / Hugs Disagree on Constraints

2004-10-05 Thread Christian Sievers
Dominic Steinitz asked: > Is asTypeOf really Haskell 98? Yes, it is in the Prelude. And there is no special magic, it is Haskell-98-implementable, see http://haskell.org/onlinereport/standard-prelude.html#$vasTypeOf Bye Christian Sievers ___ Haskell m

Re: [Haskell] GHC / Hugs Disagree on Constraints

2004-10-05 Thread Dominic Steinitz
[EMAIL PROTECTED] wrote: 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

[Haskell] GHC / Hugs Disagree on Constraints

2004-10-04 Thread oleg
> 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

Re: [Haskell] GHC / Hugs Disagree on Constraints

2004-10-04 Thread Dominic Steinitz
Of Dominic | Steinitz | Sent: 02 October 2004 12:04 | To: [EMAIL PROTECTED] | 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, LargeWor

RE: [Haskell] GHC / Hugs Disagree on Constraints

2004-10-04 Thread Simon Peyton-Jones
Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Dominic | Steinitz | Sent: 02 October 2004 12:04 | To: [EMAIL PROTECTED] | Subject: [Haskell] GHC / Hugs Disagree on Constraints | | GHC accepts this with -fglasgow-exts | | instance (Ord a, Bits a, Boun

[Haskell] GHC / Hugs Disagree on Constraints

2004-10-02 Thread Dominic Steinitz
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))*