[GHC] #9732: Pattern synonyms and unboxed values

#9732: Pattern synonyms and unboxed values -------------------------------------+------------------------------------- Reporter: monoidal | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 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: -------------------------------------+------------------------------------- It's possible to declare a toplevel unboxed value with a pattern synonym, which causes a panic: {{{ {-# LANGUAGE PatternSynonyms, MagicHash #-} pattern P = 0# }}} (compare with error on `x = 0#`). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9732: Pattern synonyms and unboxed values -------------------------------------+------------------------------------- Reporter: monoidal | Owner: 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: | -------------------------------------+------------------------------------- Description changed by monoidal: Old description:
It's possible to declare a toplevel unboxed value with a pattern synonym, which causes a panic:
{{{ {-# LANGUAGE PatternSynonyms, MagicHash #-} pattern P = 0# }}}
(compare with error on `x = 0#`).
New description: It's possible to declare a toplevel unboxed value with a pattern synonym, which causes a panic: {{{ {-# LANGUAGE PatternSynonyms, MagicHash #-} pattern P = 0# }}} (compare with error on `x = 0#`). `pattern P <- 0#` seems to work fine. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => cactus -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#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 goldfire): I would think that pattern synonyms for unlifted types ''should'' work, but with the same restrictions as normal patterns for unlifted types. That is, you can't use these patterns to define a global variable. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Right. If it works when the pattern synonym is expanded, it should work un-expanded Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): The problem with `pattern P = 0#` is that the wrapper it yields is `$WP = 0#` which is a top-level binding at an unboxed type. If `P` had any arguments, then `$WP` would be a function instead of a variable, and so it would be valid. So we could say that unboxed pattern synonyms are only allowed if they are either unidirectional or have arguments. But doesn't that sound a bit arbitrary? Side question: is it even possible to change the definition of `P` to have an argument but still be unboxed? Something like `pattern P x = (# 0#, x #)` doesn't work, because unboxed tuples are not allowed in patterns. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Look at `WwLib.mkWorkerArgs` which deals with much the same issue. We just add a void argument to the wrapper avoid the top-level unboxed binding. I think we can do the same thing for pattern synonyms, no? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Hmm. `mkWorkerArgs` looks like quite the rabbit hole... does it make sense to figure out the plumbing for that, or is it good enough to just steal the basic idea and implement something similar for pattern synonyms that ensures there's always at least one argument (a synthetic `()` if need be) to pattern synonym wrapper functions returning unboxed values? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): As for the unidirectional case, I was accidentally looking at the simplified output instead of just the desugared one. So with this code: {{{ {-# LANGUAGE PatternSynonyms, MagicHash #-} pattern PAT <- 0# f PAT = 42# }}} the Core generated for `f` is: {{{ Main.f :: GHC.Prim.Int# -> GHC.Prim.Int# [LclIdX, Str=DmdType] Main.f = \ (ds_dpR :: GHC.Prim.Int#) -> break<2>() case (\ _ [Occ=Dead, OS=OneShot] -> Control.Exception.Base.patError @ GHC.Prim.Int# "T9732.hs:7:1-11|function f"#) GHC.Prim.void# of wild_00 { __DEFAULT -> (case break<1>() 42 of wild_X4 { __DEFAULT -> Main.$mPAT @ GHC.Prim.Int# ds_dpR wild_X4 }) wild_00 } }}} which is close enough: it would be correct if only `wild_00` wasn't floated out... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Never mind, I've figured out that last bit -- it's because in this case, `$mPAT` is used at type `Int# -> Int# -> Int# -> Int#`, so it's always going to be strict in both the `cont` and the `fail` arguments. I'll change the code generator for matchers so that both `cont` and `fail` takes an extra `()` argument. Another problem, then, will be making the matcher polymorphic enough that its `r` type argument can be either `*` or `#`... So all in all, in this example, currently: {{{ $mPAT :: forall (r :: *). Int# -> r -> r -> r }}} but it should be {{{ $mPAT :: forall (r :: ?). Int# -> (() -> r) -> (() -> r) -> r }}} Does that sound reasonable? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): (and of course if `$mPAT :: forall (r :: ?)` is not kosher, we can just have two matchers, one `$mPAT :: forall (r :: *)` and one `$mPAT# :: (forall r :: #)`, and just have the extra `()` arguments for `cont`/`fail` for the latter) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): * `cont` and `fail` should take an extra arg if (but only if) they have no other value args, and the result type is unlifted. This is easy to test. * Don't give them an extra arg of `()`. Rather use `voidPrimId`. This is zero bits wide, and hence takes no instructions to pass. Just like `mkWorkerArgs`. * Yes, it's fine to give the `r` variable an `OpenTypeKind`. Similar to the `errorId` definitions in `MkId`. OK? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): Yes, I've found `voidPrimId`/`voidArgId` meanwhile, and I have a working implementation pushed to `wip/T9732` just now. However, I had to split the matcher into two, since otherwise I can't decide when to have the extra arg, since the result type is completely unknown at matcher generation time. So for now, I've went with {{{ Main.$mPAT :: forall r. GHC.Prim.Int# -> r -> r -> r Main.$m#PAT :: forall (r :: #). GHC.Prim.Int# -> (GHC.Prim.Void# -> r) -> (GHC.Prim.Void# -> r) -> r }}} so that takes care of using pattern synonyms when the _result_ type is unlifted: both of these now compile lint-free, and give the expected behaviour: {{{ f PAT = 42# g PAT = (42 :: Int) }}} So the only remaining TODO should be to add this extra `Void#` argument to the generated wrappers when there are no other arguments and the pattern type is unlifted. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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 simonpj): Yes, I see. You don't know if the result is unlifted, but you DO know if `cont` has value args. (Which it does not in this case.) I think you can just have the second of your two matchers, with `forall (r :: ?). ...`, something that is not possible in source Haskell, but which you can do in generated code I think. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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): A single open-kinded matcher works, yes, if we are OK with argument-free `cont`s and all `fail`s taking the extra `Void#` argument. I will redo my implementation for this design. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9732: Pattern synonyms and unboxed values -------------------------------------+------------------------------------- Reporter: monoidal | Owner: cactus Type: bug | Status: patch 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: | -------------------------------------+------------------------------------- Changes (by cactus): * status: new => patch Comment: Implementation based on the discussion above is now pushed to `wip/T9732`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9732: Pattern synonyms and unboxed values -------------------------------------+------------------------------------- Reporter: monoidal | Owner: cactus Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: pattern synonyms Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by cactus): * keywords: => pattern synonyms -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9732: Pattern synonyms and unboxed values
-------------------------------------+-------------------------------------
Reporter: monoidal | Owner: cactus
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
Resolution: | Keywords: pattern synonyms
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 Dr. ERDI Gergo

#9732: Pattern synonyms and unboxed values -------------------------------------+------------------------------------- Reporter: monoidal | Owner: cactus Type: bug | Status: merge Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.8.3 Resolution: | Keywords: pattern synonyms Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by cactus): * status: patch => merge * milestone: => 7.10.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9732: Pattern synonyms and unboxed values -------------------------------------+------------------------------------- Reporter: monoidal | Owner: cactus Type: bug | Status: merge Priority: normal | Milestone: 7.8.4 Component: Compiler | Version: 7.8.3 Resolution: | Keywords: pattern synonyms Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by cactus): * milestone: 7.10.1 => 7.8.4 Comment: Note that `7f929862..638991` all need to be cherry-picked to the 7.8 branch for this to work. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9732: Pattern synonyms and unboxed values -------------------------------------+------------------------------------- Reporter: monoidal | Owner: cactus Type: bug | Status: merge Priority: normal | Milestone: 7.8.4 Component: Compiler | Version: 7.8.3 Resolution: | Keywords: PatternSynonyms Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by cactus): * keywords: pattern synonyms => PatternSynonyms -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9732: Pattern synonyms and unboxed values -------------------------------------+------------------------------------- Reporter: monoidal | Owner: cactus Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.8.3 Resolution: fixed | Keywords: PatternSynonyms Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thoughtpolice): * status: merge => closed * resolution: => fixed * milestone: 7.8.4 => 7.10.1 Comment: Gergo, I couldn't cleanly apply this it seems even with those patches; so I'm afraid I'll be dropping this for 7.8.4. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9732: Pattern synonyms and unboxed values -------------------------------------+------------------------------------- Reporter: monoidal | Owner: cactus Type: bug | Status: merge Priority: normal | Milestone: 7.8.4 Component: Compiler | Version: 7.8.3 Resolution: fixed | Keywords: PatternSynonyms Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by cactus): * status: closed => merge * milestone: 7.10.1 => 7.8.4 Comment: I have pushed a new version of the commit that applies cleanly to `ghc-7.8` as `a91a2af..0f1f3e1`, please merge that. Also, in the future, please try applying the patches in question at an earlier time, instead of discovering if they have problems so close to the freeze date. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9732: Pattern synonyms and unboxed values -------------------------------------+------------------------------------- Reporter: monoidal | Owner: cactus Type: bug | Status: closed Priority: normal | Milestone: 7.10.1 Component: Compiler | Version: 7.8.3 Resolution: fixed | Keywords: PatternSynonyms Operating System: | Architecture: Unknown/Multiple Unknown/Multiple | Difficulty: Unknown Type of failure: Compile- | Blocked By: time crash | Related Tickets: Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thoughtpolice): * status: merge => closed * milestone: 7.8.4 => 7.10.1 Comment: 7.8.4 is already done; closing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9732#comment:24 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC