-ddump-splices truncates Integer literals to Int literals
I trusted that the splice results shown by -ddump-splices
were correct. They weren't, which caused me to waste a lot of time debugging my Template Haskell expressions when they were already correct.
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 8.4.3
Example program
{-# OPTIONS_GHC -ddump-splices #-}
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Language.Haskell.TH.Syntax (Lift(lift))
main = print ( $( lift (toInteger (maxBound :: Int) + 1) )
, $( lift (minBound :: Int) )
)
runghc
Output of Note that the output of the program on the bottom line below is correct. The two splice results shown by -ddump-splices
incorrectly match each other:
Example.hs:8:19-56: Splicing expression
lift (toInteger (maxBound :: Int) + 1) ======> -9223372036854775808
Example.hs:9:19-40: Splicing expression
lift (minBound :: Int) ======> (-9223372036854775808)
(9223372036854775808,-9223372036854775808)
Trac metadata
Trac field | Value |
---|---|
Version | 8.4.3 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |