You need something like this:

{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}

class YesNo a where  
    yesno :: a -> Bool
   
instance (Num a, Eq a) => YesNo a where
    yesno = (/= 0)

The reason this doesn't work without turning on some "scary" flags is that you can easily write code that is ambiguous since typeclasses are open. Open means that some other file can define a data type that has an instance of Num and an instance for YesNo and then there's no obvious choice which instance should be used.

If you want a bit more detail, here's a relevant StackOverflow question: https://stackoverflow.com/questions/8877541/how-to-write-an-instance-for-all-types-in-another-type-class


On Sat, Apr 3, 2021 at 9:26 PM Galaxy Being <borgauf@gmail.com> wrote:
I'm following LYHFGG and I have this

class YesNo a where  
    yesno :: a -> Bool

instance YesNo Int where  
    yesno 0 = False  
    yesno _ = True


but then I have to specify Int here

> yesno (5 :: Int)
True

Just with 5 gives this error

Ambiguous type variable ‘a0’ arising from the literal ‘5’
      prevents the constraint ‘(Num a0)’ from being solved.
      Probable fix: use a type annotation to specify what ‘a0’ should be.

I tried this

instance YesNo (Num a) where  
    yesno 0 = False  
    yesno _ = True

but got cryptic errors. What can I do to make yesno take any of Num's numbers?

LB

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners