#3330: Type checker hangs
--------------------------------------+-------------------------------------
  Reporter:  MartijnVanSteenbergen    |          Owner:  chak            
      Type:  bug                      |         Status:  new             
  Priority:  normal                   |      Milestone:  6.12.1          
 Component:  Compiler (Type checker)  |        Version:  6.12.1 RC1      
Resolution:                           |       Keywords:                  
Difficulty:  Unknown                  |             Os:  Unknown/Multiple
  Testcase:                           |   Architecture:  x86_64 (amd64)  
   Failure:  Compile-time crash       |  
--------------------------------------+-------------------------------------
Changes (by byorgey):

  * failure:  => Compile-time crash
  * version:  6.10.3 => 6.12.1 RC1
  * os:  MacOS X => Unknown/Multiple

Comment:

 I think I've also tickled this bug, which appears to still exist in
 6.12.1rc2.  Here's a stripped-down version of the code that causes GHC to
 diverge for me:

 {{{
 {-# LANGUAGE EmptyDataDecls, TypeFamilies, TypeOperators, GADTs,
 KindSignatures #-}

 data (f :+: g) x = Inl (f x) | Inr (g x)

 data R :: (* -> *) -> * where
   RSum  :: R f -> R g -> R (f :+: g)

 class Rep f where
   rep :: R f

 instance (Rep f, Rep g) => Rep (f :+: g) where
   rep = RSum rep rep

 type family Der (f :: * -> *) :: * -> *
 type instance Der (f :+: g) = Der f :+: Der g

 plug :: Rep f => Der f x -> x -> f x
 plug = plug' rep where
   plug' :: R f -> Der f x -> x -> f x
   plug' (RSum rf rg) (Inl df) x = Inl (plug rf df x)
 }}}

 Note that this code has a bug; the call to plug in the last line ought to
 be plug' (and it works properly when fixed), but I would expect a type
 error instead of a diverging compiler.

 I'm classifying this as a "compile-time crash" since one bottom is as good
 as another. ;)

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/3330#comment:7>
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