[GHC] #14228: PatternSynonyms Non-exhaustive with UnboxedSums

#14228: PatternSynonyms Non-exhaustive with UnboxedSums -------------------------------------+------------------------------------- Reporter: guibou | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Keywords: UnboxedSum, | Operating System: Unknown/Multiple PatternSynonyms | Architecture: | Type of failure: Incorrect result Unknown/Multiple | at runtime Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following implementation of `Maybe` using UnboxedSums results in `Non- exhaustive patterns in case`: (`Failure.hs` file) {{{#!haskell {-# LANGUAGE UnboxedSums #-} {-# LANGUAGE PatternSynonyms #-} type Maybe' t = (# t | () #) pattern Just' :: a -> Maybe' a pattern Just' x = (# x | #) pattern Nothing' :: Maybe' a pattern Nothing' = (# | () #) foo x = case x of Nothing' -> putStrLn "nothing" Just' _ -> putStrLn "just" main = do putStrLn "Nothing'" foo Nothing' putStrLn "Just'" foo (Just' "hello") }}} When executed, it prints: {{{ Nothing' nothing Just' Failure: Failure.hs:10:20-29: Non-exhaustive patterns in case }}} Compiled with `ghc Failure.hs`. Please note that by removing the `pattern`s, and writting `foo` as following works as expected: {{{#!haskell foo x = case x of (# | () #) -> putStrLn "nothing" (# _ | #) -> putStrLn "just" }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14228 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14228: PatternSynonyms Non-exhaustive with UnboxedSums -------------------------------------+------------------------------------- Reporter: guibou | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.1 Resolution: | Keywords: UnboxedSums, | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: UnboxedSum, PatternSynonyms => UnboxedSums, PatternSynonyms Comment: Wow! Great catch. Indeed, the `ddump-simpl` output for that program looks mighty suspicious. I'll post an abridged version below: {{{#!hs -- RHS size: {terms: 14, types: 20, coercions: 0, joins: 0/0} $mJust' :: forall (r :: TYPE rep) a. Maybe' a -> (a -> r) -> (Void# -> r) -> r $mJust' = \ (@ (rep :: RuntimeRep)) (@ (r :: TYPE rep)) (@ a) (scrut :: Maybe' a) (cont :: a -> r) _ -> case scrut of { (#_|#) x -> cont x; (#|_#) ipv -> patError "Bug.hs:8:19-27|case"# } -- RHS size: {terms: 17, types: 21, coercions: 0, joins: 0/0} $mNothing' :: forall (r :: TYPE rep) a. Maybe' a -> (Void# -> r) -> (Void# -> r) -> r $mNothing' = \ (@ (rep :: RuntimeRep)) (@ (r :: TYPE rep)) (@ a) (scrut :: Maybe' a) (cont :: Void# -> r) _ -> case scrut of { (#_|#) ipv -> patError "Bug.hs:11:20-29|case"#; (#|_#) ds -> case ds of { () -> cont void# } } }}} Just //look// at that rubbish! The matchers for `Just'` and `Nothing'` each take a failure continuation as an argument, but appear to ignore them completely and just proceed directly to `patError` in case the expected pattern wasn't matched. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14228#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14228: PatternSynonyms Non-exhaustive with UnboxedSums -------------------------------------+------------------------------------- Reporter: guibou | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: UnboxedSums, | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3951 Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => patch * differential: => Phab:D3951 * milestone: => 8.2.2 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14228#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14228: PatternSynonyms Non-exhaustive with UnboxedSums
-------------------------------------+-------------------------------------
Reporter: guibou | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1
Resolution: | Keywords: UnboxedSums,
| PatternSynonyms
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3951
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#14228: PatternSynonyms Non-exhaustive with UnboxedSums -------------------------------------+------------------------------------- Reporter: guibou | Owner: (none) Type: bug | Status: merge Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: | Keywords: UnboxedSums, | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3951 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: patch => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14228#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14228: PatternSynonyms Non-exhaustive with UnboxedSums -------------------------------------+------------------------------------- Reporter: guibou | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: UnboxedSums, | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3951 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14228#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#14228: PatternSynonyms Non-exhaustive with UnboxedSums -------------------------------------+------------------------------------- Reporter: guibou | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1 Resolution: fixed | Keywords: UnboxedSums, | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect result | Unknown/Multiple at runtime | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3951 Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): comment:3 merged to `ghc-8.2` as fb5190185b6819ff4f4b64167d37da85337c524c. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14228#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC