On Thu, Dec 11, 2025 at 09:15:16AM +0000, Simon Peyton Jones wrote:
> Classes with exactly one method and no superclass (or one superclass and no
> method) are called "unary classes".  And yes, they are still implemented
> with no overhead.
> 
> See this long Note:
> https://gitlab.haskell.org/ghc/ghc/-/blame/master/compiler/GHC/Core/TyCon.hs#L1453

Super, thank you for the reference.

> > I find type classes very difficult to evolve in a way that
> > satisfies my stability needs. Part of the reason for this is that
> > type classes as typically used don't really permit any form of
> > data abstraction: you list out all the methods explicitly in the
> > class definition.  There is no data hiding.
> 
> That's odd.   Can't you say
> ```
> module M( C, warble ) where
>    class C a where { op1, op2 :: a -> a }
> 
> warble :: C a => a -> a
> warble = ...
> ```
> and now a client of `M` can see `C` and `warble` but has no idea of the
> methods.

That deals with one direction across the abstraction boundary: the
elimination form.  We also need introduction forms as you point out:

> Of course if a client wants to make a new data type T into an instance of C
> then they need to know the methods, but that's reasonable: to make T an
> instance of C we must provide a witness for `op1` and `op2`.  So your
> teaser is indeed teasing.

Right, and once witnesses have been provided for `op1` and `op2`, the
client is now coupled to that interface.  Here's what I'm suggesting
instead:

    -- | Crucially, CD is abstract
    module M( C, CD, op1, op2, warble, Ops(..), cdOfOps ) where

    data CD a = MkCD { op1Impl :: a -> a, op2Impl :: a -> a }

    class C a where cImpl :: CD a

    warble :: C a => a -> a
    warble = ...

    op1 :: C a => a -> a
    op1 = op1Impl cImpl

    op2 :: C a => a -> a
    op2 = op2Impl cImpl

    data Ops a = MkOps { opsOp1 :: a -> a, opsOp2 :: a -> a }

    cdOfOps :: Ops a  -> CD a
    cdOfOps ops = MkCD { op1Impl = opsOp1 ops, op2Impl = opsOp2 ops }

And clients can now define

    instance C T where
      cImpl = cdOfOps MkOps { opsOp1 = ..., opsOp2 = ... }

But I can also provide more helper functions such as these:

  cdOfId :: CD a
  cdOfId = MkCD {op1Impl = id, op2Impl = id}
  
  cdOfTwice :: (a -> a) -> CD a
  cdOfTwice f = MkCD {op1Impl = f, op2Impl = f . f}

So instances can be written briefly, in a way that is typically done
with DerivingVia:

  instance C T2 where
    cImpl = cdOfId
  
  instance C Bool where
    cImpl = cdOfTwice not

Why do this? Suppose I realise that it is a law that `op2` must
*always* be `op1 . op1`.  Then `cdOfOps` becomes risky, and I can add
a warning to it, deprecate it, and subsequently remove it if I want.
Everything else, including `cdOfId` and `cdOfTwice` are safe, and can
remain unchanged.

There is no easy path if `op2` is a method.  I can't add a warning to
it, because it's still safe to *use* it and client code will be using
it.  It's just unsafe to *define* it.  Ideally it should be lifted out
of the class definition and defined as `op2 = op1 . op1`, but that
breaks every client who has a C instance defined, without the ability
to provide a smooth deprecation cycle.

Anyway, I hope to be able to write this up in more detail in the near
future, including the benefits I see we would have had during AMP,
Monad Of No Return, and the proposal to remove (>>) from Monad, if
this approach had been standard practice.

Tom
_______________________________________________
ghc-devs mailing list -- [email protected]
To unsubscribe send an email to [email protected]

Reply via email to