[Haskell-cafe] Re: Trying to write 'safeFromInteger'
Peter Verswyvelen
bugfact at gmail.com
Tue Apr 7 19:09:34 EDT 2009
You must explicitly quantify the type parameters in the top level function
when you use this extension. This works:
{-# LANGUAGE ScopedTypeVariables #-}
safeFromInteger :: forall a . (Num a, Integral a, Bounded a) => Integer ->
Maybe a
safeFromInteger i =
if i > (toInteger (maxBound :: a))
then Nothing
else Just (fromInteger i)
On Tue, Apr 7, 2009 at 11:42 PM, Kannan Goundan <kannan at cakoose.com> wrote:
> Max Rabkin <max.rabkin <at> gmail.com> writes:
>
> > The problem with your code is that the type of maxBound is
> > unspecified. You need (maxBound `asTypeOf` i), or enable
> > ScopedTypeVariables and use (maxBound :: a) (I think).
>
> I tried doing the (maxBound :: a) thing, but got another confusing error:
>
> safeFromInteger :: (Num a, Integral a, Bounded a) => Integer -> Maybe a
> safeFromInteger i =
> if i > (toInteger (maxBound :: a))
> then Nothing
> else Just (fromInteger i)
>
> # ghci -XScopedTypeVariables Test.hs
>
> Test.hs:3:20:
> Could not deduce (Bounded a1) from the context ()
> arising from a use of `maxBound' at TestIntegerBounds.hs:3:20-27
> Possible fix:
> add (Bounded a1) to the context of an expression type signature
> In the first argument of `toInteger', namely `(maxBound :: a)'
> In the second argument of `(>)', namely
> `(toInteger (maxBound :: a))'
> In the expression: i > (toInteger (maxBound :: a))
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090408/caaf9e02/attachment.htm
More information about the Haskell-Cafe
mailing list