[This is a repost of an email I sent yesterday to
`[EMAIL PROTECTED]'. For some reasons it did not come through.
Either the moderator didn't like it or something is wrong with
`haskell.org'. I tacitly assume the latter ;-). RH]

[This email is mainly directed to the type and class system experts
among us.]

To come right to the point I wonder whether it is technically possible
to derive instance declarations? Consider the following declarations.

> class Flatten tree where
>     flatten                   :: tree a -> [a]
>
> newtype Id a                  =  Id a
>
> flatten (Id a)                =  [a]

As it stands this is not legal Haskell (Hugs complains `Repeated
definition for variable "flatten"'). If we rename `flatten' to
`flattenId', Hugs is perfectly happy and infers the type `flattenId ::
Id a -> [a]'. So why not automatically infer the following instance
declaration (on the grounds that we know that `flatten' is overloaded
and assuming that the name clash is not just accidental)?

> instance Flatten Id where ...

Given the following group of declarations

> data Fork tree a              =  Fork (tree a) (tree a)
>
> flatten (Fork l r)            =  flatten l ++ flatten r

we would infer the instance declaration

> instance (Flatten tree) => Flatten (Fork tree) where ...

Note that if we rename the occurence of `flatten' on the lhs Hugs
infers the type `(Flatten tree) => Fork tree a -> [a]'. Things become
interesting if we consider recursive types.

> data Bush a                   =  Leaf a | Fork (Bush a) (Bush a)
>
> flatten (Leaf a)              =  [a]
> flatten (Fork l r)            =  flatten l ++ flatten r

Even if we rename `flatten' on the lhs the program does not typecheck
(hugs complains `Bush is not an instance of class "Flatten"'). If we
rename the occurences of `flatten' on the rhs as well hugs infers the
type `Bush a -> [a]' giving rise to the following instance declaration.

> instance Flatten Bush where ...

So here is my question: is it always possible to automate this process
(even in the presence of mutual recursive type definitions and multiple
parameter type classes)?

As an aside, note that it is not always possible to turn a function
binding into an instance declaration because Haskell has no type
abstractions. Consider the function binding,

> flatten ts                    =  concat [ flatten t | t <- ts ]

which has type `(Flatten t) => [t a] -> [a]'. Unfortunately, `[t a] =
[] (t a)' does not match `tree a'. The type composition of `[]' and `t'
is not expressible without introducing an auxiliary type (like
`newtype Compose t u a =  Compose (t (u a))').

Finally note that I do not ask whether it is desirable to omit instance
declarations. I do not think that it is always desirable. However,
there are situations where one would wish that instance declarations
were less heavyweight. For example, if the class comprises only a
single method or if it is used only locally  within a module. Or during
program development: I often use hug's `:type' command to document my
program; wouldn't it be nice if one could use a similar mechanism to
infer instance declarations (especially if the types are very
complicated).

Cheers, Ralf


Reply via email to