COMPLETE pragma insufficiently documented
Summary
Consider the following program:
data LexemeVW' var white
= LVWVar' var Var
| LVWWhite' white Whitespace
| LLex Lexeme
deriving (Eq, Show)
type LexemeV = LexemeVW' () Void
type LexemeW = LexemeVW' Void ()
type LexemeVW = LexemeVW' () ()
pattern LVar :: Var -> LexemeVW' () white
pattern LVar v <- LVWVar' () v
where
LVar v = LVWVar' () v
pattern LWhite :: Whitespace -> LexemeVW' var ()
pattern LWhite v <- LVWWhite' () v
where
LWhite v = LVWWhite' () v
isV :: LexemeV -> Bool
isV (LVar _) = True
isV (LLex _) = False
The matches on isV
are complete (since the LVWWhite' constructor is prohibited by having a Void argument). I'd like to add a COMPLETE
pragma informing GHC of this, but, this is only complete for LexemeV
, not LexemeW
or LexemeVW
! Presumably this pragma will do the trick:
{-# COMPLETE LVar, LLex :: LexemeVW' () Void #-}
But this is a parse error!
parse error on input ‘(’
|
486 | {-# COMPLETE LVar, LLex :: LexemeVW' () Void #-}
| ^
Steps to reproduce
Small repro:
{-# LANGUAGE PatternSynonyms #-}
import Data.Void
type Var = Int
type Whitespace = Int
type Lexeme = Int
data LexemeVW' var white
= LVWVar' var Var
| LVWWhite' white Whitespace
| LLex Lexeme
deriving (Eq, Show)
pattern LVar :: Var -> LexemeVW' () white
pattern LVar v <- LVWVar' () v
where
LVar v = LVWVar' () v
{-# COMPLETE LVar, LLex :: LexemeVW' () Void #-}
Expected behavior
I expect the COMPLETE
pragma to parse, and to subsequently silence the isV
warning.
Environment
- GHC version used: 8.8.1 and 8.6.5
Optional:
- Operating System:
- System Architecture:
EDIT (by @rae): The problem is in the "I expect", above, because the manual does not lay this out as clearly as it should.
Edited by Richard Eisenberg