[Haskell] Re: type class instance selection & search

Conal Elliott conal at conal.net
Wed Aug 1 16:23:00 EDT 2007


On 8/1/07, apfelmus <apfelmus at quantentunnel.de> wrote:

> There are some fundamental problems/design choices for type classes
> in conjunction with separate compilation/modularity that need to be
> researched before trying anything like that. In particular, any
> ad-hoc Prolog, CHR or -fallow-undecidable-instances just ignores
> these problems and doesn't solve them.

> The problem with the Functor/Cofunctor instances is that they are
> ambiguous as soon as a type constructor X is made an instance of
> both Functor and Cofunctor . Of course, such an X cannot exist in a
> mathematically useful way (really ?) but the current system doesn't
> allow to tell this to the compiler. Alas, we can always say

>   instance Functor F where
>     fmap   = undefined
>   instance Cofunctor F where
>     cofmap = undefined

> The problem is not so much that there might be ambiguities, but how
> to detect and when to report them.

I agree: and my intent is that the compiler would detect and report the
ambiguity as an error.

>    Consider:

>   module F where
>     class Functor f
>     class Cofunctor f

>   module O where
>     import F

>     data O f g a
>     instance (Functor g,   Functor f  ) => Functor (O g f)
>     instance (Cofunctor g, Cofunctor f) => Functor (O g f)

>   module X where
>     import F

>     data X a
>     instance Functor   X
>     instance Cofunctor X

>   module Unsound where
>     import F
>     import O
>     import X

>     type Unsound a = O X X a

> The current design rejects module O.
> - Another possible design choice is to reject only module Unsound, i.e.
> when the conflicting instance declarations both come into scope. But it
> may be tricky/undecidable to to detect such conflicting instances.
> - A third possibility is to reject module X based on hypothetical
> information from module F that states that the instances of Functor and
> Cofunctor are disjoint.
> - The fourth choice is to not reject any module but to wait until a
> function really uses the type  Unsound a  and to reject this function.
> This is probably a bad idea since this may delay the error even further
> to modules that import Unsound.

I'd be much happier with any of the latter three options than with the
current design.

  - Conal
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell/attachments/20070801/db9833ce/attachment.htm


More information about the Haskell mailing list