[GHC] #9617: Try to replace `quot` and `rem` with `quotRem` when possible

#9617: Try to replace `quot` and `rem` with `quotRem` when possible -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.9 Keywords: | Operating System: Architecture: Unknown/Multiple | Unknown/Multiple Difficulty: Unknown | Type of failure: Blocked By: | None/Unknown Related Tickets: | Test Case: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- If I define {{{#!hs myquot x y = fst (quotRem x y) myrem x y = snd (quotRem x y) bob :: Int -> Int -> Int bob x y = myquot x y + myrem x y }}} Then I get this beautiful thing with GHC 7.9 (I ''don't'' get anything beautiful in 7.8.3, so great work, compiler gurus!): {{{#!hs bob :: Int -> Int -> Int bob = \ (w_sWx :: Int) (w1_sWy :: Int) -> case w_sWx of _ { I# ww1_sWB -> case w1_sWy of _ { I# ww3_sWF -> case ww3_sWF of wild_aSo { __DEFAULT -> case quotRemInt# ww1_sWB wild_aSo of _ { (# ipv_aSr, ipv1_aSs #) -> I# (+# ipv_aSr ipv1_aSs) }; (-1) -> case ww1_sWB of wild1_aSu { __DEFAULT -> case quotRemInt# wild1_aSu (-1) of _ { (# ipv_aSx, ipv1_aSy #) -> I# (+# ipv_aSx ipv1_aSy) }; (-9223372036854775808) -> case overflowError of wild2_00 { } }; 0 -> case divZeroError of wild1_00 { } } } } }}} However, if I write {{{ jones :: Int -> Int -> Int jones x y = quot x y + rem x y }}} I don't get anything nice. What I'm thinking (perhaps out of ignorance) is that we might be able to use the `myquot` and `myrem` definitions if it's possible to get some sort of dead code elimination to recognize when one or the other is not used, at which point it can replace the `quotRemInt#` with `quotInt#` or `remInt#`. Then we can quit the silly `quotRem` dance in user code and just write what we actually mean. Of course, exactly the same thing applies to `divMod`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9617 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9617: Try to replace `quot` and `rem` with `quotRem` when possible -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): I think the dead code elimination is probably pretty simple here. If we see {{{#!hs case quotRemInt# x y of _ { (# q, r #) -> expr } }}} and either `q` or `r` is not free in `expr`, replace that with {{{#!hs case quotInt# x y of _ { q -> expr } }}} or the other way around. I don't know where code to do such a thing would belong, however. It certainly would have to be post-CSE. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9617#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9617: Implement `quot` and `rem` using `quotRem`; implement `div` and `mod` using `divMod` -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): Good news: It seems it may not even be necessary (for `Int`, at least) to find a way to turn the `quotRemInt#` back into `quotInt#` or `remInt#`—the performance difference there appears to be somewhere between tiny and nonexistent. It's not clear to me whether that will be the same for `divMod`, which adds a few more operations over `div` or `mod` (but fast ones). More good news: After bashing my head against it for a few hours, I managed to get `divMod` to do what I wanted. I had to swap the divide by zero test with the arithmetic overflow test. I don't understand ''why'' this made it work, but it seems to have done the job. It looks like this: {{{#!hs divZeroError# :: Void# -> (# Int#, Int# #) divZeroError# a = error "Divide by zero" overflowError# :: Void# -> Int# overflowError# a = error "Arithmetic overflow: attempted to divide minBound by -1" divModInt# :: Int# -> Int# -> (# Int#, Int# #) x# `divModInt#` y# | isTrue# (y# ==# (-1#)) && isTrue# (x# ==# (case minBound of I# mb -> mb)) = (# overflowError# void#, 0# #) | isTrue# (y# ==# 0#) = divZeroError# void# | isTrue# (x# ># 0#) && isTrue# (y# <# 0#) = case (x# -# 1#) `quotRemInt#` y# of (# q, r #) -> (# q -# 1#, r +# y# +# 1# #) | isTrue# (x# <# 0#) && isTrue# (y# ># 0#) = case (x# +# 1#) `quotRemInt#` y# of (# q, r #) -> (# q -# 1#, r +# y# -# 1# #) | otherwise = x# `quotRemInt#` y# divModInt :: Int -> Int -> (Int, Int) (I# x) `divModInt` (I# y) = case x `divModInt#` y of (# q, r #) -> (I# q, I# r) div :: Int -> Int -> Int {-# INLINE div #-} div x y = fst (divModInt x y) infixl 7 `div` mod :: Int -> Int -> Int {-# INLINE mod #-} x `mod` y = snd (divModInt x y) infixl 7 `mod` }}} Using these definitions, it seems things stay sufficiently similar long enough for CSE to do its job, so {{{#!hs divPlusMod :: Int -> Int -> Int divPlusMod x y = div x y + mod x y }}} compiles into something very similar to what you'd get from {{{#!hs divPlusModStandard :: Int -> Int -> Int divPlusModStandard x y = case divMod x y of (q, r) -> q + r }}} but with the proposed definitions, I'm getting quite a bit less code duplication, which seems to be a small but good thing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9617#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9617: Implement `quot` and `rem` using `quotRem`; implement `div` and `mod` using `divMod` -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.9 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): Argh. It looks like I got that wrong. That's only working because it's too big to inline. `divMod` may just be hopeless. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9617#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC