[Haskell-beginners] Idiomatic way to avoid type class instance definitions for Int and Integer separately
Daniel Fischer
daniel.is.fischer at googlemail.com
Tue Mar 15 21:11:06 CET 2011
On Tuesday 15 March 2011 20:43:59, Amitava Shee wrote:
> 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.
Yes, the language report specifies a fairly restricted form of legal
instance declarations, so to have an
instance Foo a where ...
or an
instance Bar (Either Int a) where ...
you need to turn on FlexibleInstances
>
> 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.
>
Yes, if the constraint is not smaller than the instance head, the compiler
doesn't know a priori that instance checking will terminate, so it asks you
to tell it to go ahead by enabling UndecidableInstances (which is perhaps a
too scary name). Despite its scary name, that is a relatively harmless
extension, it just allows the compiler to try and check instances where it
doesn't know in advance that checking will terminate. Even if the checking
doesn't terminate, it won't send the compiler into an infinite loop because
it has a context stack and doesn't try to use more steps than that allows
(you can set the size of the stack if the default size is too small for
your use-case). If checking terminates, it's fine.
> 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.
All harmless. You just allowed more general forms of instance declarations
than specified in the report (see above) and told the compiler to try even
though it doesn't have an a priori guarantee that it will finish.
> Did I introduce a bug?
No. Unless possibly if you want further instances, see my previous mail.
>
> -Amitava
More information about the Beginners
mailing list