[GHC] #7788: Recursive type family causes <<loop>>

GHC cvs-ghc at haskell.org
Sat Mar 23 05:18:09 CET 2013


#7788: Recursive type family causes <<loop>>
----------------------------------------+-----------------------------------
Reporter:  shachaf                      |          Owner:                  
    Type:  bug                          |         Status:  new             
Priority:  normal                       |      Component:  Compiler        
 Version:  7.6.2                        |       Keywords:                  
      Os:  Unknown/Multiple             |   Architecture:  Unknown/Multiple
 Failure:  Incorrect result at runtime  |      Blockedby:                  
Blocking:                               |        Related:                  
----------------------------------------+-----------------------------------
 This file:

 {{{
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE UndecidableInstances #-}

 data Proxy a = Proxy

 foo :: Proxy (F (Fix Id)) -> ()
 foo = undefined

 newtype Fix a = Fix (a (Fix a))
 newtype Id a = Id a

 type family F a
 type instance F (Fix a) = F (a (Fix a))
 type instance F (Id a) = F a

 main :: IO ()
 main = print $ foo Proxy
 }}}

 Dies with `<<loop>>`. The type family is recursive, of course:

 {{{
 *Main> :kind! F (Fix Id)
 F (Fix Id) :: *^CInterrupted.
 }}}

 But `<<loop>>` is still not the behavior I'd expect. The actual value is
 just `undefined`.

 In the file that this example came up, the situation was even worse --
 there was a situation where

 {{{
 moldMapOf l f = runAccessor . l (Accessor . f)
 main = print $ (flip appEndo [] . moldMapOf (ix 3) (Endo . (:)) $ testVal
 :: [Int]) -- <<loop>>
 main = print $ (flip appEndo [] . runAccessor . (ix 3) (Accessor . Endo .
 (:)) $ testVal :: [Int]) -- undefined
 }}}

 I.e. substitution can turn one program (which happens to be ⊥ here,
 admittedly, but that's not fundamental) into another (`<<loop>>`). This
 makes it very tricky to track down the recursive type family. If necessary
 I can hunt down a working test case and post it here -- it's a bit tricky
 to get working, though.

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



More information about the ghc-tickets mailing list