[GHC] #13929: GHC panic with levity polymorphism

#13929: GHC panic with levity polymorphism --------------------------------------+--------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Keywords: | Operating System: Windows Architecture: x86_64 (amd64) | Type of failure: None/Unknown Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: --------------------------------------+--------------------------------- I'm using GHC version 8.2.0.20170507 This code fails to compile {{{#!hs {-# LANGUAGE MagicHash #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE AllowAmbiguousTypes #-} module Main where import GHC.Exts import Data.Kind import GHC.Generics class GUnbox (f :: Type -> Type) (r :: RuntimeRep) where type GUnboxed f r :: TYPE r gunbox :: f p -> GUnboxed f r instance (GUnbox f rf, GUnbox g rg) => GUnbox (f :*: g) ('TupleRep '[rf, rg]) where type GUnboxed (f :*: g) ('TupleRep '[rf, rg]) = (# GUnboxed f rf, GUnboxed g rg #) -- if I remove implementation of `gunbox` it compiles successfully gunbox (x :*: y) = (# gunbox x, gunbox y #) main :: IO () main = pure () }}} with message: {{{ [1 of 1] Compiling Main ( Main.hs, .stack- work\dist\f42fcbca\build\Main.o ) ghc.EXE: panic! (the 'impossible' happened) (GHC version 8.2.0.20170507 for x86_64-unknown-mingw32): isUnliftedType GUnboxed g_a21y rg_a21z :: TYPE rg_a21z Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler\utils\Outputable.hs:1134:58 in ghc:Outputable callStackDoc, called at compiler\utils\Outputable.hs:1138:37 in ghc:Outputable pprPanic, called at compiler\types\Type.hs:1954:10 in ghc:Type Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism ---------------------------------+-------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by bgamari): * cc: goldfire (added) Comment: Thanks for the bug report and nice reproducer! Adding goldfire to CC. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism ---------------------------------+-------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) Comment: Fun example -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism ---------------------------------+-------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Changes (by bgamari): * keywords: => TypeInType -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism ---------------------------------+-------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType Operating System: Windows | Architecture: x86_64 (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | ---------------------------------+-------------------------------------- Comment (by bgamari): For the record, a more complete callstack is, {{{ ghc-stage2: panic! (the 'impossible' happened) (GHC version 8.2.0.20170704 for x86_64-unknown-linux): isUnliftedType GUnboxed g_a20x rg_a20y :: TYPE rg_a20y Call stack: CallStack (from HasCallStack): prettyCurrentCallStack, called at compiler/utils/Outputable.hs:1133:58 in ghc:Outputable callStackDoc, called at compiler/utils/Outputable.hs:1137:37 in ghc:Outputable pprPanic, called at compiler/types/Type.hs:1954:10 in ghc:Type isUnliftedType, called at compiler/coreSyn/CoreUtils.hs:487:27 in ghc:CoreUtils needsCaseBinding, called at compiler/coreSyn/MkCore.hs:162:10 in ghc:MkCore mk_val_app, called at compiler/coreSyn/MkCore.hs:146:42 in ghc:MkCore mkCoreApps, called at compiler/coreSyn/MkCore.hs:154:26 in ghc:MkCore mkCoreConApps, called at compiler/coreSyn/MkCore.hs:364:5 in ghc:MkCore mkCoreUbxTup, called at compiler/coreSyn/MkCore.hs:370:32 in ghc:MkCore mkCoreTupBoxity, called at compiler/deSugar/DsExpr.hs:382:19 in ghc:DsExpr Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Windows | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * keywords: TypeInType => TypeInType, LevityPolymorphism -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * os: Windows => Unknown/Multiple * architecture: x86_64 (amd64) => Unknown/Multiple -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): To be clear, I don't think (although could be wrong) this program should compile; afterall, the type of `gunbox` requires that we represent a levity polymorphic result, which we cannot do. Hence, the real bug here is the panic instead of a proper type error. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

To be clear, I don't think (although could be wrong) this program should compile; afterall, the type of `gunbox` requires that we represent a levity polymorphic result, which we cannot do. Hence, the real bug here is
#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vagarenko): Replying to [comment:7 bgamari]: the panic instead of a proper type error. I think levity polymorphism paper says you can't have functions with levity-polymorphic parameters, levity-polymorphic results are OK. This compiles fine: {{{#!hs instance (GUnbox f r) => GUnbox (M1 i t f) r where type GUnboxed (M1 i t f) r = GUnboxed f r gunbox (M1 x) = gunbox x }}} But unboxed sum also fails to compile: {{{#!hs instance (GUnbox f rf, GUnbox g rg) => GUnbox (f :+: g) ('SumRep '[rf, rg]) where type GUnboxed (f :+: g) ('SumRep '[rf, rg]) = (# GUnboxed f rf | GUnboxed g rg #) gunbox (L1 l) = (# gunbox l | #) gunbox (R1 r) = (# | gunbox r #) }}} with the same message. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.2.2 Comment: I'm afraid this won't be fixed for 8.2.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism
-------------------------------------+-------------------------------------
Reporter: vagarenko | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1-rc2
Resolution: | Keywords: TypeInType,
| LevityPolymorphism
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

To be clear, I don't think (although could be wrong) this program should compile; afterall, the type of gunbox requires that we represent a levity
#13929: GHC panic with levity polymorphism
-------------------------------------+-------------------------------------
Reporter: vagarenko | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1-rc2
Resolution: | Keywords: TypeInType,
| LevityPolymorphism
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by vagarenko):
Replying to [comment:10 Ben Gamari
I think levity polymorphism paper says you can't have functions with levity-polymorphic parameters, levity-polymorphic results are OK.
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): It looks to me that the runtime representation of `x` and `y` can't be known at compile time -- these arguments are levity-polymorphic, which is problematic. Do you see otherwise? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

It looks to me that the runtime representation of `x` and `y` can't be known at compile time -- these arguments are levity-polymorphic, which is
#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by vagarenko): Replying to [comment:12 goldfire]: problematic. Do you see otherwise? `x, y :: f p` where `f :: Type -> Type` and `p :: Type` so they are always lifted, right? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): The problem is the result type of `gunbox x`. Namely, we have {{{#!hs class GUnbox (f :: Type -> Type) (r :: RuntimeRep) where type GUnboxed f r :: TYPE r gunbox :: f p -> GUnboxed f r }}} and {{{#!hs f :: Type -> Type p :: Type x :: f p }}} therefore {{{#!hs gunbox x :: GUnboxed f rf }}} Which is levity polymorphic. My understanding is that this wouldn't be the problem if this were at the head of the RHS; however, in this case we need to build an unboxed tuple from it, which is problematic. In short: returning levity polymorphic things generally isn't a problem. However, the moment we actually need to manipulate such a value we have a problem. I find it helpful to consider why this is from the standpoint of a concrete operational model. You can think of the `RuntimeRep` of a function's return type as being a description of which machine register(s) the result can be found in. In the case that we have a function like, {{{#!hs ($) :: forall (r :: RuntimeRep) (a :: TYPE r) (b :: Type). (b -> a) -> b -> a f $ x = f x }}} The `($)` function never needs to //do// anything with the levity- polymorphic value: it simply sets up the call to `f` and jumps. In fact, flow of control will never even return to `($)` after this jump. Consequently, the code that we generate for `($)` can be entirely agnostic to the `RuntimeRep` that it is used at. Now let's consider at your function, {{{#!hs gunbox :: (GUnbox f rf, GUnbox g rg) => (f :*: g) -> (# GUnboxed f rf, GUnboxed g rg #) gunbox (x :*: y) = (# gunbox x, gunbox y #) }}} Specifically, let's consider the case where `f ~ Double` and `g ~ Maybe Int` (with instances such that `rf ~ DoubleRep` and `rg ~ LiftedPtrRep`). In this case `gunbox` will need to first evaluate `gunbox x`, which will save its result in one of the machine's floating point registers. Then it will need to evaluate `gunbox y`, which will save its result in a pointer register. We can then return, having "constructed" our unboxed tuple. This case was easy as there was no "overlap" between the two registers used to return the result. However, let's consider another case, where `f ~ Double` and `g ~ Double` (therefore `rf ~ DoubleRep` and `rg ~ DoubleRep`). In this case `gunbox` will need to evaluate both `gunbox x` and `gunbox y`, but it must take care to move the result of one out of the way before evaluating the other since both will return their result in the same floating point register. This, of course, means that `gunbox` would need to behave differently depending upon the `RuntimeRep`s that it was working with. Our code generation strategy does not currently allow for this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): Great explanation in comment:14. Yes, my comment:12 is wrong. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism
-------------------------------------+-------------------------------------
Reporter: vagarenko | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1-rc2
Resolution: | Keywords: TypeInType,
| LevityPolymorphism
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by vagarenko):
Replying to [comment:14 bgamari]:
Now I see. Thank you for the very thorough explanation!
Replying to [comment:10 Ben Gamari
In [changeset:"fa626f3b1c1140a1f10bba60fdde10f767863f70/ghc" fa626f3/ghc]: {{{ #!CommitTicketReference repository="ghc" revision="fa626f3b1c1140a1f10bba60fdde10f767863f70" Fix #13929 by adding another levity polymorphism check
test case: typecheck/should_fail/T13929 }}}
Have you tested that patch with unboxed sums? See my comment:8 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): Indeed this still fails with the unboxed sum example. Adding a test. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism
-------------------------------------+-------------------------------------
Reporter: vagarenko | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1-rc2
Resolution: | Keywords: TypeInType,
| LevityPolymorphism
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: bgamari Type: bug | Status: new Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: (none) => bgamari Comment: I'll take care of the remaining case. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism
-------------------------------------+-------------------------------------
Reporter: vagarenko | Owner: bgamari
Type: bug | Status: new
Priority: high | Milestone: 8.2.2
Component: Compiler | Version: 8.2.1-rc2
Resolution: | Keywords: TypeInType,
| LevityPolymorphism
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => merge -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: bgamari Type: bug | Status: merge Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | ypecheck/should_fail/T13929 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * testcase: => ypecheck/should_fail/T13929 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13929: GHC panic with levity polymorphism -------------------------------------+------------------------------------- Reporter: vagarenko | Owner: bgamari Type: bug | Status: closed Priority: high | Milestone: 8.2.2 Component: Compiler | Version: 8.2.1-rc2 Resolution: fixed | Keywords: TypeInType, | LevityPolymorphism Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | typecheck/should_fail/T13929 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * testcase: ypecheck/should_fail/T13929 => typecheck/should_fail/T13929 * resolution: => fixed Comment: All patches listed above merged to `ghc-8.2` as of 78e673910f8759f643b263c70ad5c8fffd11a55d. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13929#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC