Out-of-range literal warnings interact poorly with rebindable syntax
Summary
The fancy logic in -Woverflowed-literals
can be triggered improperly under RebindableSyntax
.
Steps to reproduce
{-# LANGUAGE RebindableSyntax #-}
module Silly where
import Prelude hiding (negate)
negate :: Word -> Word
negate x = x + 1
foo :: Word
foo = -40
dfeuer@squirrel:~/src> ghc -fforce-recomp -Wall Silly
[1 of 1] Compiling Silly ( Silly.hs, Silly.o )Silly.hs:9:8: warning: [GHC-97441] [-Woverflowed-literals]
Literal -40 is out of the Word range 0..18446744073709551615
|
9 | foo = -40
| ^^
Expected behavior
I expect the module to compile with no warnings.
Discussion
As I understand it, there are three functions potentially involved in literal out of range warnings: fromInteger
, fromRational
, and negate
. I believe that in a module using RebindableSyntax
we want to modify the warning mechanism under the following circumstances.
- If the literal is non-negative, or if
NegativeLiterals
is enabled, then we should not get a warning for an integer literal iffromInteger
is rebound, and we should not get a warning for a rational literal iffromRational
is rebound. - If the literal is negative,
NegativeLiterals
is disabled, andnegate
is rebound, then we should act exactly as though the user had writtennegate lit
. That is, the range check should be performed onlit
(unless the relevantfromInteger
orfromRational
is rebound), rather than on-lit
. That can potentially produce warnings we do not currently produce. For example, ifnegate
is rebound butfromInteger
is not,-128 :: Int8
should produce a warning, because128
is out of range forInt8
.
Environment
- GHC version used: 9.8.2
Optional:
- Operating System:
- System Architecture: