#5913: Type class dictionary call loops at runtime
------------------------------+---------------------------------------------
 Reporter:  mnislaih          |          Owner:                  
     Type:  bug               |         Status:  new             
 Priority:  normal            |      Component:  Compiler        
  Version:  7.4.1             |       Keywords:                  
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  Runtime crash     |       Testcase:                  
Blockedby:                    |       Blocking:                  
  Related:                    |  
------------------------------+---------------------------------------------
Description changed by mnislaih:

Old description:

> The following code works fine in 7.0.3 but fails with <loop> in 7.2.x and
> 7.4.1 :
> {{{
> {-# LANGUAGE UndecidableInstances #-}
>

> class         L0 a where l0 :: a -> a
> class L0 a => L1 a where l1 :: a -> a
> class L1 a => L2 a where l2 :: a -> a
>

> data Worksfine = Worksfine deriving Show
> instance                                   L0 Worksfine where l0 = id
> instance                                   L1 Worksfine where l1 = l2
> instance {- undecidable -} L1 Worksfine => L2 Worksfine where l2 = l0
>

> data WorksfineToo = WorksfineToo deriving Show
> instance                                      L0 WorksfineToo where l0 =
> id
> instance {- undecidable -} L2 WorksfineToo => L1 WorksfineToo where l1 =
> l2
> instance {- undecidable -} L1 WorksfineToo => L2 WorksfineToo where l2 =
> id
>

> -- l1 LoopsAtRuntime = <loop>
> -- l2 LoopsAtRuntime = <loop>
> data LoopsAtRuntime = LoopsAtRuntime deriving Show
> instance                                        L0 LoopsAtRuntime where
> l0 = id
> instance {- undecidable -} L2 LoopsAtRuntime => L1 LoopsAtRuntime where
> l1 = l2
> instance {- undecidable -} L1 LoopsAtRuntime => L2 LoopsAtRuntime where
> l2 = l0
>
> main = do
>   print (l1 WorksfineToo)
>   print (l2 WorksfineToo)
>   print (l1 LoopsAtRuntime)
>   print (l2 LoopsAtRuntime)
> }}}

New description:

 The following code works fine in 7.0.3 but crashes at runtime with <loop>
 in 7.2.x and 7.4.1 :
 {{{
 {-# LANGUAGE UndecidableInstances #-}


 class         L0 a where l0 :: a -> a
 class L0 a => L1 a where l1 :: a -> a
 class L1 a => L2 a where l2 :: a -> a


 data Worksfine = Worksfine deriving Show
 instance                                   L0 Worksfine where l0 = id
 instance                                   L1 Worksfine where l1 = l2
 instance {- undecidable -} L1 Worksfine => L2 Worksfine where l2 = l0


 data WorksfineToo = WorksfineToo deriving Show
 instance                                      L0 WorksfineToo where l0 =
 id
 instance {- undecidable -} L2 WorksfineToo => L1 WorksfineToo where l1 =
 l2
 instance {- undecidable -} L1 WorksfineToo => L2 WorksfineToo where l2 =
 id


 -- l1 LoopsAtRuntime = <loop>
 -- l2 LoopsAtRuntime = <loop>
 data LoopsAtRuntime = LoopsAtRuntime deriving Show
 instance                                        L0 LoopsAtRuntime where l0
 = id
 instance {- undecidable -} L2 LoopsAtRuntime => L1 LoopsAtRuntime where l1
 = l2
 instance {- undecidable -} L1 LoopsAtRuntime => L2 LoopsAtRuntime where l2
 = l0

 main = do
   print (l1 WorksfineToo)
   print (l2 WorksfineToo)
   print (l1 LoopsAtRuntime)
   print (l2 LoopsAtRuntime)
 }}}

--

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