default declarations

Daniel Fischer daniel.is.fischer at web.de
Sat Aug 5 20:11:20 EDT 2006


Hi,

apparently ghci doesn't take default declarations into account.
Inspired by a question on the hugs-users list I wrote

module BoolNum where

default (Bool, Rational)

instance Num Bool where
    (+) = (/=)
    (-) = (/=)
    (*) = (&&)
    negate x = x
    abs x = x
    signum x = x
    fromInteger = odd


and in hugs, as expected I get
BoolNum> 1
True

but in ghci, it's
*BoolNum> 1
1,

no defaulting apparently takes pkace.

Why?

Bug or feature ?

Cheers, Daniel
-- 

"In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt."
	-- Blair P. Houghton



More information about the Glasgow-haskell-users mailing list