"Inaccessible" vs "redundant" warnings in GADT pattern matching

I’m confused about the behavior of GHC in regards to coverage checking of pattern matches. According to the GHC source code, it’s based on the Lower Your Guards (LYG) paper. That paper, as well as the Note [Determining inaccessible clauses] in the source code, indicate that a pattern match will be reported as “redundant” if removing it will have no effect on the result. But there are cases where a pattern match cannot apply, yet removing it would still alter the result - these are reported as “inaccessible”.

Yet the following code segment reports both “inaccessible” and “redundant” warnings for the same pattern match: on f (GBool _) and f (GGreat _). However, f (GGood _) is only reported as redundant. For reference, I was using GHC 9.6.4.

{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}

import Data.Kind
import GHC.TypeError

data G a where
  GShow :: Show a => a -> G a
  GBool :: Bool -> G Bool
  GGood :: Good a => a -> G a
  GGreat :: Great a ~ True => a -> G a

type family Good a :: Constraint where
  Good Bool = ()
  Good Int = TypeError (Text "Int is not good")
  Good _ = TypeError (Text "That is not good")

type family Great a :: Bool where
  Great Bool = True
  Great Int = False
  Great _ = False

f :: G Int -> Char
f (GShow _) = 's'
f (GBool _) = 'b'
f (GGood _) = 'g'
f (GGreat _) = 'r'

g :: G (Int -> Int) -> Char
g (GShow _) = 's'
gadt_type_error_2.hs:27:1: warning: [GHC-53633] [-Woverlapping-patterns]
    Pattern match is redundant
    In an equation for ‘f’: f (GBool _) = ...
   |
27 | f (GBool _) = 'b'
   | ^^^^^^^^^^^^^^^^^

gadt_type_error_2.hs:27:4: warning: [GHC-40564] [-Winaccessible-code]
    • Inaccessible code in
        a pattern with constructor: GBool :: Bool -> G Bool,
        in an equation for ‘f’
      Couldn't match type ‘Int’ with ‘Bool’
    • In the pattern: GBool _
      In an equation for ‘f’: f (GBool _) = 'b'
   |
27 | f (GBool _) = 'b'
   |    ^^^^^^^

gadt_type_error_2.hs:28:1: warning: [GHC-53633] [-Woverlapping-patterns]
    Pattern match is redundant
    In an equation for ‘f’: f (GGood _) = ...
   |
28 | f (GGood _) = 'g'
   | ^^^^^^^^^^^^^^^^^

gadt_type_error_2.hs:29:1: warning: [GHC-53633] [-Woverlapping-patterns]
    Pattern match is redundant
    In an equation for ‘f’: f (GGreat _) = ...
   |
29 | f (GGreat _) = 'r'
   | ^^^^^^^^^^^^^^^^^^

gadt_type_error_2.hs:29:4: warning: [GHC-40564] [-Winaccessible-code]
    • Inaccessible code in
        a pattern with constructor:
          GGreat :: forall a. (Great a ~ True) => a -> G a,
        in an equation for ‘f’
      Couldn't match type ‘False’ with ‘True’
    • In the pattern: GGreat _
      In an equation for ‘f’: f (GGreat _) = 'r'
   |
29 | f (GGreat _) = 'r'
   |    ^^^^^^^^

It’s fantastic that LYG can figure out that those GRHSs (guarded right-hand sides) can’t be reached. It’s also great that, if I leave out constructors that can be matched, it lists those as missing from the cases.

The example of g (GShow _) is to show that LYG can’t figure out that the type class-constrained constructor can’t be matched. That makes to me since type classes are open - some other module could yet provide an instance for Int -> Int. I would imagine the same issue holds with open type families.

I wish that the f cases with GBool, GGood and GGreat would all report type errors instead of just coverage warnings, since technically they don’t match the type of the scrutinee. Is type checking for GADT pattern matches just handled a bit more loosely?

I wonder why GGood doesn’t get an “inaccessible” warning, but GGreat does. And it’s a shame we can’t have the custom type error for GGood show up. Instead, for GGreat we get an “inaccessible” warning, but it talks about True not matching False, which is not as helpful. (I suppose I could make a custom type instead of using Bool, that would have some more descriptive name, like GoodNotAllowed.)

Wow, that is some extensive type hackery. Do note that -Winaccessible-code warnings do not come from the pattern-match checker but from the type checker; for patterns, they are often redundant with what the pattern-match checker reports.

In this case, the Pmc correctly and precisely reports that all three clauses of f but the first are redundant. As you have stated correctly, it is not possible for the single clause of g to be reported as inaccessible because of the open world assumption of type classes.

I have no idea when or how -Winaccessible-code warnings are generated, so I can’t tell why there is no such warning for f GGood{}. Perhaps it has to do with the TypeError machinery. I tried the more recent (9.8) Unsatisfiable, but that did not have an effect either.

1 Like

Thanks for your perspective, Sebastian. And I take the “extensive type hackery” comment as a high compliment!

I had suspected that the -Winaccessible-code warnings weren’t coming from the PMC. It’s a bit confusing though that the PMC can also report its own “inaccessible code” warnings, and that term has a slightly different meaning there.

I agree the PMC is behaving correctly and it’s doing a fantastic job! Good idea to try Unsatisfiable - I wasn’t aware of that.

Maybe Adam Gundry has more of an idea about how the inaccessible-code warnings are generated. I’ll ask about this in the GHC channel on Element.

Summoning me here is likely to be more successful than Element. :slight_smile:

These used to be reported as errors, but were changed to warnings, I think because there is nothing fundamentally preventing compilation of the program in the presence of dead code, and there are some use cases (e.g. program generation) where it is more convenient not to reject the program entirely:

I believe the inaccessible warning is currently emitted only when there is an enclosing GADT pattern match that binds an equality constraint, as discussed here:

Though perhaps in the light of the subsequent changes to the pattern match checker, and TypeError/Unsatisfiable constraints now being treated as insoluble, all this could do with being revisited.

1 Like

Thanks for the detailed response, @adamgundry! I think you are spot on. I would have responded sooner, but it took me a while to read through the linked issues to really understand the decisions.

I’m fine with the “Inaccessible” message being just a warning.

I’m not quite sure in Issue #12466 why it should only apply when binding an equality constraint. It would be nice if the custom type errors could be shown as a custom “inaccessible” warning. Then a library writer can use the custom errors to aid users of the library in understanding what they did wrong, without having to understand the mechanical details of how the library works. Messages more useful than “Couldn’t match False with True”, which leaks implementation details.

I want to point out that OCaml generates an error on a GADT pattern match if the type doesn’t match:

type _ foo =
  | FooI : int -> int foo
  | FooB : bool -> bool foo

let doubleFoo : int foo -> int foo = function
  | FooI n -> FooI (n * 2)
  | FooB b -> FooI 5

Line 7, characters 4-10:
Error: This pattern matches values of type bool foo
       but a pattern was expected which matches values of type int foo
       Type bool is not compatible with type int