[GHC] #13986: TypeApplications causes parse errors in @-patterns with certain Unicode characters
GHC
ghc-devs at haskell.org
Sun Jul 16 23:49:19 UTC 2017
#13986: TypeApplications causes parse errors in @-patterns with certain Unicode
characters
-------------------------------------+-------------------------------------
Reporter: Tikhon | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
(Parser) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by Tikhon:
Old description:
> The following function definition works without TypeApplications but
> fails to parse with the extension enabled:
>
> {{{#!hs
> {-# LANGUAGE TypeApplications #-}
> module Mininal where
>
> foo x₁@True = 10
> }}}
>
> It also parses correctly with "x" in place of "x₁".
New description:
The following function definition works without TypeApplications but fails
to parse with the extension enabled:
{{{#!hs
{-# LANGUAGE TypeApplications #-}
module Mininal where
foo x₁@True = 10
}}}
It also parses correctly with "x" in place of "x₁".
Parse error:
{{{
Minimal.hs:5:1-11: error: …
Parse error in pattern: foo x₁ @True
Compilation failed.
}}}
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13986#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list