[Haskell-cafe] Class-like features for explicit arguments

Roman Cheplyaka roma at ro-che.info
Sat Apr 25 14:24:37 UTC 2015


On 25/04/15 15:51, Ertugrul Söylemez wrote:
>> hrm, wouldn't your proposed extension be largely accomplished by using
>> Record pun and Record WildCards?
> 
> A part of it would, but it wouldn't preserve operators.  For example
> instead of `x r.<> y` you would have to write `(<>) r x y`.

Not at all.

  {-# LANGUAGE RecordWildCards #-}

  import Prelude hiding (sum)

  data Monoid a = Monoid { empty :: a, (<>) :: a -> a -> a }

  sum :: Num a => Monoid a
  sum = Monoid 0 (+)

  three :: Integer
  three =
    let Monoid{..} = sum in
    1 <> 2

> Other class features are not accessible,
> most notably type-level features like associated types.

Associated types become additional type variables of the record type.

A class

  class C a where
    type T a

is essentially equivalent to

  class C a t | a -> t

But the functional dependency is not enforceable on the value level
(isn't the whole point of this discussion not to restrict what
"instances" can be defined), so you end up with

  class C a t,

a simple MPTC.

> Also defaults are not available.

Now this is a good point.

> The idea is that a record would be completely equivalent to a class with
> the only difference being that you define values instead of instances,
> that there are no constraints on which values can exist and that those
> values must be passed explicitly to functions as regular arguments.

Except we already have regular records (aka data types) which satisfy
90% of the requirements, and adding another language construct to
satisfy those remaining 10% feels wrong to me. I'd rather improve the
existing construct.

Roman


-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 819 bytes
Desc: OpenPGP digital signature
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150425/fefb5bd8/attachment.sig>


More information about the Haskell-Cafe mailing list