Skip to content

Typechecker regression: Inaccessible code in a type expected by the context

The following compiles with GHC 8.0.1 and earlier, but not with GHC HEAD:

{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
module Bug where

class Foo a where
  foo :: (a ~ Int => Int) -> a -> a
  foo _ a2 = a2

instance Foo Char
$ /opt/ghc/head/bin/ghc Bug.hs 
[1 of 1] Compiling Bug              ( Bug.hs, Bug.o )

Bug.hs:9:10: error:
    • Couldn't match type ‘Char’ with ‘Int’
      Inaccessible code in
        a type expected by the context:
          Char ~ Int => Int
    • In the expression: Bug.$dmfoo @Char
      In an equation for ‘foo’: foo = Bug.$dmfoo @Char
      In the instance declaration for ‘Foo Char’

This causes lens-4.14 to fail to build with GHC HEAD.

The reason HEAD fails to compile lens, but GHC 8.0.1 works, is because the fix for #12220 (closed) is in HEAD, but not in 8.0.1.

Edited by Simon Peyton Jones
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information