#4398: Panic with FlexibleContexts and rewrite rules
---------------------------------+------------------------------------------
    Reporter:  batterseapower    |       Owner:                    
        Type:  bug               |      Status:  new               
    Priority:  normal            |   Component:  Compiler          
     Version:  6.12.1            |    Keywords:                    
    Testcase:                    |   Blockedby:                    
          Os:  Unknown/Multiple  |    Blocking:                    
Architecture:  Unknown/Multiple  |     Failure:  Compile-time crash
---------------------------------+------------------------------------------
 I wanted a rewrite rule that fired if one of the type variables was an
 instance of Ord. To make that work, I tried something like this:

 {{{
 {-# LANGUAGE FlexibleContexts #-}

 {-# RULES "suspicious" forall (x :: a) y. f (x :: Ord a => a) y = g x y
 #-}

 {-# NOINLINE f #-}
 f :: a -> a -> Bool
 f x y = True

 g :: Ord a => a -> a -> Bool
 g = (<)

 main = print $ f 2 1
 }}}

 Which generates a rewrite rule like this:

 {{{
 "suspicious" ALWAYS
     forall {@ a $dOrd :: Ord a x :: a y :: a}
       f @ a x y
       = g @ a $dOrd x y
 }}}

 Naturally, $dOrd isn't present on the left hand side so we get a panic.

 Is there any way to write this kind of rule without inducing a panic? I
 suspect that there isn't, but would like to be proven wrong.. sometimes
 you can optimise better if you can e.g. see that a type is Orderable.

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