[Haskell-beginners] Puzzling type error

Daniel Fischer daniel.is.fischer at web.de
Sun Aug 24 14:27:25 EDT 2008


Am Sonntag, 24. August 2008 19:38 schrieb Logesh Pillay:
> I've written the following implementation of the algorithm in this
> article http://www.afjarvis.staff.shef.ac.uk/maths/jarvisspec02.pdf
>
> sqRoot n scale = sqRoot' (5*n) 5
>   where
>   sqRoot' a b
>
>     | floor (logBase 10 b) >= scale = div b 10
>     | a >= b                        = sqRoot' (a-b) (b+10)
>     | otherwise                     = sqRoot' (a*100) ((100 * (div b
>
> 10)) + (mod b 10))
>
> Since this involves whole numbers only, I was surprised by the following
> run-time error.
>
> *Main> sqRoot 2 5
>
> <interactive>:1:0:
>     Ambiguous type variable `t' in the constraints:
>       `RealFrac t' arising from a use of `sqRoot' at <interactive>:1:0-9
>       `Floating t' arising from a use of `sqRoot' at <interactive>:1:0-9
>       `Integral t' arising from a use of `sqRoot' at <interactive>:1:0-9
>     Probable fix: add a type signature that fixes these type variable(s)
>
> What am I missing?
>
> Logesh Pillay
>

There is no automatic conversion between different numeric types, you must do 
that explicitly, except for numeric literals.

From the guard a >= b (and the expression a-b) follows that a and b must have 
the same type.
From the expressions (b `div` 10) and (b `mod` 10) follows that that type must 
belong to the type class Integral.
From the use of logBase follows that that type must belong to the type class 
Floating.
Finally, from the use of floor follows that that type must also belong to the 
type class RealFrac.

If you ask GHCi for the type of sqRoot, it will tell you:
*Main> :t sqRoot
sqRoot :: (Integral t, Floating t, RealFrac t, Integral b) => t -> b -> t

The problem occurs when you want to evaluate sqRoot, because then the types t 
and b must be decided. Since only standard numeric type classes are involved, 
GHCi is willing to default the ambiguous types, so it will look if it can 
find a type which simultaneously belongs to all three type classes in the 
default list (I think the default list GHCi uses is (Integer, Double)).

Of course it doesn't find such a type, so it complains.
Note, however, that it doesn't complain about the scale parameter, that can be 
defaulted to Integer without any problem.

The ugly (and insane) fix would be to provide instances of Fractional, 
RealFrac and Floating for Integer or an instance of Integral for Double.

The good fix is to insert calls to the apprpriate conversion function where 
necessary, for example

sqRoot n scale = sqRoot' (5*n) 5
  where
  sqRoot' a b
    | floor (logBase 10 $ fromIntegral b) >= scale = div b 10
    | a >= b    = sqRoot' (a-b) (b+10)
    | otherwise = sqRoot' (a*100) ((100 * (div b 10)) + (mod b 10))

works.

HTH,
Daniel


More information about the Beginners mailing list