[GHC] #12240: Common Sense for Type Classes
GHC
ghc-devs at haskell.org
Sat Jul 9 00:47:27 UTC 2016
#12240: Common Sense for Type Classes
-------------------------------------+-------------------------------------
Reporter: Mathnerd314 | Owner:
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by ezyang):
Mathnerd314: For what it's worth, I think this is a very interesting
proposal, and merits further investigation.
Let me consider a slightly modified version of your original example:
{{{
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
module T4921 where
class C a b where
f :: a -> b
instance C Int Char where
f = undefined
g x = f (x :: Int)
}}}
What should the inferred type of `g` be? There seem to be two options:
1. `g :: C Int b => Int -> b`, which is the current behavior of GHC today.
The reasoning goes like this, "While it is true that there is only one
instance of C where a ~ Int today, in some later module someone could very
well define `C Int Int`, in which case, egg on my face if I picked the
original instance! Better leave it to the user of `g` to tell me which one
they actually want."
2. `g :: Int -> Char`, which I believe is what you are proposing. The
reasoning here is, "Well, based on the instances I can see, it's BLOODY
WELL obvious that the only possible instance `f` could use is `C a b`. The
resolution is unambiguous."
In most cases, option (1) makes more programs typecheck, EXCEPT when there
could be ambiguity, in which case the more specific type is desirable;
e.g. if I say `show (g 2)` (what am I showing? With the instances I can
see, the only thing possible is `Char`.)
Actually, there is mechanism for dealing with this situation: defaulting.
In Haskell98, the `default` declaration is a way of saying, "When I get an
ambiguous type, please pluck out this type to solve the ambiguity and then
go your merry way."
What your proposal seems to suggest is an alternate way to do defaulting,
by consulting the instance environment in question. Specifically, if I
have an ambiguous type variable `v` which occurs in some class `C t1 v
...`, if there is only ONE choice of `v` which allows the instance
resolution to go through, I should default `v` to that one! This would
(also) solve the original problem in your ticket.
But maybe you have an example where you wanted more specific instance
resolution, even in the absence of ambiguity. I'd be quite interested to
see it.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12240#comment:13>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list