[GHC] #9732: Pattern synonyms and unboxed values
GHC
ghc-devs at haskell.org
Tue Oct 28 09:21:10 UTC 2014
#9732: Pattern synonyms and unboxed values
-------------------------------------+-------------------------------------
Reporter: monoidal | Owner: cactus
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
Resolution: | Keywords:
Operating System: | Architecture: Unknown/Multiple
Unknown/Multiple | Difficulty: Unknown
Type of failure: Compile- | Blocked By:
time crash | Related Tickets:
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by cactus):
`pattern P <- 0#` doesn't completely work either:
{{{
{-# LANGUAGE PatternSynonyms, MagicHash #-}
pattern PAT <- 0#
f PAT = 42#
g 0# = 42#
}}}
This results in an `f` function that always fails the pattern match:
{{{
Main.f :: GHC.Prim.Int# -> GHC.Prim.Int#
[GblId, Arity=1, Str=DmdType]
Main.f =
\ _ [Occ=Dead] ->
break<4>()
Control.Exception.Base.patError
@ GHC.Prim.Int# "T9732.hs:6:1-11|function f"#
}}}
Contrast this with
{{{
Main.g :: GHC.Prim.Int# -> GHC.Prim.Int#
[GblId, Arity=1, Str=DmdType]
Main.g =
\ (ds_dL5 :: GHC.Prim.Int#) ->
break<1>()
case ds_dL5 of _ [Occ=Dead] {
__DEFAULT ->
Control.Exception.Base.patError
@ GHC.Prim.Int# "T9732.hs:7:1-10|function g"#;
0 -> break<0>() 42
}
}}}
Interestingly, if `f` returns a lifted `Int`, it all works out as
expected:
{{{
f PAT = (42 :: Int)
}}}
results in
{{{
Main.f :: GHC.Prim.Int# -> GHC.Types.Int
[GblId, Arity=1, Str=DmdType]
Main.f =
\ (ds_dLU :: GHC.Prim.Int#) ->
break<4>()
let {
cont_aLE :: GHC.Types.Int
[LclId, Str=DmdType]
cont_aLE = break<3>() GHC.Types.I# 42 } in
let {
fail_aLF :: GHC.Types.Int
[LclId, Str=DmdType]
fail_aLF =
Control.Exception.Base.patError
@ GHC.Types.Int "T9732.hs:6:1-19|function f"# } in
break<2>(fail_aLF,cont_aLE)
case ds_dLU of _ [Occ=Dead] {
__DEFAULT -> fail_aLF;
0 -> cont_aLE
}
}}}
Is it a good idea to just disallow pattern synonyms of unlifted types? Or
should `pattern P <- 0#` work at least?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9732#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list