Skip to content
Snippets Groups Projects
Commit 7a3cda53 authored by Ryan Scott's avatar Ryan Scott Committed by Krzysztof Gogolewski
Browse files

Fix #15502 by not casting to Int during TH conversion

Summary:
When turning an `IntegerL` to an `IntegralLit` during TH
conversion, we were stupidly casting an `Integer` to an `Int` in
order to determine how it should be pretty-printed. Unsurprisingly,
this causes problems when the `Integer` doesn't lie within the bounds
of an `Int`, as demonstrated in #15502.

The fix is simple: don't cast to an `Int`.

Test Plan: make test TEST=T15502

Reviewers: bgamari, simonpj

Reviewed By: simonpj

Subscribers: simonpj, rwbarton, carter

GHC Trac Issues: #15502

Differential Revision: https://phabricator.haskell.org/D5089
parent 5e6cf2a9
No related branches found
No related tags found
No related merge requests found
......@@ -1436,9 +1436,12 @@ data IntegralLit
deriving (Data, Show)
mkIntegralLit :: Integral a => a -> IntegralLit
mkIntegralLit i = IL { il_text = SourceText (show (fromIntegral i :: Int))
mkIntegralLit i = IL { il_text = SourceText (show i_integer)
, il_neg = i < 0
, il_value = toInteger i }
, il_value = i_integer }
where
i_integer :: Integer
i_integer = toInteger i
negateIntegralLit :: IntegralLit -> IntegralLit
negateIntegralLit (IL text neg value)
......@@ -1463,6 +1466,13 @@ data FractionalLit
mkFractionalLit :: Real a => a -> FractionalLit
mkFractionalLit r = FL { fl_text = SourceText (show (realToFrac r::Double))
-- Converting to a Double here may technically lose
-- precision (see #15502). We could alternatively
-- convert to a Rational for the most accuracy, but
-- it would cause Floats and Doubles to be displayed
-- strangely, so we opt not to do this. (In contrast
-- to mkIntegralLit, where we always convert to an
-- Integer for the highest accuracy.)
, fl_neg = r < 0
, fl_value = toRational r }
......
{-# LANGUAGE TemplateHaskell #-}
module T15502 where
import Language.Haskell.TH.Syntax (Lift(lift))
main = print ( $( lift (toInteger (maxBound :: Int) + 1) )
, $( lift (minBound :: Int) )
)
T15502.hs:7:19-56: Splicing expression
lift (toInteger (maxBound :: Int) + 1) ======> 9223372036854775808
T15502.hs:8:19-40: Splicing expression
lift (minBound :: Int) ======> (-9223372036854775808)
......@@ -426,4 +426,5 @@ test('TH_rebindableAdo', normal, compile, [''])
test('T14627', normal, compile_fail, [''])
test('TH_invalid_add_top_decl', normal, compile_fail, [''])
test('T15550', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('T15502', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('T15518', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment