[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 + fromIntegral (maxBound::a)) - 1

Hugs rejects it with +N -98 with


One fix is to bring type variables into the local scope, for
example,


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 :: (LargeKey a b) =
         fromIntegral $
         (1 + fromIntegral (maxBound::b))*
            (1 + fromIntegral (maxBound::a)) - 1


You still need -98 flag for Hugs. Another solution is totally
Haskell98: introduce two functions


aoflk:: (LargeKey a b) -> a; aoflk = undefined
boflk:: (LargeKey a b) -> b; boflk = undefined


then maxBound can be implemented as


      maxBound = result where
        result =
         fromIntegral $
         (1 + fromIntegral (maxBound `asTypeOf` (boflk result)))*
            (1 + fromIntegral (maxBound `asTypeOf` (aoflk result))) - 1


The apparent recursion in the above definition is superficial. The
definition isn't actually recursive. We merely need the type of the
'result' rather than its value.



Oleg,

Did you get the first solution to work? When I tried it with hugs -98 I got

ERROR "Codec/Encryption/LargeKey.hs":109 - Syntax error in input (unexpected `=')

ghc with -fglasgow-exts accepts it.

Dominic.


_______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Reply via email to