#3108: Do a better job of solving recursive type-class constraints with 
functional
dependencies
----------------------------------------+-----------------------------------
    Reporter:  simonpj                  |       Owner:                  
        Type:  bug                      |      Status:  new             
    Priority:  high                     |   Milestone:  7.6.1           
   Component:  Compiler (Type checker)  |     Version:  6.10.1          
    Keywords:                           |          Os:  Unknown/Multiple
Architecture:  Unknown/Multiple         |     Failure:  None/Unknown    
  Difficulty:  Unknown                  |    Testcase:                  
   Blockedby:                           |    Blocking:                  
     Related:                           |  
----------------------------------------+-----------------------------------
Changes (by simonpj):

 * cc: dimitris@… (added)
  * failure:  => None/Unknown
  * priority:  lowest => high


Comment:

 With the new constraint solver we an ASSERT error for this program:
 {{{
 {-# LANGUAGE OverlappingInstances, UndecidableInstances,
 MultiParamTypeClasses,
              FunctionalDependencies, FlexibleInstances #-}

 module T3108 where

 -- Direct recursion terminates (typechecking-wise)

 class C0 x
  where
  m0 :: x -> ()
  m0 = const undefined

 instance (C0 x, C0 y) => C0 (x,y)
 instance C0 Bool
 instance C0 (x,Bool) => C0 x

 foo :: ()
 foo = m0 (1::Int)


 -- Indirect recursion does not terminate (typechecking-wise)

 class C1 x
  where
  m1 :: x -> ()
  m1 = const undefined

 instance (C1 x, C1 y) => C1 (x,y)
 instance C1 Bool
 instance (C2 x y, C1 (y,Bool)) => C1 x

 class C2 x y | x -> y
 instance C2 Int Int

 -- It is this declaration that causes nontermination of typechecking.
 bar :: ()
 bar = m1 (1::Int)
 }}}
 Thus:
 {{{
 simonpj@cam-05-unx:~/tmp$ ~/5builds/HEAD/inplace/bin/ghc-stage1 -c
 T3108.hs -dcore-lint -fforce-recomp
 setEvBind
     Cycle in evidence binds, evvar = $dC1{v aep} [lid]
     {$dC1{v adw} [lid]
        = main:T3108.$fC1x{v r1} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J},
                                                      y{tv aej} [tcs]]
                                                    [$dC2{v aek} [lid],
 $dC1{v ael} [lid]],
      $dC2{v aek} [lid]
        = $dC2{v aeo} [lid] `cast` (main:T3108.C2{tc r7}
                                      <ghc-prim:GHC.Types.Int{(w) tc 3J}>
 (Sym cobox{v aen} [lid])),
      $dC1{v ael} [lid]
        = $dC1{v aep} [lid] `cast` (main:T3108.C1{tc r9}
                                      (Sym cobox{v aen} [lid],
                                       <ghc-prim:GHC.Types.Bool{(w) tc
 3c}>)),
      cobox{v aen} [lid] = CO <ghc-prim:GHC.Types.Int{(w) tc 3J}>,
      $dC2{v aeo} [lid]
        = main:T3108.$fC2IntInt{v r0} [lidx[DFunId]] @[] [],
      $dC1{v aep} [lid]
        = main:T3108.$fC1(,){v r3} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J},
                                                        ghc-
 prim:GHC.Types.Bool{(w) tc 3c}]
                                                      [$dC1{v adw} [lid],
 $dC1{v aeq} [lid]]}
 setEvBind
     Cycle in evidence binds, evvar = $dC0{v aer} [lid]
     {$dC1{v adw} [lid]
        = main:T3108.$fC1x{v r1} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J},
                                                      y{tv aej} [tcs]]
                                                    [$dC2{v aek} [lid],
 $dC1{v ael} [lid]],
      $dC0{v ady} [lid]
        = main:T3108.$fC0x{v r4} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J}]
                                                    [$dC0{v aer} [lid]],
      $dC2{v aek} [lid]
        = $dC2{v aeo} [lid] `cast` (main:T3108.C2{tc r7}
                                      <ghc-prim:GHC.Types.Int{(w) tc 3J}>
 (Sym cobox{v aen} [lid])),
      $dC1{v ael} [lid]
        = $dC1{v aep} [lid] `cast` (main:T3108.C1{tc r9}
                                      (Sym cobox{v aen} [lid],
                                       <ghc-prim:GHC.Types.Bool{(w) tc
 3c}>)),
      cobox{v aen} [lid] = CO <ghc-prim:GHC.Types.Int{(w) tc 3J}>,
      $dC2{v aeo} [lid]
        = main:T3108.$fC2IntInt{v r0} [lidx[DFunId]] @[] [],
      $dC1{v aep} [lid]
        = main:T3108.$fC1(,){v r3} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J},
                                                        ghc-
 prim:GHC.Types.Bool{(w) tc 3c}]
                                                      [$dC1{v adw} [lid],
 $dC1{v aeq} [lid]],
      $dC1{v aeq} [lid]
        = main:T3108.$fC1Bool{v r2} [lidx[DFunId(nt)]] @[] [],
      $dC0{v aer} [lid]
        = main:T3108.$fC0(,){v r6} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J},
                                                        ghc-
 prim:GHC.Types.Bool{(w) tc 3c}]
                                                      [$dC0{v ady} [lid],
 $dC0{v aes} [lid]]}
 simonpj@cam-05-unx:~/tmp$ ~/5builds/HEAD/inplace/bin/ghc-stage1 -c
 T3108.hs -dcore-lint -fforce-recomp
 setEvBind
     Cycle in evidence binds, evvar = $dC1{v aep} [lid]
     {$dC1{v adw} [lid]
        = main:T3108.$fC1x{v r1} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J},
                                                      y{tv aej} [tcs]]
                                                    [$dC2{v aek} [lid],
 $dC1{v ael} [lid]],
      $dC2{v aek} [lid]
        = $dC2{v aeo} [lid] `cast` (main:T3108.C2{tc r7}
                                      <ghc-prim:GHC.Types.Int{(w) tc 3J}>
 (Sym cobox{v aen} [lid])),
      $dC1{v ael} [lid]
        = $dC1{v aep} [lid] `cast` (main:T3108.C1{tc r9}
                                      (Sym cobox{v aen} [lid],
                                       <ghc-prim:GHC.Types.Bool{(w) tc
 3c}>)),
      cobox{v aen} [lid] = CO <ghc-prim:GHC.Types.Int{(w) tc 3J}>,
      $dC2{v aeo} [lid]
        = main:T3108.$fC2IntInt{v r0} [lidx[DFunId]] @[] [],
      $dC1{v aep} [lid]
        = main:T3108.$fC1(,){v r3} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J},
                                                        ghc-
 prim:GHC.Types.Bool{(w) tc 3c}]
                                                      [$dC1{v adw} [lid],
 $dC1{v aeq} [lid]]}
 setEvBind
     Cycle in evidence binds, evvar = $dC0{v aer} [lid]
     {$dC1{v adw} [lid]
        = main:T3108.$fC1x{v r1} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J},
                                                      y{tv aej} [tcs]]
                                                    [$dC2{v aek} [lid],
 $dC1{v ael} [lid]],
      $dC0{v ady} [lid]
        = main:T3108.$fC0x{v r4} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J}]
                                                    [$dC0{v aer} [lid]],
      $dC2{v aek} [lid]
        = $dC2{v aeo} [lid] `cast` (main:T3108.C2{tc r7}
                                      <ghc-prim:GHC.Types.Int{(w) tc 3J}>
 (Sym cobox{v aen} [lid])),
      $dC1{v ael} [lid]
        = $dC1{v aep} [lid] `cast` (main:T3108.C1{tc r9}
                                      (Sym cobox{v aen} [lid],
                                       <ghc-prim:GHC.Types.Bool{(w) tc
 3c}>)),
      cobox{v aen} [lid] = CO <ghc-prim:GHC.Types.Int{(w) tc 3J}>,
      $dC2{v aeo} [lid]
        = main:T3108.$fC2IntInt{v r0} [lidx[DFunId]] @[] [],
      $dC1{v aep} [lid]
        = main:T3108.$fC1(,){v r3} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J},
                                                        ghc-
 prim:GHC.Types.Bool{(w) tc 3c}]
                                                      [$dC1{v adw} [lid],
 $dC1{v aeq} [lid]],
      $dC1{v aeq} [lid]
        = main:T3108.$fC1Bool{v r2} [lidx[DFunId(nt)]] @[] [],
      $dC0{v aer} [lid]
        = main:T3108.$fC0(,){v r6} [lidx[DFunId(nt)]] @[ghc-
 prim:GHC.Types.Int{(w) tc 3J},
                                                        ghc-
 prim:GHC.Types.Bool{(w) tc 3c}]
                                                      [$dC0{v ady} [lid],
 $dC0{v aes} [lid]]}
 }}}

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

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to