On Jul 23, 2010, at 12:21 AM, Chad Scherrer wrote:

bdRangeSize :: (Ix i, Bounded i) => i -> Int
bdRangeSize _ = rangeSize (minBound, maxBound :: i)

Unlike intended, the `i` in the type annotation to `maxBound` is not the same as the `i` in the signature of `bdRangeSize`. You need to enable ScopedTypeVariables and explicitly quantify the type variable `i` in order to refer to it in the annotation of `maxBound`:

    {-# LANGUAGE ScopedTypeVariables #-}

    import Data.Ix

    bdRangeSize :: forall i . (Ix i, Bounded i) => i -> Int
    bdRangeSize _ = rangeSize (minBound, maxBound :: i)

Cheers,
Sebastian

--
Underestimating the novelty of the future is a time-honored tradition.
(D.G.)



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to