[GHC] #12514: Can't write unboxed sum type constructors in prefix form
GHC
ghc-devs at haskell.org
Mon Aug 22 00:51:30 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):
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
More information about the ghc-tickets
mailing list