[GHC] #13193: Integer (gmp) performance regression?

GHC ghc-devs at haskell.org
Fri Jan 27 23:17:31 UTC 2017


#13193: Integer (gmp) performance regression?
-------------------------------------+-------------------------------------
        Reporter:  j.waldmann        |                Owner:
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.0.1
      Resolution:                    |             Keywords:  newcomer
Operating System:  Linux             |         Architecture:  x86_64
 Type of failure:  Runtime           |  (amd64)
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by simonpj):

 Thanks for working on this.  If you think that HEAD is compiling code that
 is sub-optimal, can you boil it out to an example?   But if it is just
 that the original Haskell forces GHC to generate bad code, then yes let's
 just improve the implementation of `minusInteger`.

 I couldn't quite figure out which is the case from the notes above.

 I did try to compile the code from comment:6.  For the record, here's what
 I compiled; and it seemed to give good code (no allocation)
 {{{
 {-# LANGUAGE MagicHash, UnboxedTuples #-}

 module Foo where
 import Prelude ()
 import GHC.Classes
 import GHC.Magic
 import GHC.Prim
 import GHC.Types
 #if WORD_SIZE_IN_BITS < 64
 import GHC.IntWord64
 #endif

 #define INT_MINBOUND -300
 #define ABS_INT_MINBOUND 300

 wordToBigNat :: Word# -> BigNat
 wordToBigNat x = 7

 wordToBigNat2 :: Word# -> Word# -> BigNat
 wordToBigNat2 _ lw# = 3

 data Integer  = S#                !Int#
                 -- ^ iff value in @[minBound::'Int', maxBound::'Int']@
 range
               | Jp# {-# UNPACK #-} !BigNat
                 -- ^ iff value in @]maxBound::'Int', +inf[@ range
               | Jn# {-# UNPACK #-} !BigNat
                 -- ^ iff value in @]-inf, minBound::'Int'[@ range
 type BigNat = Int

 -- | Subtract one 'Integer' from another.
 minusInteger :: Integer -> Integer -> Integer
 minusInteger x       (S# 0#)            = x
 minusInteger (S# 0#) (S# INT_MINBOUND#) = Jp# (wordToBigNat
 ABS_INT_MINBOUND##)
 minusInteger (S# 0#) (S# y#)            = S# (negateInt# y#)
 minusInteger (S# x#) (S# y#)
   = case subIntC# x# y# of
     (# z#, 0# #) -> S# z#
     (# 0#, _  #) -> Jn# (wordToBigNat2 1## 0##)
     (# z#, _  #)
       | isTrue# (z# ># 0#) -> Jn# (wordToBigNat ( (int2Word# (negateInt#
 z#))))
       | True               -> Jp# (wordToBigNat ( (int2Word# z#)))
 -- more cases, that aren't (S# _) (S# _)
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13193#comment:9>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list