[Haskell-beginners] beginner's type error

John Dorsey haskell at colquitt.org
Fri Apr 3 02:33:07 EDT 2009


Ivan,

> without engaging my brain too much, given what you've said, then why
> is "10" both integral and floating point? why not "10" being integral
> and "10.0" being floating point?

The literal "10", as it appears in Haskell source, stands for something
that can take on any numeric type, but as soon as you use it in a context
that constrains it, well, it gets constrained!

"10" can be integral, or it can be floating point.  As I think Jason was
saying, *if* there was a type that was both integral and floating point,
then 10 could represent something of that type.  But there's no *sensible*
type that has both integral and floating point nature.  (At least none that
comes to mind.  Maybe you could do something with symbolic manipulation
that would make sense.)

Leaving behind sensible types, we can define one that's both integral
and fractional.  I'm going to violate all kinds of commonly assumed (but
unenforced) laws of the numeric classes, in an act of self-loathing, so
enjoy the following abomination!  The code is appended at the end of
this message.

dorsey at elwood:~/src/scratch$ ghci int-float.hs
*Main> :t munge
munge :: IntFloat -> IntFloat
*Main> :t munge 10
munge 10 :: IntFloat
*Main> fromIntegral (munge 10)
42

If you look at the code for munge below, you'll see that I've mixed
integral operations (div) with floating point operations (**) and
fractional operations (/).

I have no trouble applying munge to 10.  The literal "10" (which really means
"fromIntegral 10") takes on the right type because it has to to match munge's
argument type.

So why would I choose to do this terrible thing?  To illustrate that:

1) The open world assumption of Haskell type classes implies that
   a type like this could be definied later, even if it doesn't exist now.

2) Even though you can do this and obey the type rules, I had to use
   a silly type, with very silly class instance definitions.  Integral
   things just aren't fractional!

To answer you other specific question, about why they didn't just
distinguish "10" from "10.0" as some other languages do, the original
motivation was well before my time.  But it does seem to me that being
able to use "10" to refer not only to Integers and Floats, but also to
Ints, Int16s, Doubles, and many unforseen numeric types, was a clever
choice.  Sadly, numeric literals make the short-list of things that
confuse Haskell neophites the most.

I hope all this is at least either interesting or helpful.

Regards,
John


-- int-float.hs

-- a datatype inhabiting floating and integral classes,
-- but which doesn't model numerics particularly well

data IntFloat = IF String
  deriving (Show, Eq, Ord)

munge :: IntFloat -> IntFloat
munge x = x / x `div` x ** x

instance Num IntFloat where
  _ + _ = IF "sum"
  _ - _ = IF "difference"
  _ * _ = IF "product"
  negate _ = IF "negation"
  abs _ = IF "abs"
  signum _ = IF "signum"
  fromInteger _ = IF "fromInteger"

instance Integral IntFloat where
  quot _ _ = IF "quot"
  rem  _ _ = IF "rem"
  div  _ _ = IF "div"
  mod  _ _ = IF "mod"
  quotRem _ _ = (IF "quotRem quot", IF "quotRem rem")
  divMod  _ _ = (IF "divMod div", IF "divMod mod")
  toInteger _ = 42

instance Floating IntFloat where
  pi = IF "pi"
  exp _ = IF "exp"
  sqrt _ = IF "sqrt"
  log _ = IF "log"
  (**) _ _ = IF "**"
  logBase _ _ = IF "logBase"
  sin _ = IF "sin"
  tan _ = IF "tan"
  cos _ = IF "cos"
  asin _ = IF "asin"
  atan _ = IF "atan"
  acos _ = IF "acos"
  sinh _ = IF "sinh"
  tanh _ = IF "tanh"
  cosh _ = IF "cosh"
  asinh _ = IF "asinh"
  atanh _ = IF "atanh"
  acosh _ = IF "acosh"

instance Real IntFloat where
  toRational _ = toRational 42

instance Enum IntFloat where
  succ _ = IF "succ"
  pred _ = IF "pred"
  toEnum _ = IF "toEnum"
  fromEnum _ = 42
  enumFrom _ = [IF "enumFrom"]
  enumFromThen _ _ = [IF "enumFromThen"]
  enumFromTo _ _ = [IF "enumFromTo"]
  enumFromThenTo _ _ _ = [IF "enumFromThenTo"]

instance Fractional IntFloat where
  (/) _ _ = IF "/"
  recip _ = IF "recip"
  fromRational _ = IF "fromRational"



More information about the Beginners mailing list