[GHC] #16036: expDouble## 0.0## doesn't get complied into 1.0##
GHC
ghc-devs at haskell.org
Wed Dec 12 02:30:06 UTC 2018
#16036: expDouble## 0.0## doesn't get complied into 1.0##
-------------------------------------+-------------------------------------
Reporter: Fuuzetsu | Owner: (none)
Type: feature | Status: new
request |
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.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:
-------------------------------------+-------------------------------------
{{{
[nix-shell:/tmp]$ cat T.hs
{-# LANGUAGE MagicHash #-}
{-# OPTIONS_GHC -O2 -ddump-simpl -ddump-to-file #-}
module T (f) where
import GHC.Float
import GHC.Prim
f :: Double
f = D# (expDouble# 0.0## -## 1.0##)
[nix-shell:/tmp]$ ghc -fforce-recomp T.hs
[1 of 1] Compiling T ( T.hs, T.o )
[nix-shell:/tmp]$ cat T.dump-simpl
==================== Tidy Core ====================
2018-12-12 02:23:40.288094743 UTC
Result size of Tidy Core
= {terms: 20, types: 6, coercions: 0, joins: 0/0}
-- RHS size: {terms: 5, types: 0, coercions: 0, joins: 0/0}
f :: Double
[GblId,
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 15 20}]
f = GHC.Types.D# (-## (expDouble# 0.0##) 1.0##)
…
}}}
This was spotted in real code where we had GHC generate something like
{{{#!haskell
1# ->
jump $j9_s1IVU
(GHC.Prim.+##
sc3_s2pVI
(GHC.Prim.-##
(GHC.Prim.expDouble#
0.0##)
1.0##))
}}}
I would expect this (I think reasonably) to be just `{{{jump $j9_s1IVU
sc3_s2pVI}}}`.
Maybe {{{expDouble## <literal>##}}} should always evaluate at compile time
to not block further constant folding?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16036>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list