[GHC] #12514: Can't write unboxed sum type constructors in prefix form
GHC
ghc-devs at haskell.org
Mon Aug 22 14:08:15 UTC 2016
#12514: Can't write unboxed sum type constructors in prefix form
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
(Parser) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
Replying to [comment:2 simonpj]:
> But if we stick to the current unary notation, I rather think we should
not allow spaces anywhere. Ditto for tuples. Maybe we should do it in the
lexer, not the parser?
Just to be clear on the is/ought distinction being discussed, GHC
//currently// accepts spaces in prefix tuple types/expressions/patterns:
{{{
$ /opt/ghc/head/bin/ghci -fobject-code -XUnboxedTuples
GHCi, version 8.1.20160819: http://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
λ> :t ( , , )
( , , ) :: a -> b -> c -> (a, b, c)
λ> :t (# , , #)
(# , , #) :: a -> b -> c -> (# a, b, c #)
λ> :k ( , , )
( , , ) :: * -> * -> * -> *
λ> :k (# , , #)
(# , , #) :: * -> * -> * -> TYPE 'GHC.Types.UnboxedTupleRep
λ> :t \a -> case a of ( , , ) x y z -> (# , , #) x y z
\a -> case a of ( , , ) x y z -> (# , , #) x y z
:: (a, b, c) -> (# a, b, c #)
}}}
Also, there is a current restriction for unboxed sums (as noted in osa1's
[http://osa1.net/posts/2016-07-22-unboxed-sums-faq.html#syntax-is-awful-
why blog]) that fully saturated applications of unboxed sum expressions
must separate their bars by whitespace:
> Data constructors use the same syntax, except we have to put spaces
between bars. For example, if you have a type with 10 alternatives, you do
something like `(# | | | | value | | | | | #)`. Space between bars is
optional in the type syntax, but not optional in the term syntax. The
reason is because otherwise we’d have to steal some existing syntax. For
example, `(# ||| a #)` can be parsed as singleton unboxed tuple of
`Control.Arrow.|||` applied to an argument, or an unboxed sum with 4
alternatives.
So if we require that the prefix counterparts must not have whitespace,
then we ought to consider what effects that would/should have on the
above. Food for thought.
> Also for data constructors what is the prefix form. E.g. Instead of
`(#| True ||#)`, do we write
> * `(#| ||#) True`, or
> * `(#_||#) True`?
>
> I prefer the latter. We should not have spaces in the middle of names?
Indeed, the latter notation is what GHC is
[https://git.haskell.org/ghc.git/blob/0d3bf62092de83375025edca6f7242812338542d:/compiler/prelude/TysWiredIn.hs#l854
using internally], I believe. But I'll be honest in that I'm not a huge
fan of that notation. For one thing, the underscore in the expression
`(#_||#) True` feels like it could represent a typed hole. Also, if
`(#_||#) True` is allowed to appear in pattern syntax, is the underscore a
wildcard pattern? Perhaps we could rule out these possibilities by
carefully designing the lexer/parser, but it's worth thinking over.
One more thing worth bringing up: in the
[https://ghc.haskell.org/trac/ghc/wiki/UnpackedSumTypes#Designquestions
UnpackedSumTypes wiki page], Richard brings up an interesting alternative
syntax for unboxed sum expressions, where `(# 0 of 3 | x #)` would mean
`(# x | | #)`. If we adopted that, we could have a much less ambiguous
prefix form:
{{{
(# 0 of 3 |#) x
\x -> case x of (# 0 of 3|#) x -> x
}}}
But I don't know if redesigning the term-level syntax is on the agenda.
osa1 mentions it in [osa1.net/posts/2016-07-22-unboxed-sums-faq.html the
conclusion] of his blog post, so maybe he can chime in on this.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12514#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list