[Haskell-cafe] unresolved overloading

Claus Reinke claus.reinke at talk21.com
Thu Jul 12 13:04:01 EDT 2007


>g x             = [2] ++ [3,5..truncate(sqrt x)]
>p  n            = fp n (g  n)
>fp n [ ]        = True
>fp n  (x:xs)  = if (mod n x) == 0 then False else fp n xs

>ERROR - Unresolved overloading
>*** Type       : (RealFrac a, Floating a, Integral a) => Bool
>*** Expression : p 103

>I know why, there is no type that is at the same time: RealFrac,
>Floating and Integral;  but I don´t know how to solve.
>What kind of type casting or type definition can I use to fix the error?

this can be turned into a nice small example for many things are a
right, and many things that are wrong with haskell numeric programs
(cf. http://www.haskell.org/haskellwiki/Generic_numeric_type ).

not only are the typical type errors confusing, and give little help
with fixing the issue (deliberately highlighting unresolved choices
rather than choosing arbitrary defaults, but not even suggesting
possible conversions with pros and cons [*]), but placating the
type system in various ways is not sufficient to guarantee useability,
or intended results, and seemingly simple rewrites may require
type system extensions to remain simple.

first, note that the definitions typecheck even though it would
be difficult to find a correct way of using them. next, consider
the variations appended below (using different conversions,
or breaking the strong connection introduced by the lambda-
bound 'n' in the original 'p0'). again, this typechecks, and can
indeed be used, but that is no guarantee that the variants are
equivalent, or do what was intended, or even work for other
use cases. for fun, try changing '103' to '103.5' (and no, you
can't abstract that to a where-clause unless you rely on
'no-monomorphism-restriction'), then comment out the lines
in main that start raising errors one by one, then run the
remaining lines and enjoy the result. then consider whether
this is indeed an intended use case.

i'm all for safe, explicit coercions rather than unsafe defaults.
but typechecking definitions is not sufficient to guarantee
either useability or correctness here, and type errors give little
help in clarifying intentions and correcting code. in other words,
there is something wrong in this part of haskell, even below
the concerns that usually lead to alternative numerical preludes.

i'm not at all sure to what extent this can be improved, but
when the topic comes up, good examples are usually hard
to come by, so i just wanted to record this one here for the
mailing-list archives.

claus

[*] sometimes i wonder whether there should be a
    WrongNum type, which would imply all the usual
    default conversions of scripting languages, but would
    generate warnings at each dubious usage site (about
    comparing Doubles, or losing precision, or possible
    overflows, ..).

    that way, beginners might at least get something running
    that they could then improve until the warnings are gone,
    avoiding the blank-page effect. instead of saying "i have
    no idea what to do here", the system would say "i'm
    defaulting to Double here, but that might not be a good
    idea, so please confirm this decision explicitly in the code",
    or "i'm applying this implicit conversion here, but this has
    semantic consequences, so you probably want to choose
    this or a related conversion explicitly in your code"..

---------------------------------------------- code variations
{-# OPTIONS_GHC -fno-monomorphism-restriction #-}
{-# OPTIONS_GHC -fglasgow-exts #-}

g x           = [2] ++ [3,5..truncate(sqrt x)]

p0 n          = fp n (g  n)

p1a n         = fp (truncate n) (g  n)
p1b n         = fp (round n) (g  n)
p1c n         = fp n (g  $ fromIntegral n)

p2 n n'       = fp n (g  n')

p3  :: (forall a. Num a => a) -> Bool
p3  n          = fp n (g  n)

fp n [ ]      = True
fp n  (x:xs)  = if (mod n x) == 0 then False else fp n xs

main = do
--  print $ p0 103 -- original, with type error
  print $ p1a 103
  print $ p1b 103
  print $ p1c 103
  print $ p2 103 103
  print $ let x = 103 in p2 x x -- requires no-monomorphism-restriction
  print $ let x _ = 103 in p2 (x ()) (x ())
  print $ p3 103 -- requires glasgow-exts





More information about the Haskell-Cafe mailing list