[GHC] #11367: [Regression] Pattern synonyms
GHC
ghc-devs at haskell.org
Thu Jan 7 00:42:01 UTC 2016
#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
More information about the ghc-tickets
mailing list