[GHC] #14228: PatternSynonyms Non-exhaustive with UnboxedSums
GHC
ghc-devs at haskell.org
Wed Sep 13 20:33:05 UTC 2017
#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
More information about the ghc-tickets
mailing list