
#12466: Typechecker regression: Inaccessible code in a type expected by the context -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | 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: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): goldfire, are you saying this code should emit a warning? If so, what can be done to fix the code? FWIW, this bug also prevents the [https://github.com/ekmett/constraints/tree/1649e382b8dffe5e2694d0959caeba65e... constraints] library from building with GHC HEAD, although the bug appears in a slightly different form. Here's a stripped-down example that compiles with GHC 8.0.1, but not GHC HEAD: {{{#!hs {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} module ConstraintsBug where import GHC.TypeLits (Nat) import Unsafe.Coerce (unsafeCoerce) data Dict a where Dict :: a => Dict a newtype a :- b = Sub (a => Dict b) axiom :: forall a b. Dict (a ~ b) axiom = unsafeCoerce (Dict :: Dict (a ~ a)) type Divides n m = n ~ Gcd n m type family Gcd :: Nat -> Nat -> Nat where dividesGcd :: forall a b c. (Divides a b, Divides a c) :- Divides a (Gcd b c) dividesGcd = Sub axiom }}} {{{ $ /opt/ghc/head/bin/ghc ConstraintsBug.hs [1 of 1] Compiling ConstraintsBug ( ConstraintsBug.hs, ConstraintsBug.o ) ConstraintsBug.hs:26:14: error: • Couldn't match type ‘a’ with ‘Gcd a b’ ‘a’ is a rigid type variable bound by the type signature for: dividesGcd :: forall (a :: Nat) (b :: Nat) (c :: Nat). (Divides a b, Divides a c) :- Divides a (Gcd b c) at ConstraintsBug.hs:25:1-77 Inaccessible code in a type expected by the context: (Divides a b, Divides a c) => Dict a ~ Gcd a (Gcd b c) • In the first argument of ‘Sub’, namely ‘axiom’ In the expression: Sub axiom In an equation for ‘dividesGcd’: dividesGcd = Sub axiom • Relevant bindings include dividesGcd :: (Divides a b, Divides a c) :- Divides a (Gcd b c) (bound at ConstraintsBug.hs:26:1) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12466#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler