[GHC] #16122: `round :: Double -> Int64` much slower than `fromIntegral @Int @Int64 . round`
GHC
ghc-devs at haskell.org
Mon Jan 7 07:27:32 UTC 2019
#16122: `round :: Double -> Int64` much slower than `fromIntegral @Int @Int64 .
round`
-------------------------------------+-------------------------------------
Reporter: Fuuzetsu | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.6.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by akio):
Replying to [comment:4 simonpj]:
> * Rules are applied to the RHS of other rules, if the phases allow; this
seems reasonable. After all, that's what will happen whenever the rule is
applied.
Hmm, this doesn't appear to be true in general. It looks like user-defined
rules are never applied to the RHS of other rules. Only built-in rules
are. I checked this by compiling the following module:
{{{#!hs
module Foo where
import qualified GHC.List as List
foo, bar:: Int
foo = 0
bar = 0
baz :: [Int]
baz = []
{-# RULES "foo" foo = 1 #-}
{-# RULES "bar/foo" bar = foo #-} -- the "foo" rule doesn't fire
{-# RULES "baz" baz = List.concat [] #-} -- the "concat" rule from
GHC.List doesn't fire
}}}
Here is what I think is the relevant code
https://gitlab.haskell.org/ghc/ghc/blob/9ea8dcea3e5ba96808ef91028e0efde9d31f7272/compiler/simplCore/Simplify.hs#L3558.
The rule RHS is simplified under `rule_env`, which has the `sm_rules`
field set to `False`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16122#comment:6>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list