[GHC] #11367: [Regression] Pattern synonyms

#11367: [Regression] Pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: -------------------------------------+------------------------------------- Regression. This worked in 7.10.2: {{{#!hs {-# LANGUAGE PatternSynonyms, ViewPatterns #-} pattern A :: Int -> String pattern A n <- (read -> n) where A 0 = "hi" A 1 = "bye" }}} Removing the final clause works in GHC head but given the same code it claims the clause is empty: {{{ % ghci -ignore-dot-ghci /tmp/tmp.t0h0pMgwWb.hs GHCi, version 8.1.20160105: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tmp.t0h0pMgwWb.hs, interpreted ) /tmp/tmp.t0h0pMgwWb.hs:4:9: error: pattern synonym 'where' clause cannot be empty In the pattern synonym declaration for: A Failed, modules loaded: none. Prelude> }}} The where clause is certainly not empty — ironically seems to be caused by my very own #10426 ([https://phabricator.haskell.org/D1665 D1665]) :--) hoist by my own ticket as we say: {{{#!hs ; when (length matches /= 1) (wrongNumberErr loc) }}} Personally a trailing `where` is quite alright and handy when quickly checking if a declaration is otherwise OK. It works for data/newtype declarations as well as type classes. A workaround is to pattern match in other ways: {{{#!hs pattern A n <- ... where A = \case 0 -> "hi" 1 -> "bye" }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

A 3 "*** Exception: /tmp/tmp.t0h0pMgwWb.hs:(4,1)-(5,14): Non-exhaustive
#11367: [Regression] Pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Small note: When a pattern synonym is non-exhaustive its name is mangled: {{{ patterns in function $bA }}} It would be preferable to emit “Non-exhaustive patterns in pattern synonym A”. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 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: | -------------------------------------+------------------------------------- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * keywords: => PatternSynonyms -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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: | -------------------------------------+------------------------------------- Comment (by mpickering): Please can you create another ticket for the wrong name in the error message. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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: | -------------------------------------+------------------------------------- Comment (by mpickering):
Personally a trailing where is quite alright and handy when quickly checking if a declaration is otherwise OK.
I don't understand this comment. The trailing where indicates a bidirectional pattern synonym so you have to provide the builder as well as the matcher. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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 Iceland_jack: Old description:
Regression. This worked in 7.10.2:
{{{#!hs {-# LANGUAGE PatternSynonyms, ViewPatterns #-}
pattern A :: Int -> String pattern A n <- (read -> n) where A 0 = "hi" A 1 = "bye" }}}
Removing the final clause works in GHC head but given the same code it claims the clause is empty:
{{{ % ghci -ignore-dot-ghci /tmp/tmp.t0h0pMgwWb.hs GHCi, version 8.1.20160105: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tmp.t0h0pMgwWb.hs, interpreted )
/tmp/tmp.t0h0pMgwWb.hs:4:9: error: pattern synonym 'where' clause cannot be empty In the pattern synonym declaration for: A Failed, modules loaded: none. Prelude> }}}
The where clause is certainly not empty — ironically seems to be caused by my very own #10426 ([https://phabricator.haskell.org/D1665 D1665]) :--) hoist by my own ticket as we say:
{{{#!hs ; when (length matches /= 1) (wrongNumberErr loc) }}}
Personally a trailing `where` is quite alright and handy when quickly checking if a declaration is otherwise OK. It works for data/newtype declarations as well as type classes. A workaround is to pattern match in other ways:
{{{#!hs pattern A n <- ... where A = \case 0 -> "hi" 1 -> "bye" }}}
New description: Regression. This worked in 7.10.2: {{{#!hs {-# LANGUAGE PatternSynonyms, ViewPatterns #-} pattern A :: Int -> String pattern A n <- (read -> n) where A 0 = "hi" A 1 = "bye" }}} Removing the final clause works in GHC head but given the same code it claims the clause is empty: {{{ % ghci -ignore-dot-ghci /tmp/tmp.t0h0pMgwWb.hs GHCi, version 8.1.20160105: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tmp.t0h0pMgwWb.hs, interpreted ) /tmp/tmp.t0h0pMgwWb.hs:4:9: error: pattern synonym 'where' clause cannot be empty In the pattern synonym declaration for: A Failed, modules loaded: none. Prelude> }}} The where clause is certainly not empty — ironically seems to be caused by my very own #10426 ([https://phabricator.haskell.org/D1665 D1665]) :--) hoist by my own ticket as we say: {{{#!hs ; when (length matches /= 1) (wrongNumberErr loc) }}} Personally a trailing `where` is quite alright and handy when quickly checking if a declaration is otherwise OK. It works for data declarations as well as type classes. A workaround is to pattern match in other ways: {{{#!hs pattern A n <- ... where A = \case 0 -> "hi" 1 -> "bye" }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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: | -------------------------------------+------------------------------------- Old description:
Regression. This worked in 7.10.2:
{{{#!hs {-# LANGUAGE PatternSynonyms, ViewPatterns #-}
pattern A :: Int -> String pattern A n <- (read -> n) where A 0 = "hi" A 1 = "bye" }}}
Removing the final clause works in GHC head but given the same code it claims the clause is empty:
{{{ % ghci -ignore-dot-ghci /tmp/tmp.t0h0pMgwWb.hs GHCi, version 8.1.20160105: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tmp.t0h0pMgwWb.hs, interpreted )
/tmp/tmp.t0h0pMgwWb.hs:4:9: error: pattern synonym 'where' clause cannot be empty In the pattern synonym declaration for: A Failed, modules loaded: none. Prelude> }}}
The where clause is certainly not empty — ironically seems to be caused by my very own #10426 ([https://phabricator.haskell.org/D1665 D1665]) :--) hoist by my own ticket as we say:
{{{#!hs ; when (length matches /= 1) (wrongNumberErr loc) }}}
Personally a trailing `where` is quite alright and handy when quickly checking if a declaration is otherwise OK. It works for data declarations as well as type classes. A workaround is to pattern match in other ways:
{{{#!hs pattern A n <- ... where A = \case 0 -> "hi" 1 -> "bye" }}}
New description: Regression. This worked in 7.10.2: {{{#!hs {-# LANGUAGE PatternSynonyms, ViewPatterns #-} pattern A :: Int -> String pattern A n <- (read -> n) where A 0 = "hi" A 1 = "bye" }}} Removing the final clause works in GHC head but given the same code it claims the clause is empty: {{{ % ghci -ignore-dot-ghci /tmp/tmp.t0h0pMgwWb.hs GHCi, version 8.1.20160105: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( /tmp/tmp.t0h0pMgwWb.hs, interpreted ) /tmp/tmp.t0h0pMgwWb.hs:4:9: error: pattern synonym 'where' clause cannot be empty In the pattern synonym declaration for: A Failed, modules loaded: none. Prelude> }}} The where clause is certainly not empty — ironically seems to be caused by my very own #10426 ([https://phabricator.haskell.org/D1665 D1665]) :--) hoist by my own ticket as we say: {{{#!hs ; when (length matches /= 1) (wrongNumberErr loc) }}} Personally a trailing `where` is quite alright and handy when quickly checking if a declaration is otherwise OK. It works for data/newtype declarations as well as type classes. A workaround is to pattern match in other ways: {{{#!hs pattern A n <- ... where A = \case 0 -> "hi" 1 -> "bye" }}} -- Comment (by Iceland_jack): Replying to [comment:4 mpickering]:
Please can you create another ticket for the wrong name in the error message. Done #11368
Replying to [comment:5 mpickering]:
Personally a trailing where is quite alright and handy when quickly checking if a declaration is otherwise OK.
I don't understand this comment. The trailing where indicates a bidirectional pattern synonym so you have to provide the builder as well as the matcher.
It was poorly explained. My ''personal'' preference: {{{#!hs -- Unidirectional pattern A <- 'a' pattern A <- 'a' where -- Bidirectional pattern A <- 'a' where A = undefined pattern A <- 'a' where A = 'a' }}} I want to fail ASAP if I've made a mistake, I enjoy being able to compile “under-construction” code. All of these declarations compile (with creatively chosen extensions) {{{#!hs data A data A a data A (a :: Type) data A (a :: Type) :: Type data A (a :: Type) :: Type where class B class B a class B (a :: Type) class Show a => B (a :: Type) class Show a => B (a :: Type) where }}} Why I brought it up: for pattern synonyms that ''will'' be bidirectional I often add the `where` out of habit from data/class: compiler complains and I (erase where/compile/add where/add dummy clause/compile/...) or (keep where/add dummy clause/compile/...). It sounds minor (and it is!) but it adds to the cognitive load. While coding I don't like thinking “wait, did XYZ allow a where or not?”, reverting back to a well-formed declaration if I got it wrong. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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: | -------------------------------------+------------------------------------- Comment (by simonpj): Well in normal code you can't write {{{ f :: Int -> Int }}} and omit the declaration of `f`. You have to write {{{ f :: Int -> Int f = undefined }}} So it's consistent to require the same for pattern synonyms. Usually `where` clauses contain zero or more bindings, which is why an empty `where` is usually ok. But here it must contain exactly one. (Two would not make sense either.) For my money, I think it's maybe a mistake for the unidirectional/bidirectional split to be so quietly signaled. One could imagine {{{ pattern unidirectional Q a = pat pattern bidirectional P a b = pat pattern bidirectional R x = pat where R = ... }}} But opinions vary. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:8 simonpj]:
Well in normal code you can't write {{{ f :: Int -> Int }}} and omit the declaration of `f`. You have to write {{{ f :: Int -> Int f = undefined }}} So it's consistent to require the same for pattern synonyms. Funny you bring that up! I'm not sure if it's by design or a regression but omitting a method declaration (GHC 7.10) used to give a warning: {{{ Prelude> :set -XInstanceSigs Prelude> class A a where f :: a Prelude> instance A Int where f :: Int
<interactive>:11:10: Warning: No explicit implementation for ‘f’ In the instance declaration for ‘A Int’ }}} while in 8.1: {{{ <interactive>:3:22: error: The class method signature for ‘f’ lacks an accompanying binding (The class method signature must be given where ‘f’ is declared) }}} which [https://xkcd.com/1172/ affects me similarly]: I usually turn off warnings while churning out code and turn them on afterwards, now one must write a dummy definition "f = undefined" (maybe it's not so silly to expand standalone type signatures ⸨top-level, where block, instance⸩ into a dummy declaration: `-fcut-me-some-slack`....)¹
For my money, I think it's maybe a mistake for the unidirectional/bidirectional split to be so quietly signaled. One could imagine {{{ pattern unidirectional Q a = pat pattern bidirectional P a b = pat pattern bidirectional R x = pat where R = ... }}} But opinions vary.
May be! I feel it plays into the usual duality between reading and writing code. Your suggestion would certainly be clearer to people unfamiliar with pattern synonyms and all the different variations thereof, make it easier to search for and `grep` code. Consider my [comment:5 response to mpickering] as an offhand remark — a data point. It certainly should not dictate any design decisions.
Usually `where` clauses contain zero or more bindings, which is why an empty `where` is usually ok. But here it must contain exactly one. (Two would not make sense either.)
Could you not view a `where` clause in a pattern synonym as containing zero bindings (unidirectional) or a single binding (explicitly bidirectional). ¹ The more I think about it the less objectionable it sounds, as a flag solely for development. It's common to write stubs in Haskell given only their type with an dummy definition to satisfy the compiler, the compiler could expand `getId :: Person -> Id` into {{{#!hs getId :: Person -> Id getId = error "getId:15:1: Not defined." }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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: | -------------------------------------+------------------------------------- Comment (by mpickering): I think this reply is a mixture of a new ticket, #393 and some more context for this ticket.
Could you not view a where clause in a pattern synonym as containing zero bindings (unidirectional) or a single binding (explicitly bidirectional).
Yes you could, without looking I think this would require quite a bit of refactoring because of how everything is dealt with in the parser. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:10 mpickering]:
I think this reply is a mixture of a new ticket, #393 and some more context for this ticket.
Thanks mpickering, #393 looks promising. I have a keyboard macro for inserting `"undefined "`, if it got implemented I would use it aggressively: {{{
data X data Y f :: X → Y :t map f map f :: [X] -> [Y] }}}
looks great. Could [[ExplicitCallStack/ImplicitLocations]] be an alternative in #393 to `-fdefer-type-errors` + typed holes -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms 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: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Replying to [comment:10 mpickering]:
Could you not view a where clause in a pattern synonym as containing zero bindings (unidirectional) or a single binding (explicitly bidirectional).
Yes you could, without looking I think this would require quite a bit of refactoring because of how everything is dealt with in the parser.
If we take the route of #393 a pattern synonym `where` could always indicate an explicitly bidirectional pattern with a single clause: {{{#!hs pattern A <- 'a' where ---expands-into--> pattern A <- 'a' where A = _ }}} to Simon's point. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #393 #5791 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * related: => #393 #5791 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern
synonyms
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.1
Resolution: | Keywords:
| PatternSynonyms
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #393 #5791 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #393 #5791 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: merge Priority: normal | Milestone: Component: Compiler | Version: 8.1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #393 #5791 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Great! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #393 #5791 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * version: 8.1 => 8.0.1-rc1 * milestone: => 8.0.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | patsyn/should_compile/T11367 Blocked By: | Blocking: Related Tickets: #393 #5791 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by thomie): * testcase: => patsyn/should_compile/T11367 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11367: [Regression] Only one clause allowed in (explicitly bidirectional) pattern synonyms -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 Resolution: fixed | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | patsyn/should_compile/T11367 Blocked By: | Blocking: Related Tickets: #393 #5791 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed Comment: This was merged to `ghc-8.0` in e2c739772bfd12f1ad0bd900abbb34bc28de543e -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11367#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC