#4179: Infinite loop with type function inference
---------------------------------+------------------------------------------
    Reporter:  simonpj           |        Owner:              
        Type:  bug               |       Status:  new         
    Priority:  normal            |    Milestone:              
   Component:  Compiler          |      Version:  6.12.3      
    Keywords:                    |   Difficulty:              
          Os:  Unknown/Multiple  |     Testcase:              
Architecture:  Unknown/Multiple  |      Failure:  None/Unknown
---------------------------------+------------------------------------------
 Kevin Quick ([email protected]) writes:
 I started with the following:
 {{{
 {-# LANGUAGE TypeFamilies  #-}

 class DoC a where
      type A2 a
      op :: a -> A2 a

 data Con x = InCon (x (Con x))
 type FCon x = x (Con x)

 foldDoC :: Functor f => (f a -> a) -> Con f -> a foldDoC f (InCon t) = f
 (fmap (foldDoC f) t)

 doCon :: (DoC (FCon x)) => Con x -> A2 (FCon x) doCon (InCon x) = op x

 fCon :: (Functor x, DoC (FCon x)) => Con x -> A2 (FCon x) fCon = foldDoC
 op
 }}}
 I then changed the rank of op, but forgot to update the foldDoC
 accordingly---see below.  Attempting to compile this causes GHC to run
 forever using 100% cpu.  The corrected definition of foldDoC works fine.
 Should the GHC (6.12.1) behavior in the face of my foolishness be reported
 as a bug or is this a legitimate infinite recursion of type deduction?

 {{{
 {-# LANGUAGE TypeFamilies  #-}

 class DoC a where
      type A2 a
      type A3 a
      op :: a -> A2 a -> A3 a

 data Con x = InCon (x (Con x))
 type FCon x = x (Con x)

 -- should have been changed to this, which works
 -- foldDoC :: Functor f => (f a -> a) -> A2 (FCon f) -> Con f -> a
 -- foldDoC f i (InCon t) = f (fmap (foldDoC f i) t)

 -- this original version causes GHC to hang foldDoC :: Functor f => (f a
 -> a) -> Con f -> a foldDoC f (InCon t) = f (fmap (foldDoC f) t)

 doCon :: (DoC (FCon x)) => Con x -> A2 (FCon x) -> A3 (FCon x) doCon
 (InCon x) = op x

 -- note that if this is commented out then there's no hang: presumably
 because GHC doesn't have to perform type deduction for foldDoC.
 fCon :: (Functor x, DoC (FCon x)) => Con x -> A2 (FCon x) -> A3 (FCon x)
 fCon = foldDoC op
 }}}

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