
kind.hs:7:0:
Illegal instance declaration for `Yesno t'
(All instance types must be of the form (T a1 ... an)
where a1 ... an are type *variables*,
and each type variable appears at most once in the instance head.
Use -XFlexibleInstances if you want to disable this.)
In the instance declaration for `Yesno t'
Failed, modules loaded: none.
So, I added the suggested Pragma
{-# LANGUAGE FlexibleInstances #-}
module Kind where
....
Prelude> :l kind.hs
[1 of 1] Compiling Kind ( kind.hs, interpreted )
kind.hs:7:0:
Constraint is no smaller than the instance head
in the constraint: Num t
(Use -XUndecidableInstances to permit this)
In the instance declaration for `Yesno t'
Failed, modules loaded: none.
Adjusted pragma to
{-# LANGUAGE FlexibleInstances,
UndecidableInstances #-}
Prelude> :l kind.hs
[1 of 1] Compiling Kind ( kind.hs, interpreted )
Ok, modules loaded: Kind.
*Kind> yesno 10
True
*Kind> yesno 0
False
I am not sure if I understand the implications here. Did I introduce a bug?
-Amitava
On Tue, Mar 15, 2011 at 3:28 PM, aditya siram
Untested, but you might try:
instance (Num t) => YesNo t where ....
-deech
While reading "Learn You a Haskell for Great Good!" I came across the YesNo type class
I tried a minimal version as below
module Kind where
class Yesno a where yesno :: a -> Bool
instance Yesno Int where yesno 0 = False yesno _ = True
I was surprised to get an error
*Kind> :load kind.hs [1 of 1] Compiling Kind ( kind.hs, interpreted ) Ok, modules loaded: Kind. *Kind> yesno 10
<interactive>:1:6: Ambiguous type variable `t' in the constraints: `Num t' arising from the literal `10' at <interactive>:1:6-7 `Yesno t' arising from a use of `yesno' at <interactive>:1:0-7 Probable fix: add a type signature that fixes these type variable(s)
Turns out 10 in this instance is an Integer and I have not defined Yesno over Integer
Easy fix - just define an instance over Integer
instance Yesno Integer where yesno 0 = False yesno _ = True
My question - Is there a way to avoid this kind of boilerplate? What is
On Tue, Mar 15, 2011 at 2:21 PM, Amitava Shee
wrote: the idiomatic way?
Thanks & Regards, Amitava Shee
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Amitava Shee Software Architect There are two ways of constructing a software design. One is to make it so simple that there are obviously no deficiencies; the other is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult. -- C. A. R. Hoare The Emperor's Old Clothes, CACM February 1981