[GHC] #16234: Unable to resolve type families

GHC ghc-devs at haskell.org
Fri Jan 25 02:47:28 UTC 2019


#16234: Unable to resolve type families
-------------------------------------+-------------------------------------
           Reporter:  crockeea       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.6.3
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  GHC rejects
  Unknown/Multiple                   |  valid program
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #16211
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 The following code

 {{{
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE TypeFamilies     #-}

 import Control.Monad.Classes (MonadReader)
 --import Control.Monad.Primitive ()
 import Control.Monad.Trans.State.Lazy (StateT)

 main :: (n ~ StateT () IO, MonadReader () n) => IO ()
 main = undefined
 }}}

 produces the error (cleaned up for readability)

 {{{
 Main.hs:9:1: error:
     * No instance for
         (monad-classes.MonadReaderN
            (monad-classes.FindTrue
               '[monad-classes.CanDo
                   (StateT () IO)
                   (monad-classes.EffReader ()),
                 monad-classes.CanDo
                   IO
                   (monad-classes.EffReader ())])
             ()
             (StateT () IO))
         arising from a use of `main'
     * In the expression: main
       When checking the type of the IO action `main'
   |
 9 | main = undefined
   | ^
 }}}

 This is the same error as #16211, but that ticket uses a slightly
 different example to trigger the error upon recompile.

 The relevant instances are all available in `monad-classes`.

 {{{
 class Monad m => MonadReaderN (n :: Peano) r m
 instance Monad m => MonadReaderN Zero r (StateT r m)

 type family CanDo (m :: (* -> *)) (eff :: k) :: Bool
 type instance CanDo (StateT s m) eff = StateCanDo s eff

 type family StateCanDo s eff where
   StateCanDo s (EffState s) = True
   StateCanDo s (EffReader s) = True

 type family FindTrue (bs :: [Bool]) :: Peano where
   FindTrue (True ': t) = Zero
   FindTrue (False ': t) = Succ (FindTrue t)

 data EffReader (e :: *)
 }}}

 I can reproduce with the attached package using GHC-8.6.3 and cabal:

 {{{
 $ cabal sandbox init
 $ cabal install --only-dependencies
 $ cabal build
 }}}

 I was unable to minimize the attached example any further. Here's two ways
 to make the error go away:

 1. `import Control.Monad.Primitive ()`. It's unclear why this would help
 because according to the maintainer of monad-classes, it has no transitive
 dependencies on `primitive`.
 2. Change the signature of `main` to `main :: (MonadReader () (StateT ()
 IO) => IO ()`

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


More information about the ghc-tickets mailing list