#1651: panic when interactively evaluating expression with a family type
--------------------------------------+-------------------------------------
  Reporter:  chak                     |          Owner:         
      Type:  bug                      |         Status:  new    
  Priority:  normal                   |      Milestone:         
 Component:  Compiler (Type checker)  |        Version:  6.7    
  Severity:  normal                   |       Keywords:         
Difficulty:  Unknown                  |             Os:  Unknown
  Testcase:                           |   Architecture:  Unknown
--------------------------------------+-------------------------------------
{{{
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE EmptyDataDecls #-}

 newtype Succ a = Succ a deriving Show
 data    Zero   = Zero
 instance Show Zero where show _ = "Zero"

 type family Add a b
 type instance Add Zero a     = a
 type instance Add (Succ n) m = Succ (Add n m)

 add :: a -> b -> Add a b
 add = undefined

 okay = show $ add Zero Zero
 bad  = add Zero Zero

 {- ghci transcript:

 *Main> okay
 "Zero"
 *Main> bad
 ghc-6.7.20070828: panic! (the 'impossible' happened)
   (GHC version 6.7.20070828 for i386-unknown-linux):
     readFilledBox t_a1D9{tv} [box]

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

 *Main> show bad

 <interactive>:1:0:
     No instance for (Show (Add Zero Zero))
       arising from a use of `show' at <interactive>:1:0-7
     Possible fix:
       add an instance declaration for (Show (Add Zero Zero))
     In the expression: show bad
     In the definition of `it': it = show bad
 -}
 }}}
 The panic arises as follows: `tcGhciStmts` calls `TcMatches.tcDoStmt` to
 type check `it <- bad`, which in turn evaluates
 {{{
  withBox liftedTypeKind $ \ pat_ty ->
    tcMonoExpr rhs (mkAppTy m_ty pat_ty)
 }}}
 The `withBox` executes the `readfilledBox` that causes the panic, as
 `tcMonoExpr` promises to fill the boxes in its second argument.  This
 promise is not fulfilled, as `tcMonoBox` defers the match `Add Zero Zero ~
 IO t_ayP`.

 Further up the call chain `tcGhciStmts` will eventually simplify the LIE
 and would discover the type mismatch (and hence abandon "Plan A", of which
 all this is part).  Unfortunately, we never get there due to `withBox`s
 attempt to read `t_avP`.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1651>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to