#4272: Typechecker loop with type families
-------------------------------+--------------------------------------------
    Reporter:  NickSmallbone   |       Owner:                         
        Type:  bug             |      Status:  new                    
    Priority:  normal          |   Component:  Compiler (Type checker)
     Version:  6.13            |    Keywords:                         
    Testcase:                  |   Blockedby:                         
          Os:  Linux           |    Blocking:                         
Architecture:  x86_64 (amd64)  |     Failure:  Compile-time crash     
-------------------------------+--------------------------------------------
 The following code (which I think is ill-typed) causes GHC to hang, both
 on 6.12.1 and 6.13.20100616:

 {{{
 {-# LANGUAGE TypeFamilies, ScopedTypeVariables, FlexibleContexts #-}
 module Crash where

 class Family f where
   terms :: f a -> a

 class Family (TermFamily a) => TermLike a where
   type TermFamily a :: * -> *

 laws :: forall a b. TermLike a => TermFamily a a -> b
 laws t = prune t (terms (undefined :: TermFamily a a))

 prune :: TermLike a => TermFamily a a -> TermFamily a a -> b
 prune = undefined
 }}}

 The compiler still hangs if I remove the typeclass constraints (everything
 to the left of a =>, I mean), but everything else seems to be necessary
 for the compiler to loop. Using -dshow-passes shows that it's the
 typechecker that loops.

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