
I have a question about how numeric classes and type checking works. I have two functions that I think should behave the same but don't. -- I want to split n things up using a given list of fractions -- for example >allocate' 100 [1/3,1/3,1/3] -- [33,33,33] allocate' n fs = vs where vs = map (floor . (*n)) fs -- I want to find anything left over eventually I will want to -- return what is unallocated as well but for now allocated -- and unallocated are not used! allocate n fs = vs where vs = map (floor . (*n)) fs allocated = sum vs unallocated = n - allocated When I load these function in the top level everything looks good [1 of 1] Compiling Main ( allocate.hs, interpreted ) Ok, modules loaded: Main.main *Main> allocate' 100 [1/3,1/3,1/3] [33,33,33] *Main> allocate 100 [1/3,1/3,1/3] <interactive>:1:0: Ambiguous type variable `t' in the constraints: `Integral t' arising from a use of `allocate' at <interactive>:1:0-25 `RealFrac t' arising from a use of `allocate' at <interactive>:1:0-25 Probable fix: add a type signature that fixes these type variable(s) *Main> I mixed up my types when finding the allocated and unallocated, but I am not sure why it produces an error when unallocated and allocated are never used? Shouldn't the two functions be compiled down to the same thing? Suggestions on how to do this more elegantly as well as pointers for understanding numeric type classes would be appreciated. TIA Lloyd

The important thing is the type of "floor":
floor :: (Integral b, RealFrac a) => a -> b
That is, if you have a real, fractional type, and you apply floor to
it, you'll get some integral type.
If you look at allocate', you'll see
allocate' :: (RealFrac in, Integral out) => in -> [in] -> [out]
When you apply this function without any other information, you're
applying Haskell's defaulting rules; I believe you'll get Double for
"in" and Integer for "out".
But in allocate, you have two additional declarations:
allocated = sum vs
therefore, allocated :: out
unallocated = n - sum vs
unallocated :: ?
(-) has type (Num a) => a -> a -> a. Since both RealFrac and Integral
have Num as a superclass, that constraint goes away. But you still
end up unifying "in" with "out". Now you need a type that is both a
real-fractional type and an integer type. Unsurprisingly, no such
type exists.
To fix:
unallocated = n - fromIntegral (sum vs)
-- ryan
On Fri, Feb 29, 2008 at 12:09 AM, Lloyd Smith
I have a question about how numeric classes and type checking works. I have two functions that I think should behave the same but don't.
-- I want to split n things up using a given list of fractions -- for example >allocate' 100 [1/3,1/3,1/3] -- [33,33,33] allocate' n fs = vs where vs = map (floor . (*n)) fs
-- I want to find anything left over eventually I will want to -- return what is unallocated as well but for now allocated -- and unallocated are not used! allocate n fs = vs where vs = map (floor . (*n)) fs allocated = sum vs unallocated = n - allocated
When I load these function in the top level everything looks good
[1 of 1] Compiling Main ( allocate.hs, interpreted ) Ok, modules loaded: Main.main *Main> allocate' 100 [1/3,1/3,1/3] [33,33,33] *Main> allocate 100 [1/3,1/3,1/3]
<interactive>:1:0: Ambiguous type variable `t' in the constraints: `Integral t' arising from a use of `allocate' at <interactive>:1:0-25 `RealFrac t' arising from a use of `allocate' at <interactive>:1:0-25 Probable fix: add a type signature that fixes these type variable(s) *Main>
I mixed up my types when finding the allocated and unallocated, but I am not sure why it produces an error when unallocated and allocated are never used? Shouldn't the two functions be compiled down to the same thing?
Suggestions on how to do this more elegantly as well as pointers for understanding numeric type classes would be appreciated.
TIA Lloyd _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, Feb 29, 2008 at 7:09 PM, Lloyd Smith
I mixed up my types when finding the allocated and unallocated, but I am not sure why it produces an error when unallocated and allocated are never used? Shouldn't the two functions be compiled down to the same thing?
Suggestions on how to do this more elegantly as well as pointers for understanding numeric type classes would be appreciated.
Let's have a look at the types involved: Prelude> :t allocate' allocate' :: (RealFrac a, Integral b) => a -> [a] -> [b] Prelude> :t allocate allocate :: (Integral b, RealFrac b) => b -> [b] -> [b] We can see that (allocate') takes RealFrac arguments and returns an Integral result. So far so good. However, the signature for (allocate) is slightly different: it requires that the argument and result types be the same. Unfortunately, this is impossible, because no type can have a sensible instance for both RealFrac and Integral. Why do the two functions have different signatures? The obvious culprit is the "unused" code in the definition of (allocate'). Notice that (allocated) will use the same underlying type as (vs), which is the "return" type of the function. However, unallocated tries to subtract (allocated) from (n), and (n) has the "argument" type of the function. The type-checker sees the two types must be the same in order for the subtraction to work, and so the overall function ends up with a nonsense type. The moral of the story is that even though that extra code might not execute at run-time, it can still influence type-inference and type-checking, which is your actual problem here. The solution for your woes is probably to insert a (fromIntegral) somewhere. I suspect that allocated = fromIntegral $ sum vs will do the trick. Hope this helps, Stuart
participants (3)
-
Lloyd Smith
-
Ryan Ingram
-
Stuart Cook