[Haskell] How to close a type class

oleg at pobox.com oleg at pobox.com
Fri Nov 12 01:22:48 EST 2004


It is well known that type classes in Haskell are open. A user may at
any time extend a visible type class by providing a new
instance. There are situations where such an extensibility is
undesirable. We may want to prevent the user from adding an instance
to our class for some specific type -- or for all types (except some
finite set of types). This messages shows that this problem is
solvable in Haskell with common extensions. The code in this message
has been tested with GHC 6.2.1, GHC 6.3.20041106 snapshot, and Hugs
-98 (Nov 2003).

We first discuss the problem of excluding specific ground types from a
type class. That problem easily reduces to the one of defining a class
that has no instances and cannot have ones. We then describe excluding
non-ground types in the presence of overlapping (and perhaps,
incoherent) instance extensions. The latter solution shows how to
close a class -- that is, preclude adding any further instances to
it. Completely closing the class has a price to pay: the principal
type of an expression that involves closed class methods exists and
_can_ be inferred -- but cannot be explicitly written.

The essence of the technique can be expressed by a well-known phrase
	How to replace failure by a [long...] list of successes

On Thu Nov 11 10:57:42 EST 2004 Ben Rudiak-Gould wrote on Haskell
Cafe:
> Except how would you prevent the user from declaring an instance for
> PrivateState RealWorld? Oh well. 

Let us indeed consider preventing the user from declaring an instance
of our class for a specific ground type. The answer is simple: we
declare that instance ourselves. But we make that instance
_statically_ unusable. Here's a simple example:

> {-# OPTIONS -fglasgow-exts #-}
> {-# OPTIONS -fallow-undecidable-instances #-}
>
> module C1 where
>
> class C a where op:: a -> String
> instance C Int where op x  = show x
> instance C Char where op x = "char"

Suppose we wish to define two instances of that class, C Int and C
Char, and prevent the user from declaring an instance of C for a
string. So, we define that instance ourselves:

> instance Fail String => C String where op = error "thou shall not be"
>
> class Fail a
>
> test1 = op (1::Int)
> test2 = op 'z'
> --test3 = op "str"

Here class Fail has no instances (we shall discuss how to guarantee
that in a moment). If we uncomment out the test3 line, we get a type
error.

Thus we have reduced the problem of excluding certain types from a
typeclass to the problem of excluding all types from one particular
typeclass: Fail. How can we prevent the user from adding instances to
Fail? Again, we define the most general instance the class Fail may
have:

> instance Fail [a] => Fail a

If the test3 line stays commented out, the code typechecks and test1
and test2 work as expected. However, if we now uncomment the test3
line, we get the truly impressive type error message (I like the way
it looks in Hugs).

If overlapping instances extension is off, any attempt to add another
instance to class Fail will be rejected by the compiler, because it
will be overlapping with our general instance.


Let us now turn to a more complex problem of the exclusion of
non-ground types in the presence of overlapping instances. For
example, suppose we wish to prevent any instances of class C for
lists of any type. If overlapping instances are allowed, writing
	instance Fail [a] => C [a] 
will not do us much good, because the user may still introduce 
"instance C [Int]" for specific ground types like Int.

Although overlapping (let alone incoherent) instance extensions seem
to be quite permissive, there is still a law they must obey: the law
of functional dependencies. That law lets us effectively close a
class. Indeed, functional dependencies are already a tool to
semi-close a class, to disallow a broad subset of instances (the ones
that fail the dependency).

Our solution requires adding a dummy type parameter to the type
class. Note that the signatures of class methods are not affected.

> {-# OPTIONS -fglasgow-exts #-}
> {-# OPTIONS -fallow-undecidable-instances #-}
> {-# OPTIONS -fallow-overlapping-instances #-}
> {-# OPTIONS -fallow-incoherent-instances #-}

We activate all extensions

> module C2 (C(..)) where
>
> data Private a -- NOT exported
>
> class C a b | a->b where op:: a -> String
> instance C Int (Private Int) where op x  = show x
> instance C Char (Private Char) where op x = "char"
> test1 = op (1::Int)
> test2 = op 'z'

Here we add a dummy class parameter 'b'. Note that the method
signature remains the same -- and so all the uses of the method.

To preclude the instantiation of the class for any list, we make the
instance ourselves:

> instance C [[a]] (Private [[a]])
>     => C [a] (Private [a]) where op = error "thou shall not be"

The user may try to add a new instance, say
	instance C [Int] ???
but what can he put instead of ??? Functional dependencies leave
*only* one choice: (Private [Int]) -- but the type constructor Private
is not exported from C2 and not available. So, effectively the user is
prevented from adding any instance of class C for a list of any type
-- and the one instance there is, is statically unusable. We can see
that if we try to evaluate `op "str"'. We get even more spectacular
type error.

We can extend that idea to completely close the class C to any new
instances -- whatever they may be. We merely need to add to our module
C2:

> instance C [a] (Private [a])
>     => C a (Private a) where op = error "thou shall not be"

The class is closed. But there is a price to pay. We can write

> module C3 where
> import C2
>
> test4 x = op x ++ "abc"

We can evaluate "test4 'c'", we can get the compiler to infer the
principal type for test4 and to show it to us

 *C3> :t test4
 test4 :: forall a. (C a (C2.Private a)) => a -> [Char]

but we cannot write that type signature ourselves, because the type
constructor C2.Private is not exported. If we wish to give test4
signature, we must use particular instantiations of class C, e.g., 
"test4:: Int -> String"



More information about the Haskell mailing list