[GHC] #14322: Simplifying an instance context makes a rewrite rule no longer typecheck

GHC ghc-devs at haskell.org
Wed Oct 4 19:47:44 UTC 2017


#14322: Simplifying an instance context makes a rewrite rule no longer typecheck
-------------------------------------+-------------------------------------
           Reporter:  RyanGlScott    |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
  (Type checker)                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 This code (taken from the `reducers` package) compiles:

 {{{#!hs
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}

 import Prelude (Applicative(..), Functor(..), (.))

 class Semigroup m where
   (<>) :: m -> m -> m

 class Semigroup m => Reducer c m where
   snoc :: m -> c -> m

 newtype Traversal f = Traversal { getTraversal :: f () }

 instance Applicative f => Semigroup (Traversal f) where
   Traversal a <> Traversal b = Traversal (a *> b)

 instance Applicative f => Reducer (f a) (Traversal f) where
   Traversal a `snoc` b = Traversal (() <$ (a *> b))

 snocTraversal :: Reducer (f ()) (Traversal f) => Traversal f -> f () ->
 Traversal f
 snocTraversal a = (<>) a . Traversal
 {-# RULES "snocTraversal" snoc = snocTraversal #-}
 }}}

 But on GHC 8.2.1 and later, it gives this warning:

 {{{
 GHCi, version 8.2.1: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Main             ( Bug.hs, interpreted )

 Bug.hs:21:18: warning: [-Wsimplifiable-class-constraints]
     • The constraint ‘Reducer (f ()) (Traversal f)’
         matches an instance declaration
       instance Applicative f => Reducer (f a) (Traversal f)
         -- Defined at Bug.hs:18:10
       This makes type inference for inner bindings fragile;
         either use MonoLocalBinds, or simplify it using the instance
     • In the type signature:
         snocTraversal :: Reducer (f ()) (Traversal f) =>
                          Traversal f -> f () -> Traversal f
    |
 21 | snocTraversal :: Reducer (f ()) (Traversal f) => Traversal f -> f ()
 -> Traversal f
    |
 ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 }}}

 I decided to follow GHC's orders and reduce the `Reducer (f ()) (Traversal
 f)` context to just `Applicative f`:

 {{{#!hs
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}

 import Prelude (Applicative(..), Functor(..), (.))

 class Semigroup m where
   (<>) :: m -> m -> m

 class Semigroup m => Reducer c m where
   snoc :: m -> c -> m

 newtype Traversal f = Traversal { getTraversal :: f () }

 instance Applicative f => Semigroup (Traversal f) where
   Traversal a <> Traversal b = Traversal (a *> b)

 instance Applicative f => Reducer (f a) (Traversal f) where
   Traversal a `snoc` b = Traversal (() <$ (a *> b))

 snocTraversal :: Applicative f => Traversal f -> f () -> Traversal f
 snocTraversal a = (<>) a . Traversal
 {-# RULES "snocTraversal" snoc = snocTraversal #-}
 }}}

 But after doing so, the file no longer typechecks!

 {{{
 GHCi, version 8.2.1: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Main             ( Bug.hs, interpreted )

 Bug.hs:23:34: error:
     • Could not deduce (Applicative f)
         arising from a use of ‘snocTraversal’
       from the context: Reducer (f ()) (Traversal f)
         bound by the RULE "snocTraversal" at Bug.hs:23:11-46
       Possible fix:
         add (Applicative f) to the context of the RULE "snocTraversal"
     • In the expression: snocTraversal
       When checking the transformation rule "snocTraversal"
    |
 23 | {-# RULES "snocTraversal" snoc = snocTraversal #-}
    |                                  ^^^^^^^^^^^^^
 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14322>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list