On Friday 23 July 2010 00:21:49, Chad Scherrer wrote: > Hello cafe, > > I'm trying to do some things with bounded indices so I can carry > around arrays (well, Vectors, really) without needing to refer to the > bounds. > > For example, if I know my indices are Bool values, I can do > > > rangeSize (minBound, maxBound :: Bool) > > 2 > > I'd like to be able to do this in general, but... > > > :t rangeSize (minBound, maxBound) > > <interactive>:1:11: > Ambiguous type variable `a' in the constraints: > `Bounded a' > arising from a use of `minBound' at <interactive>:1:11-18 > `Ix a' arising from a use of `rangeSize' at <interactive>:1:0-29 > Probable fix: add a type signature that fixes these type variable(s) > > I thought it might help to put it into a module and do a better job > with the type, like this: >
{-# LANGUAGE ScopedTypeVariables #-} bdRangeSize :: forall i. (Ix i, Bounded i) => i -> Int > bdRangeSize :: (Ix i, Bounded i) => i -> Int > bdRangeSize _ = rangeSize (minBound, maxBound :: i) > or, H98, without ScopedTypeVariables and forall, bdRangeSize x = rangeSize (minBound `asTypeOf` x, maxBound) > but I still have problems: > > MyArray.hs:22:36: > Could not deduce (Bounded i1) from the context () > arising from a use of `maxBound' at MyArray.hs:22:36-43 > Possible fix: > add (Bounded i1) to the context of an expression type signature > In the expression: maxBound :: i > In the first argument of `rangeSize', namely > `(minBound, maxBound :: i)' > In the expression: rangeSize (minBound, maxBound :: i) > > I thought maybe it's an existential types problem or something, but I > don't understand why it would be coming up here. Any thoughts? > > Oh yes, and I'm using GHC version 6.12.1. > > Thanks, > Chad _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe