instance overlap
Serge D. Mechveliani
mechvel at botik.ru
Sun Jan 20 09:55:39 EST 2008
I thank Bertram Felgenhauer <bertram.felgenhauer at googlemail.com>
for his helpful notes on my request on overlapping instances.
First, here is the abstract of this my letter.
-------------------------------------------------------------------
I address to the GHC developers with the following questions and
suggestions.
1. Can you check what ghc-5.02.3 will report on the below small program
with DShow
(under -fglasgow-exts -fallow-overlapping-instances
-fallow-undecidable-instances
) ?
>> class DShow a where dShows :: a -> String -> String
>> instance DShow Char where dShows = showChar
>> instance DShow Int where dShows = shows
>>
>> instance DShow a => DShow [a] -- (1)
>> where
>> dShows _ = showString "contrived show value"
>>
>> instance DShow String where dShows = shows -- (2)
>>
>> f :: DShow a => [a] -> String
>> f xs = dShows xs ""
>> -- dShows (head xs) "" -- compare to this
>>
>> main = putStr (shows (f "abc", f [1, 2, 3 :: Int]) "\n")
2. When GHC fails to select an instance among overlapping ones, it is
often useful to report advice to the user: "consider adding such and
such instance class assertion to a type context".
For example, the user declares above f :: DShow a => [a] -> String,
and the compiler advices to consider the declaration
f :: (DShow a, DShow [a]) => [a] -> String.
With this, the compiler postpones the instance selection in a client
function (`main') for f.
2.1. Maybe, it is better for the compiler to automatically add such
decls to the context, issue a warning and to continue compilation ?
Because, evidently, the programmer presumes this declaration
meaning. (?)
3. In my example with DShow, instance overlaps are really redundant.
I looked into Prelude.Show, showList, and their usage in List and
[Char]. I added an analogue of showList, and now DShow does not need
overlapping instances.
4. But there are other situations, when it is much simpler for a
programmer to declare overlapping instances than to apply tricks with
additional class methods.
5. What the GHC developers think on my suggestion below with the user
defined preference for overlapping instances?
For any occasion, keep in mind, that sometimes I mistake.
------------------------------------------------------------------------
So, Bertram, (3) is the answer to your response of 19 Jan 2008
> Does the trick from the Show class help you? Simplified, it is
> the following:
> class Show a where show :: a -> String
> showList :: [a] -> String
> [..]
We also wrote
>> 3. Also DoCon uses overlapping instances, and works under ghc-6.8.2,
>> somehow (probably, I need to recall what precisely this usage is).
> You can fix your program by declaring
>
> f :: DShow [a] => [a] -> String
>
> or even
>
> f :: (DShow a, DShow [a]) => [a] -> String
>
> which will postpone the selection of the instance of DShow [a] to
> the point where f is called.
Yes, according to this your note, I suggest the point (2) in the abstract.
This was my intention and expectation: I hope for the compiler to postpone,
as possible, the instance selection. But it occurs that it needs a little
help from the programmer.
Probably, you answered by this why do i-overlaps work in DoCon.
I recall, old GHC compilation reports adviced me to add the contexts
similar to this `DShow [a]'. And I did add them.
But in this example with DShow, ghc-6.8.2 does not advice this.
I wonder what ghc-5.02.3 will report on this example.
I have two large projects in Haskell + GHC.
The current one is Dumatel -- a prover.
It uses i-overlaps, but not essentially, as I see now, i-overlaps can
easily be removed from it.
The old project is DoCon -- computer algebra.
I think, i-overlaps are essential in all application domains, but in
computer mathematics they become visible somehow earlier.
> There's only trouble with overlapping instances when you have several
> instances for the same type with different behaviour. (I don't know
> whether that's true or not for DoCon.)
Yes -- with different behaviour. It is true for DoCon, and this is
generally in-avoidable.
For an applied programmer, this sometimes occurs a natural way to
implement a method instance. And the compiler does have a certain
technical trouble. It must overcome it by posponing the instance
selection as possible. For example, in DoCon, I put
(example changed, it is contrived):
----------------------------------------------------------------------
class EuclideanRing a where divideWithRemainder :: a -> a -> a
...
class EuclideanRing a => Field a where ...
instance EuclideanRing IntegerModulo_2 where
divideWithRemainder a b = ...
instance Field IntegerModulo_2 where ...
instance :: EuclideanRing a => GCD (Polynomial a)
where
gcd f g = <generic method for greatest common divisor for polynomials>
instance GCD (Polynomial IntegerModulo_2)
where
gcd f g = <special and fast method for coefficiens of
(Integer modulo 2) >
instance Field a => GCD (Polynomial a)
where
gcd f g = <special (but generic) and fast method for coefficiens of
Field a => a >
f :: (Field a, GCD (Polynomial a)) => Polynomial a -> Polynomial a
f p = gcd p (p*p - 1)
main = putSTr (show ( f (x^2+x+1) :: Polynomial IntegerModulo_2 ))
----------------------------------------------------------------------
-- sorry, I do not run this particular example, have not time now, but
similar constructs work in DoCon, in practice.
Note, that in `f', the three instances for GCD (Polynomial a) overlap.
If we remove `GCD (Polynomial a)' from the context of f, then the
compiler would not know what instance to set for gcd in RHS of f.
Right?
And with adding `GCD (Polynomial a)' to the context of f, the compiler
postpones instance selection in this example until `main'.
And this is my programmer aim.
Maybe, this i-overlap can be avoided by the trick of introducing
several additional members to the classes EuclideanRing and Field,
similarly as with Show.showList.
But this will not be so easy as for Prelude.Show. The user program
will, probably, complicate considerably. For this example, the trick
will require to declare
class EuclideanRing a
where
divideWithRemainder :: a -> a -> a
gcdForPolynomials :: Polynomial a -> Polynomial a -> Polynomial a
...ForMatrix :: ...
...
Show.showList of the Haskell Prelude is conceptually ugly, because it
interferes with usage of classes. But this trick is `small', it appears
in a couple of places in Standard Prelude only, and with all the rest,
it is hidden, I use `show' and do not recall of showList.
But I do not think that in general, adding parasitic class members is
a good way to avoid overlapping instances.
In computer algebra, this, I think, will be much worse.
This member gcdForPolynomials is ugly. But besides this, one would
need to also add the member of, say,
matrixDeterminant :: Matrix a -> a,
and other members.
And this is instead of separate plain declaration of
determinant :: (... a) => Matrix a -> a
This trick spoils the concept, provoces the user to a wrong style.
And probably, there will be further complication with implementation.
This trick is tricky. And mathematical practice for defining methods
is plain, it is as written above, it follows common reason.
The simpler (for user) -- the better.
The aim is not to provide different algorimths for a same type.
The aim is to provide one algorithm for a certain class of types
(class of mathematical domains), other algorithm for another class of
domains, and so on, for several algorithms.
For example, for determinant for (Matrix a) one can find 4-5
different useful generic algorithms, and each one requires its
particular conditions on `a', and on construction of `a'.
Different algorithms usually are based on different conditions on the
domain -- different type contexts (what is set before `=>'). The user
aim is to define these algorithms in a generic way, and on the other
hand, some of them are defined in a more special way -- for the need
of fast computation.
This is a natural way to implement a computational method.
The description of these domain classes is also natural -- by the
Haskell classes and type contexts. This agrees with science.
But there is a minor deficiency here: the above domain classes may
intersect non-trivially. This cannot be avoided.
A pair of the above domain classes may have non-empty intersection.
Let a domain D be in this intersection. Now, what if
instance-1.gcd f g /= instance-2.gcd f g
for some f and g from D ? Then, the programmer is responsible. In this
case, one may have wrong result at run time.
Also I can even imagine a situation, when such a diversion is intended
-- this is on the programmer.
This must _not_ be an error for compiler. The compiler could _warn_
about possible result diversion, but we do not require of a compiler
such a wisedom.
In my practice, different algorithms for instance-1 and instance-2
often have very different computation cost, but they always have the
same data result in the end. For example, different algorithms for
multiplying matrices correspond to the same symbol "*", and they must
produce the same product matrix -- this is science.
If the results diverse, then, in my current practice, this is a
_programmer_ error.
But when the compiler cannot postpone instance selection, what instance
(among matching a domain sub-class D) needs the compiler to select for
D ?
Let it be, -- so far, -- one of the most special instances.
This agrees with
a) common intuition, b) mathematical practice, c) current GHC solution.
And generally, for future, consider the following simple solution.
(The compliler reports of overlaps, and then,) the programmer orders in
the source program the instances that overlap -- by inserting the
precedence declaration:
instance-a (Precedence 1), instance-b (Precedence 2), ...
-- add possible `(Precedence n)' declaration to instance declaration.
This numeration is local for each overlapping set of instances.
Then, for a class of domains in the intersection of these instances,
the compiler must select among the matching instances the one with the
smallest precedence No.
For example, for the above instances for GCD, I would set the
precedence:
----------------------------------------------------------------------
instance GCD (Polynomial IntegerModulo_2) (Precedence 1) where ...
instance Field a => GCD (Polynomial a) (Precedence 2) where ...
instance :: EuclideanRing a => GCD (Polynomial a) (Precedence 3)
where ...
----------------------------------------------------------------------
-- because the method of (1) is usually faster than (2)
and (2) is usually faster than (3).
In most situations, it is easy for a programmer to set such a precedence
according to programmer's knowledge.
This is a more generic mechanism than to relay on the compiler to detect
specializations among instances, because one instance can be more
preferable but not more special by constructors
(I can provide examples).
Still there may remain situations when it is not clear even for a
programmer, which instance is better for some intersection.
In such a case, there still is not any better solution than to relay on
the programmer-set ordering. If the programmer cannot decide, he skips
some precedence setting in instances, and the compiler would fill the
them in any way (but at least, as subdued to `more-special' relation).
I wonder: what might be wrong with this programmer-set precedence
arrangement?
Now, what concerns to "computer algebra and mathematics":
do not think that instance overlaps present a specific need for
mathematics, generally, mathematics _has not anything_ as specific
with respect to programming tools.
It would be better to provide simple examples from a "real life".
For example,
class Vehicle ... instance Vehicle Bicycle ...
instance Vehicle Car ... instance Vehicle Ship ...,
a Vehicle has a set of MetalDetail-s. A Car has this kinds of
MetalDetail-s, a Ship has other kinds of MetalDetail-s,
an Object can be constructed of Vehicle-s in such and such ways.
A SeaPort is an Object. Finally, the way to compute the function
f object = "number of standard details" in an Object may relay on
the class of this object and also on its construction. Computing f
may be, in general, by class membership and spends much of computation
cost. Computing f by a concrete construction of an object is faster,
but more special, -- and the result is the same. And there will appear
instance overlap.
I am sorry, I have not time to invent this real-life example.
Regards,
-----------------
Serge Mechveliani
mechvel at botik.ru
More information about the Glasgow-haskell-users
mailing list