On 28-Jul-1998, Simon L Peyton Jones <[EMAIL PROTECTED]> wrote:
> "S.D.Mechveliani" <[EMAIL PROTECTED]> wrote:
> > This may occur a stupid question, but
> > why Haskell allows the `newtype' derivation only for the standard
> > classes?
> > Why not support declarations like
> >
> > newtype N a b = N (T a b) deriving(Eq,Ord,AddGroup,Ring)
> > or newtype N a b = N (T a b) deriving( all )
>
> That would indeed be possible for newtype; but my guess is
> that if you want 'all' then you ought to be able to get away without
> a newtype at all. But I might well be wrong about this.
> Anyway, it's not an unreasonable suggestion.
Yes, I'm not so keen on 'deriving(all)', but I like the other part
of the suggestion.
It would also be nice if Haskell-2 supported `deriving' declarations
with arbitary classes for OOP-style existential types.
class Foo t where
m1 :: t -> ...
m2 :: t -> ...
...
-- I'm using the ghc `forall' syntax for existential types
data AnyFoo = forall t . Foo t => MkAnyFoo t deriving (Foo)
The idea here is that for the `deriving (Foo)' declaration to be valid,
`Foo t' would have to be a uniparameter type class all of whose methods
have type `t -> T' for some type `T' not containing `t' [* see footnote].
The implicit instance declaration would be
instance Foo (AnyFoo) where
m1 (MkAnyFoo x) = m1 x
m2 (MkAnyFoo x) = m2 x
...
This is a more conservative proposal than my previous suggestions
about making the syntax for OOP style programming more convenient;
here the `data' declaration is explicit, so the reader can see what is
going on, only the `instance' declaration is implicit.
I think this is a reasonable compromise between brevity and readability.
[* Footnote]
Actually the restriction "not containing `t'" is probably a bit too
restrictive; I think it could be loosened to something like
"not containing `t' on the LHS of any `->' or in a argument of
any opaque type constructor". This would require changing the
derived instance declaration to
instance Foo (AnyFoo) where
m1 (MkAnyFoo x) = map_ts_to_AnyFoo_in_T1 (m1 x)
m2 (MkAnyFoo x) = map_ts_to_anyFoo_in_T2 (m2 x)
...
where each map_ts_to_AnyFoo_in_T is a function that traverses values of
type T replacing each subterm `x' that has type `t' with `MkAnyFoo x'.
--
Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED] | -- the last words of T. S. Garp.