
#13350: COMPLETE sets aren't read from external packages -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.1 Keywords: | Operating System: Unknown/Multiple PatternSynonyms | Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- If you define these two modules: {{{#!hs {-# LANGUAGE PatternSynonyms #-} module Foo where data KindRep = KindRepTyConApp | KindRepVar | KindRepApp | KindRepFun | KindRepTYPE | KindRepTypeLitS | KindRepTypeLitD pattern KindRepTypeLit :: KindRep pattern KindRepTypeLit = KindRepTypeLitD {-# COMPLETE KindRepTyConApp, KindRepVar, KindRepApp, KindRepFun, KindRepTYPE, KindRepTypeLit #-} }}} {{{#!hs module Bar where import Foo krInt :: KindRep -> Int krInt KindRepTyConApp{} = 0 krInt KindRepVar{} = 1 krInt KindRepApp{} = 2 krInt KindRepFun{} = 3 krInt KindRepTYPE{} = 4 krInt KindRepTypeLit{} = 5 }}} And you compile `Bar.hs` with `-Wall` on, it will not emit any pattern- match exhaustiveness warnings, as expected. However, something different happens if you import all of these `KindRep` conlikes from `Type.Reflection.Unsafe` instead: {{{#!hs module Bar where import Type.Reflection.Unsafe krInt :: KindRep -> Int krInt KindRepTyConApp{} = 0 krInt KindRepVar{} = 1 krInt KindRepApp{} = 2 krInt KindRepFun{} = 3 krInt KindRepTYPE{} = 4 krInt KindRepTypeLit{} = 5 }}} {{{ $ ~/Software/ghc2/inplace/bin/ghc-stage2 --interactive -Wall Bar.hs GHCi, version 8.1.20170228: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bar ( Bar.hs, interpreted ) Bar.hs:6:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘krInt’: Patterns not matched: (KindRepTypeLitS _ _) (KindRepTypeLitD _ _) | 6 | krInt KindRepTyConApp{} = 0 | ^^^^^^^^^^^^^^^^^^^^^^^^^^^... }}} When the `COMPLETE` set is defined in a module in an //external package// (`base:Type.Reflection.Unsafe`, in this example), GHC doesn't properly take it into account when emitting pattern-match exhaustiveness warnings! This makes `COMPLETE` sets not terribly useful in practice at the moment. (NB: `Type.Reflection.Unsafe`'s definitions of `KindRepTyConApp` //et al.// aren't quite the same as what I defined above, but their exact definitions aren't important here, just that they have the same names and `COMPLETE` set. And this is the only `COMPLETE` set that I could defined in the boot libraries at the moment, making it convenient to use.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13350 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler