[Haskell-cafe] is there something special about the Num instance?

Yuriy yuriy.halytskyy at gmail.com
Wed Dec 3 18:21:37 EST 2008


 Numeric literals are special. Their type is (Num t) => t, so it can
 belong to any type that is instance of Num. Whereas Test belongs to
 Test type only so you cannot call bar on any instance of Foo.

 So your pattern constrains type signature of bar more then it is
 constrained by class declaration. 
 
 On Wed, Dec 03, 2008 at 03:05:37PM -0800, Anatoly Yakovenko wrote:
 > module Test where
 > --why does this work:
 > data Test = Test
 > 
 > class Foo t where
 >    foo :: Num v => t -> v -> IO ()
 > 
 > instance Foo Test where
 >    foo _ 1 = print $ "one"
 >    foo _ _ = print $ "not one"
 > 
 > --but this doesn't?
 > 
 > class Bar t where
 >    bar :: Foo v => t -> v -> IO ()
 > 
 > instance Bar Test where
 >    bar _ Test = print $ "test"
 >    bar _ _ = print $ "not test"
 > _______________________________________________
 > Haskell-Cafe mailing list
 > Haskell-Cafe at haskell.org
 > http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list