
#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