hello,

yep this is annoying.  there is a flag in GHC to warn you about
such missing methods:
-fwarn-missing-methods

another thihng to watch out for are classes where there are mutually recursive defaults (like the Eq class). forgetting to define a method there will still loop, but won't be caught by the compiler even with the flag above, as technically there are no undefined methods. it would be nice if we incororated in the language the
"minimum required definition" thing that is currently in comments.


bye
iavor




Graham Klyne wrote:
I came across a surprising feature of Haskell's class system.

If I declare an instance of a class, but do not define one of the functions of that class, the compiler does not notice. Even if I try to reference the undefined function, the compiler doesn't notice. It's only when I try to evaluate the missing function, at run-time, that I get an error message.

I now see this is correct behaviour:
[[
If no binding is given for some class method then the corresponding default class method in the class declaration is used (if present); if such a default does not exist then the class method of this instance is bound to undefined and no compile-time error results.
]]
-- [Report, section 4.3.2]


Is there a rationale for allowing class methods to be undefined for an instance?

#g
--

[[
-- Missing class functions not detected?
-- SpikeMissingClassFunctions.hs

class (Show (m a), Show a) => C m a where
    a1 :: [a] -> m a
    a2 :: m a -> [a]
    a3 :: m a -> Bool

data MyC a = MyC [a]

instance (Show a) => C MyC a where
    a1 s         = MyC s
    a2 (MyC s)   = s

instance (Show a) => Show (MyC a) where
    show (MyC s) = "MyC "++(show s)

test1 = a1 [1,2,3] :: MyC Int     -- "MyC [1,2,3]"
test2 = a2 test1                  -- "[1,2,3]"
test3 = a3 test1                  -- "Program error: Undefined member: a3"
]]

Hugs log:
[[
Reading file "D:\Cvs\DEV\HaskellRDF\Spike\SpikeMissingClassFunctions.hs":

Hugs session for:
C:\DEV\Hugs98\libraries\Hugs\Prelude.hs
C:\DEV\Hugs98\libraries\Prelude.hs
D:\Cvs\DEV\HaskellRDF\Spike\SpikeMissingClassFunctions.hs
Main> test1
MyC [1,2,3]
Main> test2
[1,2,3]
Main> test3

Program error: Undefined member: a3
]]


------------------- Graham Klyne <[EMAIL PROTECTED]> PGP: 0FAA 69FF C083 000B A2E9 A131 01B9 1C7A DBCA CB5E

_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to