Domanda

Is it possible to create a typeclass that can no longer admit new members (perhaps by using module boundaries)? I can refuse to export a function necessary for a complete instance definition, but that only results in a runtime error if someone produces an invalid instance. Can I make it a compile time error?

È stato utile?

Soluzione 2

I believe the answer is a qualified yes, depending on what you're trying to achieve.

You can refrain from exporting the type class name itself from your interface module1, while still exporting the names of the type class functions. Then no one can make an instance of the class because no one can name it!

Example:

module Foo (
    foo,
    bar
) where

class SecretClass a where
    foo :: a
    bar :: a -> a -> a

instance SecretClass Int where
    foo = 3
    bar = (+)

The downside is no one can write a type with your class as a constraint either. This doesn't entirely prevent people from writing functions that would have such a type, because the compiler will still be able to infer the type. But it would be very annoying.

You can mitigate the downside by providing another empty type class, with your "closed" class as a super-class. You make every instance of your original class also an instance of the sub class, and you export the sub class (along with all of the type class functions), but not the super class. (For clarity you should probably use the "public" class rather than the "secret" one in all of the types you expose, but I believe it works either way).

Example:

{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}

module Foo ( 
    PublicClass,
    foo,  
    bar   
) where 

class SecretClass a where 
    foo :: a
    bar :: a -> a -> a

class SecretClass a => PublicClass a

instance SecretClass Int where 
    foo = 3
    bar = (+) 

instance SecretClass a => PublicClass a

You can do without the extensions if you're willing to manually declare an instance of PublicClass for each instance of SecretClass.

Now client code can use PublicClass to write type class constraints, but every instance of PublicClass requires an instance of SecretClass for the same type, and with no way to declare a new instance of SecretClass no one can make any more types instances of PublicClass2.

What all of this doesn't get you is the ability for the compiler to treat the class as "closed". It will still complain about ambiguous type variables that could be resolved by picking the only visible instance of "closed".


1 Pure opinion: it's usually a good idea to have a separate internal module with a scary name which exports everything so that you can get at it for testing/debugging, with an interface module that imports the internal module and only exports the things you want to export.

2 I guess with extensions someone could declare a new overlapping instance. E.g. if you've provided an instance for [a], someone could declare an new instance of PublicClass for [Int], which would piggyback on the instance of SecretClass for [a]. But given that PublicClass has no functions and they can't write an instance of SecretClass I can't see that much could be done with that.

Altri suggerimenti

Since GHC 7.8.1, closed type families can be declared, and I think with the help of them, and ConstraintKinds, you can do this:

type family SecretClass (a :: *) :: Constraint where
  SecretClass Int = ()

SecretClass a forms a constraint, equivalent to a type class, and since the family can't be extended by anyone, no other instances of the "class" can be defined.

(This is actually just speculation, since I can't test it, but the code in this interesting link makes it look like it would work.)

You can encode closed type classes via closed type families, which can be essentially encoded as associated type families in turn. The key to this solution is that instances of an associated type family have be inside a type class instance, and there can only be one type class instance for each monomorphic type.

Note that this approach is independent of the module system. Instead of relying on module boundaries, we provide an explicit list of which instances are legal. This means, on the one hand, that the legal instances can be spread over multiple modules or even packages, and on the other hand, that we cannot provide illegal instances even in the same module.

For this answer, I assume that we want to close the following class so that it can only be instantiated for the type Int and Integer, but not for other types:

 -- not yet closed
class Example a where
  method :: a -> a

First, we need a little framework for encoding closed type families as associated type families.

{-# LANGUAGE TypeFamilies, EmptyDataDecls #-}

class Closed c where
  type Instance c a

The parameter c stands for the name of the type family and the parameter a is the index of the type family. The family instance of c for a is encoded as Instance c a. Since c is a class parameter as well, all family instances of c have to be given together, in a single class instance declaration.

Now, we use this framework to define a closed type family MemberOfExample to encode that Int and Integer are Ok, and all other types are not.

data MemberOfExample
data Ok

instance Closed MemberOfExample where
  type Instance MemberOfExample Int = Ok
  type Instance MemberOfExample Integer = Ok

Finally, we use this closed type family in a superclass contraint of our Example.

class Instance MemberOfExample a ~ Ok => Example a where
  method :: a -> a

We can define the valid instances for Int and Integer as usual.

instance Example Int where
  method x = x + 1

instance Example Integer where
  method x = x + 1

But we cannot define invalid instances for other types than Int and Integer.

-- GHC error: Couldn't match type `Instance MemberOfExample Float' with `Ok'
instance Example Float where
  method x = x + 1

And we cannot extend the set of valid types, either.

-- GHC error: Duplicate instance declarations
instance Closed MemberOfExample where
  type Instance MemberOfExample Float = Ok

-- GHC error: Associated type `Instance' must be inside a class instance
type instance Instance MemberOfExample Float = Ok

Unfortunately, we can write the following bogus instance:

-- Unfortunately accepted
instance Instance MemberOfExample Float ~ Ok => Example Float where
  method x = x + 1

But since we will never be able to discharge the equality constraint, I don't think we can ever use it for anything. For example, the following is rejected:

-- Couldn't match type `Instance MemberOfExample Float' with `Ok'
test = method (pi :: Float)

You could refactor the typeclass into a data declaration (use record syntax) which contains all the functions your typeclass had. A fixed finite list of instances sounds like you don't need a class anyway.

This is of course essentially what the compiler is doing behibd the scenes with your class anyway.

This would allow you to export the list of instances as functions to your data type, and you can export them but not the constructors for the data type. Similarly, you can restrict exporting of the accessor functions, and just export the interface you actually want.

This works fine because data types aren't subject to the module-boundary-crossing open world assumption the typeclasses are.

Sometimes adding typesystem complexity just makes things harder.

When all you are interested in is that you have an enumerated set of instances, then this trick might help:

class (Elem t '[Int, Integer, Bool] ~ True) => Closed t where

type family Elem (t :: k) (ts :: [k]) :: Bool where
  Elem a '[] = False
  Elem a (a ': as) = True
  Elem a (b ': bs) = Elem a bs

instance Closed Int
instance Closed Integer
instance Closed Bool
-- instance Closed Float -- ERROR

Here's another variation on phipshabler's answer. This one doesn't need ConstraintKinds, and should avoid needing UndecidableSuperClasses.

type family Good a where
  Good Int = 'True
  Good Bool = 'True
  Good _ = 'False

class Good a ~ 'True => Closed a where ...
Autorizzato sotto: CC-BY-SA insieme a attribuzione
Non affiliato a StackOverflow
scroll top