I worry that this thread is turning into a bit of bike shed before we have a good sense of what construction tools we have on hand!
Bardur Arantsson <spam@scientician.net> writes:
> Actually, thinking about it a little further... TupleSections is already
> opt-in, so this needn't conflict per se.
Isn't this dangerous, in how it now gives a trivial piece of code
two very different interpretations, in a plausibly unintentional way?
> {-# LANGUAGE TupleSections #-}
> (x, y, ) :: t -> (a, b, t)
> {-# LANGUAGE LaxCommas #-}
> (x, y, ) :: (a, b)
I understand that we have OverloadedStrings, viz:
> {-# LANGUAGE NoOverloadedStrings #-}
> "a" :: [Char]
> {-# LANGUAGE OverloadedStrings #-}
> "a" :: IsString a => a
and yet, the differences in this respect seems significant:
The unintentionality of change in interpretation effected by the
transition NoOverloadedStrings -> OverloadedStrings is implausible.
Whereas with the LaxCommas -> TupleSections transition I guess it would
be fair to say that it is plausible.
Moreover, OverloadedStrings doesn't disallow using string literals as
string literals, whereas LaxCommas and TupleSections are mutually
exclusive.
--
с уважениeм / respectfully,
Косырев Сергей
_______________________________________________
Haskell-prime mailing list
Haskell-prime@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-prime