[Haskell-cafe] What is a number. (Was: Num instances for
2-dimensional types)
Iavor Diatchki
iavor.diatchki at gmail.com
Tue Oct 6 13:35:47 EDT 2009
Hi,
On Tue, Oct 6, 2009 at 2:37 AM, Henning Thielemann
<lemming at henning-thielemann.de> wrote:
> Numeric literals are treated as Integer or Rational, and are then converted
> with the function fromInteger or fromRational, respectively, to the required
> type. Whatever fromInteger function is in scope, will be used. If
> fromInteger is in a class other than Num (in NumericPrelude it is Ring, but
> it can be also a function that is not a class method), then number literals
> have a type like:
> 2 :: MyNumClass a => a
This is only the case if you use GHC's NoImplicitPrelude extension,
otherwise the "fromInteger" of the Prelude is used, even if it is not
in scope. Here is an example:
module A where
boolLit :: Integer -> Bool
boolLit 0 = False
boolLit _ = True
{-# LANGUAGE NoImplicitPrelude #-}
module Main where
import A(boolLit)
import Prelude(Integer,Bool,print)
fromInteger :: Integer -> Bool
fromInteger = boolLit
main = print 0
Note that 0 means different things in the different modules!
-Iavor
More information about the Haskell-Cafe
mailing list