tags:

views:

278

answers:

5

I have a typeclass "MyClass", and there is a function in it which produces a string. I want to use this to imply an instance of Show, so that I can pass types implementing MyClass to "show". So far I have,

class MyClass a where
    someFunc :: a -> a
    myShow :: a -> String

instance MyClass a => Show a where
    show a = myShow a

which gives the error "Constraint is no smaller than the instance head." I also tried,

class MyClass a where
    someFunc :: a -> a
    myShow :: a -> String

instance Show (MyClass a) where
    show a = myShow a

which gives the error, "Class `MyClass' used as a type."

How can I correctly express this relationship in Haskell? Thanks.

I should add that I wish to follow this up with specific instances of MyClass that emit specific strings based on their type. For example,

data Foo = Foo
data Bar = Bar

instance MyClass Foo where
    myShow a = "foo"

instance MyClass Bar where
    myShow a = "bar"

main = do
    print Foo
    print Bar
+1  A: 

You can compile it, but not with Haskell 98, You have to enable some language extensions :

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
-- at the top of your file

Flexible instances is there to allow context in instance declaration. I don't really know the meaning of UndecidableInstances, but I would avoid as much as I can.

Raoul Supercopter
I was assuming that the fact that GHC thinks it's undecidable is a probably a problem. If anyone could explain why it's undecidable that would be great!
Steve
If you enable UndecidableInstances, FlexibleInstances is superfluous.
John
+12  A: 

(Edit: leaving the body for posterity, but jump to the end for the real solution)

In the declaration instance MyClass a => Show a, let's examine the error "Constraint is no smaller than the instance head." The constraint is the type class constraint to the left of '=>', in this case MyClass a. The "instance head" is everything after the class you're writing an instance for, in this case a (to the right of Show). One of the type inference rules in GHC requires that the constraint have fewer constructors and variables than the head. This is part of what are called the 'Paterson Conditions'. These exist as a guarantee that type checking terminates.

In this case, the constraint is exactly the same as the head, i.e. a, so it fails this test. You can remove the Paterson condition checks by enabling UndecidableInstances, most likely with the {-# LANGUAGE UndecidableInstances #-} pragma.

In this case, you're essentially using your class MyClass as a typeclass synonym for the Show class. Creating class synonyms like this is one of the canonical uses for the UndecidableInstances extension, so you can safely use it here.

'Undecidable' means that GHC can't prove typechecking will terminate. Although it sounds dangerous, the worst that can happen from enabling UndecidableInstances is that the compiler will loop, eventually terminating after exhausting the stack. If it compiles, then obviously typechecking terminated, so there are no problems. The dangerous extension is IncoherentInstances, which is as bad as it sounds.

Edit: another problem made possible by this approach arises from this situation:

instance MyClass a => Show a where

data MyFoo = MyFoo ... deriving (Show)

instance MyClass MyFoo where

Now there are two instances of Show for MyFoo, the one from the deriving clause and the one for MyClass instances. The compiler can't decide which to use, so it will bail out with an error message. If you're trying to make MyClass instances of types you don't control that already have Show instances, you'll have to use newtypes to hide the already-existing Show instances.

So that's the error message and how UndecidableInstances makes it go away. Unfortunately it's a lot of trouble to use in actual code, for reasons Edward Kmett explains. The original impetus was to avoid specifying a Show constraint when there's already a MyClass constraint. Given that, what I would do is just use myShow from MyClass instead of show. You won't need the Show constraint at all.

John
Thanks, it indeed works if I enable UndecidableInstances. Weird. Is this an abuse of the typeclass system? I was mostly trying to avoid having to specify the constraint "Show" for all functions that take "MyClass" and also need to show. Since all MyClass instances should have a string associated with them, I figured automatically deriving Show would be one way. However it seems better to just avoid the problem by explicitly specifying Show where necessary, instead of enabling esoteric language extensions. What do you think?
Steve
I would use myShow instead of show in all functions so you don't need the Show constraint at all. In the instance definitions you can then write `myShow = show` if it's appropriate. I would avoid writing `instance MyClass a => Show a` because of the problem described in the edit. Dave Hinton's solution is better than UndecidableInstances, but I don't think you shouldn't add a superclass constraint just for convenience.
John
Keep in mind that this hack with these extensions only works reasonably safely within a single module. You can't even use exports from this module even if you don't export MyClass, in any other module that will ever have a module that transitively depends upon it that ever wants to show anything that isn't an instance of MyClass.
Edward Kmett
+1  A: 

I think it would be better to do it the other way around:

class Show a => MyClass a where
    someFunc :: a -> a

myShow :: MyClass a => a -> String
myShow = show
Dave Hinton
...except, that won't let the OP declare a custom `show` version. Also, it won't allow a declaration of `MyClass` for a type that is not (yet) a Show instance.
BMeph
The thing to realize here is that when you say show = myShow, you've already lost the battle of having a custom show since a type can't have two different show functions, and a type that implements MyClass must be a instance of Show (calling it myShow instaid of show makes no difference.) That is if I want T to be an instance of MyClass, I have to implement myShow, in the end that turns out to become it's show function as an instance of Show. Compare that to first implementing Show, and then implementing MyClass, and you see that the only difference is the name of the function.
HaskellElephant
I like this solution because the way the OP presents his problem, `myShow` is equivalent to `show` for all `MyClass` instances because `MyClass` would imply `Show` (by OP's desire). You wouldn't need the `myShow` function in this case though. Just use `show`.
trinithis
+13  A: 

I wish to vigorously disagree with the broken solutions posed thus far.

instance MyClass a => Show a where
    show a = myShow a

Due to the way that instance resolution works, this is a very dangerous instance to have running around!

Instance resolution proceeds by effectively pattern matching on the right hand side of each instance's =>, completely without regard to what is on the left of the =>.

When none of those instances overlap, this is a beautiful thing. However, what you are saying here is "Here is a rule you should use for EVERY Show instance. When asked for a show instance for any type, you'll need an instance of MyClass, so go get that, and here is the implementation." -- once the compiler has committed to the choice of using your instance, (just by virtue of the fact that 'a' unifies with everything) it has no chance to fall back and use any other instances!

If you turn on {-# LANGUAGE OverlappingInstances, IncoherentInstances #-}, etc. to make it compile, you will get not-so-subtle failures when you go to write modules that import the module that provides this definition and need to use any other Show instance. Ultimately you'll be able to get this code to compile with enough extensions, but it sadly will not do what you think it should do!

If you think about it given:

instance MyClass a => Show a where
    show = myShow

instance HisClass a => Show a where
    show = hisShow

which should the compiler pick?

Your module may only define one of these, but end user code will import a bunch of modules, not just yours. Also, if another module defines

instance Show HisDataTypeThatHasNeverHeardOfMyClass

the compiler would be well within its rights to ignore his instance and try to use yours.

The right answer, sadly, is to do two things.

For each individual instance of MyClass you can define a corresponding instance of Show with the very mechanical definition

instance MyClass Foo where ...

instance Show Foo where
    show = myShow

This is fairly unfortunate, but works well when there are only a few instances of MyClass under consideration.

When you have a large number of instances, the way to avoid code-duplication (for when the class is considerably more complicated than show) is to define.

newtype WrappedMyClass a = WrapMyClass { unwrapMyClass :: a }

instance MyClass a => Show (WrappedMyClass a) where
    show (WrapMyClass a) = myShow a

This provides the newtype as a vehicle for instance dispatch. and then

instance Foo a => Show (WrappedFoo a) where ...
instance Bar a => Show (WrappedBar a) where ...

is unambiguous, because the type 'patterns' for WrappedFoo a and WrappedBar a are disjoint.

There are a number of examples of this idiom running around in the the base package.

In Control.Applicative there are definitions for WrappedMonad and WrappedArrow for this very reason.

Ideally you'd be able to say:

instance Monad t => Applicative t where
    pure = return
    (<*>) = ap 

but effectively what this instance is saying is that every Applicative should be derived by first finding an instance for Monad, and then dispatching to it. So while it would have the intention of saying that every Monad is Applicative (by the way the implication-like => reads) what it actually says is that every Applicative is a Monad, because having an instance head 't' matches any type. In many ways, the syntax for 'instance' and 'class' definitions is backwards.

Edward Kmett
Hah, I got so caught up in explaining the error message and what UndecidableInstances does that I completely forgot to put in my real solution (except in a very small comment)! I've edited my response to include it.
John
Thank you! As I'm sure you can tell from my question, I'm still learning exactly what typeclasses "are", and this helps tremendously.As much as I dislike "design patterns", it would be great to see a book detailing cookbook solutions to common situations in Haskell programs, including the above "idiom" as you call it.
Steve
By the way, is it safe to say, "a typeclass cannot (safely) automatically derive (infer) another typeclass, it can only require (be constrained by) one?"
Steve
Well, it is occasionally (if rarely) useful to infer another typeclass wholesale, but only i that is the only purpose of the other typeclass. i.e. you can make class (Foo a, Bar a) => FooBar a; and instance (Foo a, Bar a) => FooBar aand that turns out to be perfectly unambiguous, you've given an alias to the combination of Foo and Bar. (You need a few extensions to make that work)But yes, in general typeclasses shouldn't be used to infer other classes in their entirety because of the issues above.
Edward Kmett
A: 

You may find some interesting answers in a related SO question: http://stackoverflow.com/questions/2877304/linking-combining-type-classes-in-haskell/

Wei Hu