[GHC] #15927: Weird interaction between fundeps and overlappable instances

GHC ghc-devs at haskell.org
Wed Nov 21 10:30:34 UTC 2018


#15927: Weird interaction between fundeps and overlappable instances
-------------------------------------+-------------------------------------
           Reporter:  Darwin226      |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.6.3
          Component:  Compiler       |           Version:  8.6.2
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC accepts
  Unknown/Multiple                   |  invalid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Consider this code

 {{{#!hs
 class MyState s m | m -> s where
     getMyState :: m s
 instance {-# OVERLAPPABLE #-} (MyState s m, MonadTrans t, Monad m) =>
 MyState s (t m) where
     getMyState = lift getMyState
 instance Monad m => MyState s (StateT s m) where
     getMyState = get

 f :: (MyState Int m, MyState Char m, MonadIO m) => m ()
 f = do
     int <- getMyState
     str <- getMyState
     liftIO $ putStrLn (replicate int str)


 works1 :: (MyState s m, Show s, MonadIO m) => m ()
 works1 = do
     a <- getMyState
     liftIO (print a)

 works2 = runStateT (runStateT f (5 :: Int)) 'a'
 }}}

 It defines a class similar to `MonadState` of mtl. There is a functional
 dependency in place, just like with `MonadState` and we can see that it
 works the same because `works1` compiles where `a` would have an ambiguous
 type otherwise.

 The `f` function "shouldn't" compile because it's using two different
 states at once subverting the functional dependency restriction. It does
 however compile because an explicit type signature is provided with an
 unsolvable constraint.

 Now the really weird part is that `works2` also compiles and produces the
 expected result even though it's using `f`.

 Here's what I think is happening: instance resolution is looking for
 `MyState Int (StateT Char m)` and it finds the `MyState s (StateT s m)`
 instance. Instead of complaining that `Int` doesn't match `Char` (due to
 the fundep), it just rejects the instance and takes the overlappable one
 that does match. In the case where the state is unknown (i.e. both
 instances match), the fundep kicks in. That's why `runStateT works1 True`
 works.

 Is this intended behavior? It seems pretty useful in some situations and
 I've tested this with 8.2 and 8.6 with the same results.

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


More information about the ghc-tickets mailing list