[GHC] #15502: -ddump-splices truncates Integer literals to Int literals
GHC
ghc-devs at haskell.org
Fri Aug 10 19:25:33 UTC 2018
#15502: -ddump-splices truncates Integer literals to Int literals
-------------------------------------+-------------------------------------
Reporter: ChaiTRex | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
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 ==
{{{#!hs
{-# 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) )
)
}}}
== Output of `runghc` ==
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)
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15502>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list