[GHC] #12514: Can't write unboxed sum type constructors in prefix form

#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) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- You can write `(# Int | Char #)`, but not `(# | #) Int Char`. This is annoying since it prevents you from partially applying unboxed sum type constructors, and it also precludes you from doing cool things like `reify ''(#||#)` (as I woefully noted [https://phabricator.haskell.org/D2448 here]). Luckily, I don't think fixing this would be too hard. The special case of parsing unboxed tuple type constructors as prefix is handled [http://git.haskell.org/ghc.git/blob/0d3bf62092de83375025edca6f7242812338542d... here], so I //think// we'd just need to add a similar case for unboxed sums. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12514 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Well, it's not //quite// that simple, unfortunately. Vertical bars are a bit more finicky to parse than commas, so simply adding a new case to `ntgtycon` in `Parser.y` like so: {{{#!diff diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index b9479d9..fa0d0af 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -75,7 +75,8 @@ import TcEvidence ( emptyTcEvBinds ) import ForeignCall import TysPrim ( eqPrimTyCon ) import PrelNames ( eqTyCon_RDR ) -import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, tupleDataCon, nilDataCon, +import TysWiredIn ( unitTyCon, unitDataCon, tupleTyCon, sumTyCon, + tupleDataCon, nilDataCon, unboxedUnitTyCon, unboxedUnitDataCon, listTyCon_RDR, parrTyCon_RDR, consDataCon_RDR ) @@ -2861,6 +2862,9 @@ ntgtycon :: { Located RdrName } -- A "general" qualified tycon, exc | '(#' commas '#)' {% ams (sLL $1 $> $ getRdrName (tupleTyCon Unboxed (snd $2 + 1))) (mo $1:mc $3:(mcommas (fst $2))) } + | '(#' bars '#)' {% ams (sLL $1 $> $ getRdrName (sumTyCon + (snd $2 + 1))) + (mo $1:mc $3:(mbars (fst $2))) } | '(' '->' ')' {% ams (sLL $1 $> $ getRdrName funTyCon) [mop $1,mu AnnRarrow $2,mcp $3] } | '[' ']' {% ams (sLL $1 $> $ listTyCon_RDR) [mos $1,mcs $2] } @@ -3468,6 +3472,11 @@ mcs ll = mj AnnCloseS ll mcommas :: [SrcSpan] -> [AddAnn] mcommas ss = map (\s -> mj AnnCommaTuple (L s ())) ss +-- | Given a list of the locations of vertical bars, provide a [AddAnn] with an +-- AnnVbar entry for each SrcSpan +mbars :: [SrcSpan] -> [AddAnn] +mbars ss = map (\s -> mj AnnVbar (L s ())) ss + -- |Get the location of the last element of a OrdList, or noSrcSpan oll :: OrdList (Located a) -> SrcSpan oll l = }}} doesn't quite make the cut: Things that will parse successfully: * `(#| #)` * `(# | #)` * `(#| | #)` * `(# | | #)` That is, all sum type constructors such that (1) there's a space between the last bar and the `#)`, and (2) all bars are separated with at least one character of whitespace. Things that fail to parse: * `(#|#)` * `(# |#)` * `(#||#)` * `(#| |#)` * `(# | |#)` * `(# ||#)` * `(# || #)` (interestingly, GHC will parse this as the type operator `||` surrounded by hash-parens) Perhaps we require that bars must be separated by spaces as a prefix type constructor? Or perhaps we can finagle with the parser more to fix this above issues? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12514#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): There's a debate to be had about what concrete syntax for sums both unboxed and (not yet implemented) boxed. 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? 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? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12514#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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?
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
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: 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/0d3bf62092de83375025edca6f7242812338542... 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

#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 simonpj):
GHC currently accepts spaces in prefix tuple types/expressions/patterns:
Indeed. But I don't think it should. It an accident of implementation, not a goal. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12514#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Ben Gamari

#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): While we await a design for prefix unboxed sum type/data constructors in Haskell, a convenient workaround for this issue is to just use Template Haskell. (I've opened Phab:D2854 for this.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12514#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 Ryan Scott

#12514: Can't write unboxed sum type constructors in prefix form -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Parser) | Resolution: | Keywords: UnboxedSums Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => UnboxedSums -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12514#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12514: Can't write unboxed sum type constructors in prefix form -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.1 (Parser) | Resolution: wontfix | Keywords: UnboxedSums Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => wontfix Comment: I've lost interest in this ticket. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12514#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC