"S.D.Mechveliani" wrote:

>
> The philosophy should be:
> --------------
> seeing in the program     f ["foo","bar","baz"]
> the compiler judges that  f  applies to certain  xs :: [String].
> According to the compiled type of  f,
> the instances                          Eq String,  Eq (Maybe String)
> are required. The instance  Eq String  is standard and unique.
> Then, the compiler chooses the most special definition for the  Eq
> instance for  Maybe  among those which are in the scope and which
> match the type  Maybe String.
> So, if the second  Eq  instance for  Maybe  occurs in the scope,
> then, clearly, it is applied.
> And how the scope forms?
> In Haskell-98, any mentioning of a module name <M> under `import'
> brings to the scope all the instances defined in <M>.
> Is this how the existing implementations treat the overlaps?

Essentially, yes (assuming the `second instance' is `Eq (Maybe String)').

>
>
> Technique:
> ----------
> the compiler has to solve, what dictionary value to substitute for
> Eq (Maybe a)  declared by the compiled  f.
> According to `philosophy', the choice may be between the above
> dictionaries values from
>                                eqMaybe       :: Eq a -> Eq (Maybe a)
> or                             eqMaybeString :: Eq (Maybe String).
> The second is chosen as the most special.
> What does this mean "chosen" ?
> The  *compiled  f  has two extra arguments* :
> for the Eq class dictionary values for `a' (corresponds to the `eq'
> local variable) and for `Maybe a'  (`eqMb').
> Now,
>               f ["foo","bar","baz"]
> compiles to   f_compiled eqChar eqMaybeString ["foo","bar","baz"].
>
> Hence, ignoring so far various optimization possibilities, we see
> that  f  is compiled *once*. But each its application requires the
> appropriate dictionary value for the additional argument.
> The overlapping instances cause a non-trivial choice for this
> additional argument - which is resolved quite naturally.
> Is this how  GHC, Hugs  process the overlaps?

GHC and hugs resolve overlaps essentially as you indicated in your
`philosophy' above: you line up all the in-scope instances, and select the
most specific one that matches.  With in-scope instance set:
    Eq String
    Eq (Maybe String)
    Eq a => Eq (Maybe a)
If we're requested to find an instance for `Eq (Maybe String)', the choice is
easy - the second instance wins.

But what if we're requested to find an instance for `Eq (Maybe a)'?  Well,
obviously, we can't chose the second instance because it's *too* specific.
But the third instance looks like a fine choice.  Unfortunately, if we chose
the third instance, then we preclude the possibility of, at a later point,
chosing the more specific second instance.  Recognizing this, the request is
denied, because no choice of instance is appropriate.

The gotcha with this arrangement is the bit about `in-scope instances'.  Since
the set of in-scope instances depends on how one happens to set up the import
list, the meaning of the program can depend on the import list.  In general,
this is a bad thing.  How to resolve this?  I see two approaches: either force
the *compiler* to figure out a way to not depend on the scoping of instances
when resolving overlapping instances, or force the *user* to gets his/her
imports right, so that overlapping is always resolved consistently.  I haven't
explored the first option, but it doesn't look promising.  The second option,
however, I think I know how to do, as I sketched in an earlier post, but it
requires a bit more bookkeeping on the compiler's part.  But I haven't looked
at this idea in detail.

>
>
> > It's not enough for the compiler to just remember after compiling
> > f that it needs an explicit dictionary of Eq (Maybe a) passed, and
> > generate different calls to f than to other functions of the same type,
> > because a function like
> >    g :: Eq a => ([a] -> [a]) -> [[a]] -> Int
> > does not know what kind of f will receive (the one that depends
> > on Eq (Maybe a), or possibly Eq (a,Bool) etc.) - it is determined
> > at runtime.
>
> Here, I am about stuck.

The higher-order case isn't any more interesting than the first-order case.
The designers of the type class system were clever enough to avoid this snafu
;-)  Instance resolution is part of static type inference,  it is not
determined at runtime.

In particular, it is not the responsibility of `g' to pass dictionaries to any
parameter `f' - this would be handled at the point where `g' is applied to
`f'.  Parameters, whether higher-order or not, are always monomorphic, and
non-overloaded.  Only `let'/`where' bound idents, or top-level bound idents
can be overloaded.  If we want to think in terms of the dictionary
translation, in the translation of `g f', `f' would be partially applied to
its dictionaries, and then passed to `g'.

    g f    -->   \d -> g (f d)

(assuming that `g' itself wasn't overloaded, and that `f' was only overloaded
on one thing).

As for your later question about module `E' - it would be helpful if you'd
provide the exact module that you used.

--Jeff

Reply via email to