missing "incomplete-patterns" warning for TH-generated functions
"incomplete-patterns" warnings are generated for TH-generated case expressions, but not for TH-generated functions, so the behaviour is inconsistent.
For example:
{-# LANGUAGE TemplateHaskell #-}
module Lib where
import Language.Haskell.TH
qIncompleteCase :: Q [Dec]
qIncompleteCase = [d|
incompleteCase :: Bool -> ()
incompleteCase b = case b of
True -> () |]
qIncompleteFunction :: Q [Dec]
qIncompleteFunction =[d|
incompleteFunction :: Bool -> ()
incompleteFunction True = () |]
{-# LANGUAGE TemplateHaskell #-}
module Bug where
import Lib
$qIncompleteCase
$qIncompleteFunction
incompleteCase' :: Bool -> ()
incompleteCase' b = case b of
True -> ()
incompleteFunction' :: Bool -> ()
incompleteFunction' True = ()
When compiling the above two files with -Wall
, GHC 8.2.2 produces an "incomplete-patterns" warning for qIncompleteCase
, incompleteCase'
, and incompleteFunction'
, but not for qIncompleteFunction
. I would prefer to get a warning for qIncompleteFunction
as well.
My use case is the surjective package, in which I intentionally generate code which produces warnings in order to warn the user about corresponding issues in their code. I could generate better error messages if GHC generated warnings for TH-generated functions as well.
Trac metadata
Trac field | Value |
---|---|
Version | 8.2.2 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Template Haskell |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |