[GHC] #15460: Literals overflow
GHC
ghc-devs at haskell.org
Tue Jul 31 11:37:13 UTC 2018
#15460: Literals overflow
-------------------------------------+-------------------------------------
Reporter: hsyl20 | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Incorrect result | Unknown/Multiple
at runtime | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by hsyl20:
Old description:
> Consider the following example:
>
> {{{#!hs
> {-# LANGUAGE MagicHash #-}
> import GHC.Int
>
> main :: IO ()
> main = do
> let x = I#
> (0xfffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff#)
> print x
> }}}
>
> It gets desugared into:
> {{{#!hs
> main
> = print
> @ Int
> GHC.Show.$fShowInt
> (GHC.Types.I#
> 7237005577332262213973186563042994240829374041602535252466099000494570602495#)
> }}}
>
> Problem: the literal value isn't rounded and there is no overflow
> warning.
>
> It breaks the invariant that literal values in Core have to be in range.
> Bad things can happen when we break this invariant:
>
> {{{#!hs
> {-# LANGUAGE MagicHash #-}
> import GHC.Int
> import Control.Monad
>
> main :: IO ()
> main = do
> let x = I#
> (0xfffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff#)
> when (x > maxBound) $ do
> print "Oups"
>
> > ghc TestLitOverflow.hs -Wall -O2
> > ./TestLitOverflow
> "Oups"
> }}}
New description:
Consider the following example:
{{{#!hs
{-# LANGUAGE MagicHash #-}
import GHC.Int
main :: IO ()
main = do
let x = I#
(0xfffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff#)
print x
}}}
It gets desugared into:
{{{#!hs
main
= print
@ Int
GHC.Show.$fShowInt
(GHC.Types.I#
7237005577332262213973186563042994240829374041602535252466099000494570602495#)
}}}
Problem: the literal value isn't rounded and there is no overflow warning.
It breaks the invariant that literal values in Core have to be in range.
Bad things can happen when we break this invariant:
{{{#!hs
{-# LANGUAGE MagicHash #-}
import GHC.Int
main :: IO ()
main = do
let x = I#
(0xfffffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff#)
if (x > maxBound)
then print "Oups"
else print "Ok"
> ghc TestLitOverflow.hs -Wall -O0
> ./TestLitOverflow
"Ok"
> ghc TestLitOverflow.hs -Wall -O2
> ./TestLitOverflow
"Oups"
}}}
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15460#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list