is there something special about the Num instance?

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"

Am Donnerstag, 4. Dezember 2008 00:05 schrieb Anatoly Yakovenko:
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"
Because bar has to work for all types which belong to class Foo, but actually uses the type Test. This is what the error message Test.hs:18:10: Couldn't match expected type `v' against inferred type `Test' `v' is a rigid type variable bound by the type signature for `bar' at Test.hs:15:15 In the pattern: Test In the definition of `bar': bar _ Test = print $ "test" In the definition for method `bar' tells you. In the signature of bar, you've said that bar works for all types v which are members of Foo. Test is a monomorphic value of type Test, so it can't have type v for all v which belong to Foo. It doesn't matter that there is so far only the one instance of Foo, there could be others defined in other modules. The first works because the type of 1 in the definition of foo is defaulted to Integer (or whatever you specified in the default declaration).

Yes; I had a similar question, and it turns out Num is special, or rather, pattern matching on integer literals is special. See the thread http://www.nabble.com/Pattern-matching-on-numbers--td20571034.html The summary is that pattern matching on a literal integer is different than a regular pattern match; in particular:
foo 1 = print "one" foo _ = print "not one"
turns into
foo x = if x == fromInteger 1 then "one" else "not one"
whereas
bar Test = print "Test" bar _ = print "Not Test"
turns into
bar x = case x of { Test -> print "Test" ; _ -> print "Not Test" }
In the former case, the use of (y == fromInteger 1) means that "foo"
works on any argument within the class Num (which requires Eq),
whereas in the latter case, the use of the constructor Test directly
turns into a requirement for a particular type for "bar".
There's no way to get special pattern matching behavior for other
types; this overloading is specific to integer literals.
-- ryan
On Wed, Dec 3, 2008 at 3:05 PM, Anatoly Yakovenko
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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thanks for your help.
On Wed, Dec 3, 2008 at 3:47 PM, Ryan Ingram
Yes; I had a similar question, and it turns out Num is special, or rather, pattern matching on integer literals is special. See the thread
http://www.nabble.com/Pattern-matching-on-numbers--td20571034.html
The summary is that pattern matching on a literal integer is different than a regular pattern match; in particular:
foo 1 = print "one" foo _ = print "not one"
turns into
foo x = if x == fromInteger 1 then "one" else "not one"
whereas
bar Test = print "Test" bar _ = print "Not Test"
turns into
bar x = case x of { Test -> print "Test" ; _ -> print "Not Test" }
In the former case, the use of (y == fromInteger 1) means that "foo" works on any argument within the class Num (which requires Eq), whereas in the latter case, the use of the constructor Test directly turns into a requirement for a particular type for "bar".
There's no way to get special pattern matching behavior for other types; this overloading is specific to integer literals.
-- ryan
On Wed, Dec 3, 2008 at 3:05 PM, 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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Anatoly Yakovenko
-
Daniel Fischer
-
Ryan Ingram