#3169: Type families occurs check
-------------------------------+--------------------------------------------
  Reporter:  simonpj           |          Owner:  chak            
      Type:  bug               |         Status:  new             
  Priority:  normal            |      Milestone:  6.12.1          
 Component:  Compiler          |        Version:  6.10.2          
  Severity:  normal            |       Keywords:                  
Difficulty:  Unknown           |       Testcase:                  
        Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-------------------------------+--------------------------------------------
 Consider this:
 {{{
 {-# LANGUAGE  TypeFamilies, ScopedTypeVariables #-}
 module Map where

 import Prelude hiding ( lookup )

 class Key k where
   type Map k :: * -> *
   lookup :: k -> Map k elt -> Maybe elt

 instance (Key a, Key b) => Key (a,b) where
   type Map (a,b) = MP a b
   lookup (a,b) (m :: Map (a,b) elt)
      = case lookup a m :: Maybe (Map b elt) of
           Just (m2 :: Map b elt) -> lookup b m2 :: Maybe elt

 data MP a b elt = MP (Map a (Map b elt))
 }}}
 This ought to typecheck, even in the absence of all those type signatures.
 But alas:
 {{{
 Map.hs:13:12:
     Occurs check: cannot construct the infinite type: elt = t elt
     In the expression: lookup a m :: Maybe (Map b elt)
     In the expression:
         case lookup a m :: Maybe (Map b elt) of {
           Just (m2 :: Map b elt) -> lookup b m2 :: Maybe elt }
 }}}
 Simon

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