A question about run-time errors when class members are undefined

Anthony Clayden anthony_clayden at clear.net.nz
Fri Oct 5 10:18:51 UTC 2018


On Fri, 5 Oct 2018 at 9:00 PM, Jurriaan Hage <J.Hage at uu.nl> wrote:

>
> We first go the slavish route, to provide a basis for changing things
> later.
>
> So I am not looking for alternative ways of doing this, I am just
> wondering whether there is a rationale for doing things this way.
> The document does not give one.
>

The only explanation I can think of is that there might be default
implementations of the methods -- very likely defined in terms of other
methods in the class. (Such as (/=) defaulting to `not (==)`, and (==)
defaulting to `not (/=)`.) Then it's a nuisance to have to say 'just use
the default'. But I agree GHC should cope better than a run-time exception.


> And now I hear that records suffer from the same issue (thanks Cale).


I'm not perturbed or surprised by that. Consider the assignments to the
`zn` have the same effect here:

data D = MkD {x :: Int, y :: Bool}

z1 = MkD{ x = 5 }                                  -- y not mentioned, so
set undefined
z2 = MkD{ x = 5, y = undefined }
z3 = MkD 5 undefined

We had not run into this yet, because right now Helium does not have ‘em.


Haskell records were embarrassingly bad in 1998. No change or improvement
in Haskell 2010. Some minor easing in recent years with GHC extensions --
I'd call that lipstick on a pig.

If you've not implemented 'em yet, I just plain wouldn't. Ever. Support
Lenses or any of the 50 gazillion proposals. Even Hugs' TRex is better
(throws a type error at compile time if you omit a field).

Both sound fishy to me and if nobody can make a case for having things this
> way
> in the first place, I wonder why it’s like that.
>

There's a huge volume of minor inconsistencies and annoyances in GHC. I
guess we hardly notice because we get used to them (or we each use a subset
of features). A lot can be explained by the shackle of backwards
compatibility: every new extension must use distinct syntax, so that people
who don't want it/aren't aware of it don't run into surprises. For example,
there's now annoyingly similar-but-different semantics for H98 data,
existential fields, constrained fields, GADTs, data families/instances,
view patterns, pattern synonyms. I can't help but feel they should all get
unified into a single semantics; then those differing syntactic forms be
treated as shorthands/variations on a theme.



> The only one I might consider at this time is GADTs,


I do find the (~) type equality constraints from GADTs/Type Families very
pleasing and intuitive. You might be able to implement that without all the
other paraphernalia.

AntC


> > On 4Oct, 2018, at 03:55, Anthony Clayden <anthony_clayden at clear.net.nz>
> wrote:
> >
> > > We are adding classes and instances to Helium.
> > > We wondered about the aspect that it is allowed to have a class
> instance
> > > of which not all fields have a piece of code/value associated with
> them, ...
> >
> > I have a suggestion for that. But first let me understand where you're
> going with Helium. Are you aiming to slavishly reproduce Haskell's
> classes/instances, or is this a chance for a rethink?
> >
> > Will you want to include associated types and associated datatypes in
> the classes? Note those are just syntactic sugar for top-level type
> families and data families. It does aid readability to put them within the
> class.
> >
> > I would certainly rethink the current grouping of methods into classes.
> Number purists have long wanted to split class Num into Additive vs
> Multiplicative. (Additive would be a superclass of Multiplicative.) For the
> Naturals perhaps we want Presburger arithmetic then Additive just contains
> (+), with `negate` certainly in a different class, perhaps (-) subtract
> also in a dedicated class. Also there's people wanting Monads with just
> `bind` not `return`. But restructuring the Prelude classes/methods is just
> too hard with all that legacy code. Even though you should be able to do:
> >
> > class (Additive a, Subtractive a, Negative a, Multiplicative a, Divisive
> a) => Num a
> >
> > Note there's a lot of classes with a single method, and that seems to be
> an increasing trend. Historically it wasn't so easy in Haskell to do that
> superclass constraints business; if it had been perhaps there would be more
> classes with a single method. Then there's some disadvantages to classes
> holding multiple methods:
> > * the need to provide an overloading for every method, even though it
> may not make sense
> >   (or suffer a run-time error, as you say)
> > * the inability to 'fine tune' methods for a specific datatype [**]
> > * an internal compiler/object code cost of passing a group of methods in
> a dictionary as tuple
> >   (as apposed to directly selecting a single method)
> >
> > [**] Nats vs Integrals vs Fractionals for `Num`; and (this will be
> controversial, but ...) Some people want to/some languages do use (+) for
> concatenating Strings/lists. But the other methods in `Num` don't make any
> sense.
> >
> > If all your classes have a single method, the class name would seem to
> be superfluous, and the class/instance decl syntax seems too verbose.
> >
> > So here's a suggestion. I'll need to illustrate with some definite
> syntax, but there's nothing necessary about it. (I'll borrow the Explicit
> Type Application `@`.) To give an instance overloading for method `show` or
> (==)
> >
> > show @Int = primShowInt                     -- in effect pattern
> matching on the type
> > (==) @Int = primEqInt                       -- so see showList below
> > That is: I'm giving an overloading for those methods on type `Int`. How
> do I declare those methods are overloadable? In their signature:
> >
> > show @a :: a -> String                      -- compare show :: Show a =>
> a -> String
> > (==) @a :: a -> a -> Bool
> > Non-overladable functions don't have `@a` to the left of `::`.
> > How do I show that a class has a superclass constraint? That is: a
> method has a supermethod constraint, we'll still use `=>`:
> >
> > show @a :: showsPrec @a => a -> String      -- supermethod constraint
> > show @[a] :: show a => [a] -> String        -- instance decl, because
> not bare a, with constraint =>
> > show @[a] xss = showList xss
> > (*) @a :: (+) @a => a -> a -> a
> >
> > Is this idea completely off the wall? Take a look at Wadler's original
> 1988 memo introducing what became type classes.
> >
> http://homepages.inf.ed.ac.uk/wadler/papers/class-letter/class-letter.txt
> >
> > It reviews several possible designs, but not all those possibilities
> made it into his paper (with Stephen Blott) later in 1988/January 1989. In
> particular look at Section 1's 'Simple overloading'. It's what I'm
> suggesting above (modulo a bit of syntax). At the end of Section 1, Wadler
> rejects this design because of "potential blow-ups". But he should have
> pushed the idea a bit further. Perhaps he was scared to allow
> function/method names into type signatures? (I've already sneaked that in
> above with constraints.) These days Haskell is getting more relaxed about
> namespaces: the type `@`pplication exactly allows type names appearing in
> terms. So to counter his example, the programmer writes:
> >
> > square x = x * x                             -- no explicit signature
> given
> > square :: (*) @a => a -> a                   -- signature inferred,
> because (*) is overloaded
> > rms = sqrt . square                          -- no explicit signature
> > rms :: sqrt @a => a -> a                     -- signature inferred
> >
> > Note the inferred signature for `rms` doesn't need `(*) @a` even though
> it's inferred from `square`. Because (*) is a supermethod of `sqrt`. `sqrt`
> might also have other supermethods, that amount to `Floating`.
> >
> > > ... a run-time error results.
> > >
> > > Does anyone know of a rationale for this choice, since it seems rather
> unhaskell-like.
> >
> >
> > If you allow default method implementations (in the class, as Cale
> points out), then I guess you have to allow instance decls that don't
> mention all the methods. I think there should at least be a warning if
> there's no default method. Also beware the default method might have a more
> specific signature, which means it can't be applied for some particular
> instance.
> >
> > Altogether, I'd say, the culprit is the strong bias in early Haskell to
> bunch methods together into classes. These days with Haskell's richer/more
> fine-tuned typeclass features: what do typeclasses do that can't be done
> more precisely at method level -- indeed that would _better_ be done at
> method level?
> >
> >
> > AntC
> > _______________________________________________
> > Haskell-prime mailing list
> > Haskell-prime at haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-prime/attachments/20181005/ea2c023a/attachment-0001.html>


More information about the Haskell-prime mailing list