#1999: panic with GADT etc.
----------------------------+-----------------------------------------------
  Reporter:  jeltsch        |          Owner:             
      Type:  bug            |         Status:  new        
  Priority:  normal         |      Milestone:  6.10 branch
 Component:  Compiler       |        Version:  6.9        
Resolution:                 |       Keywords:             
  Testcase:  T1999, T1999a  |      Blockedby:             
Difficulty:  Unknown        |             Os:  Linux      
  Blocking:                 |   Architecture:  x86        
   Failure:  None/Unknown   |  
----------------------------+-----------------------------------------------
Changes (by simonpj):

 * cc: sweirich@…, jbapple@…, byorgey@… (added)
  * owner:  chak =>
  * status:  closed => new
  * resolution:  fixed =>


Old description:

> The following code causes a panic with GHC installed from
> ghc-6.9.20071218-i386-unknown-linux.tar.bz2:
> {{{
> {-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs #-}
> module Bug where
>
>     class C a where
>
>         f :: G a -> ()
>
>     instance (C ()) => C (b c) where
>
>         f (G x) = f x where
>
>     data G a where
>
>         G  :: G () -> G (b c)
> }}}
> The output of ghci is:
> {{{
> GHCi, version 6.9.20071218: http://www.haskell.org/ghc/  :? for help
> Loading package base ... linking ... done.
> [1 of 1] Compiling Bug              ( Bug.hs, interpreted )
> ghc-6.9.20071218: panic! (the 'impossible' happened)
>   (GHC version 6.9.20071218 for i386-unknown-linux):
>         Coercion.splitCoercionKindOf
>     base:GHC.Prim.left{(w) tc 34B} $co${tc aog} [tv]
>     <pred>b{tv anB} [sk] ~ b{tv aoc} [sk]
>
> Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
> }}}
> The output of ghc -c is:
> {{{
> ghc-6.9.20071218: panic! (the 'impossible' happened)
>   (GHC version 6.9.20071218 for i386-unknown-linux):
>         Coercion.splitCoercionKindOf
>     base:GHC.Prim.left{(w) tc 34B} $co${tc a6t} [tv]
>     <pred>b{tv a5O} [sk] ~ b{tv a6p} [sk]
>
> Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
> }}}

New description:

 The following code causes a panic with GHC installed from
 ghc-6.9.20071218-i386-unknown-linux.tar.bz2:
 {{{
 {-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs #-}
 module Bug where

     class C a where
         f :: G a -> ()

     instance (C ()) => C (b c) where
         f (G x) = f x where

     data G a where
         G  :: G () -> G (b c)
 }}}
 The output of ghci is:
 {{{
 GHCi, version 6.9.20071218: http://www.haskell.org/ghc/  :? for help
 Loading package base ... linking ... done.
 [1 of 1] Compiling Bug              ( Bug.hs, interpreted )
 ghc-6.9.20071218: panic! (the 'impossible' happened)
   (GHC version 6.9.20071218 for i386-unknown-linux):
         Coercion.splitCoercionKindOf
     base:GHC.Prim.left{(w) tc 34B} $co${tc aog} [tv]
     <pred>b{tv anB} [sk] ~ b{tv aoc} [sk]

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}
 The output of ghc -c is:
 {{{
 ghc-6.9.20071218: panic! (the 'impossible' happened)
   (GHC version 6.9.20071218 for i386-unknown-linux):
         Coercion.splitCoercionKindOf
     base:GHC.Prim.left{(w) tc 34B} $co${tc a6t} [tv]
     <pred>b{tv a5O} [sk] ~ b{tv a6p} [sk]

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

--

Comment:

 In our POPL paper [http://research.microsoft.com/en-
 us/um/people/simonpj/papers/ext-f/popl163af-weirich.pdf "Generative type
 abstraction and type-level computation"] we proposed to '''remove the
 ability to decomopose type applications'''.  So Ganesh's example above
 would not work any more:
 {{{
 data EqTypes a b where
   EqConstr :: EqTypes a b -> EqTypes (s a) (s b)

 eqUnConstr :: EqTypes (s a) (s b) -> EqTypes a b
 eqUnConstr (EqConstr eq) = eq
 }}}
 Neither would Jim Apple's example.

 This is an un-forced change, and it does reduce expressiveness slightly,
 with no workaround.  On the other hand, it does undoubtedly make things a
 bit simpler and, as Section 6.2 of the paper says, it allows FC to have
 un-saturated type functions. BUT for type ''inference'' we still need
 saturated type functions, so allowing un-saturated type functions in the
 intermediate language only a theoretical improvement -- programmers don't
 see the benefit.

 Dimitrios and I think that it'd be possible to re-add `left` and `right`
 coercions, without too much hassle (and re-add the saturated-type-function
 reqt to FC).  Stephanie, Brent: do you agree?

 Meanwhile, Gasnesh, Jim, how much do you care?

 All this relates to the `ghc-new-co` branch, which will shortly become the
 master, so it's of more than theoretical interest.

 Simon

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1999#comment:12>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to