recursion-ninja pushed to branch wip/fix-25664 at Glasgow Haskell Compiler / GHC

Commits:

4 changed files:

Changes:

  • compiler/GHC/Cmm/Opt.hs
    ... ... @@ -395,26 +395,39 @@ cmmMachOpFoldM platform mop [x, (CmmLit (CmmInt 1 rep))]
    395 395
         one  = CmmLit (CmmInt 1 (wordWidth platform))
    
    396 396
     
    
    397 397
     -- Now look for multiplication/division by powers of 2 (integers).
    
    398
    -
    
    399
    -cmmMachOpFoldM platform mop [x, (CmmLit (CmmInt n _))]
    
    398
    +--
    
    399
    +-- Naively this is as simple a matter as left/right bit shifts,
    
    400
    +-- but the Cmm representation if integral values quickly complicated the matter.
    
    401
    +--
    
    402
    +-- We must carefully narrow the value to be within the range of values for the
    
    403
    +-- type's logical bit-width. However, Cmm only represents values as *signed*
    
    404
    +-- integers internally yet the logical type may be unsigned. If we are dealing
    
    405
    +-- with a negative integer type at width @_w@, the only negative number that
    
    406
    +-- wraps around to be a positive power of 2 after calling narrowU is -2^(_w - 1)
    
    407
    +-- which wraps round to 2^(_w - 1), and multiplying by -2^(_w - 1) is indeed
    
    408
    +-- the same as a left shift by (w - 1), so this is OK.
    
    409
    +--
    
    410
    +-- ToDo: See #25664 (comment 605821) describing a change to the Cmm literal representation.
    
    411
    +-- When/If this is completed, this code must be refactored to account for the explicit width sizes.
    
    412
    +cmmMachOpFoldM platform mop [x, (CmmLit (CmmInt n _w))]
    
    400 413
       = case mop of
    
    401 414
             MO_Mul rep
    
    402
    -           | Just p <- exactLog2 n ->
    
    415
    +           | Just p <- exactLog2 (narrowU rep n) ->
    
    403 416
                      Just $! (cmmMachOpFold platform (MO_Shl rep) [x, CmmLit (CmmInt p $ wordWidth platform)])
    
    404 417
             MO_U_Quot rep
    
    405
    -           | Just p <- exactLog2 n ->
    
    418
    +           | Just p <- exactLog2 (narrowU rep n) ->
    
    406 419
                      Just $! (cmmMachOpFold platform (MO_U_Shr rep) [x, CmmLit (CmmInt p $ wordWidth platform)])
    
    407 420
             MO_U_Rem rep
    
    408
    -           | Just _ <- exactLog2 n ->
    
    421
    +           | Just _ <- exactLog2 (narrowU rep n)  ->
    
    409 422
                      Just $! (cmmMachOpFold platform (MO_And rep) [x, CmmLit (CmmInt (n - 1) rep)])
    
    410 423
             MO_S_Quot rep
    
    411
    -           | Just p <- exactLog2 n,
    
    424
    +           | Just p <- exactLog2 (narrowS rep n),
    
    412 425
                  CmmReg _ <- x ->   -- We duplicate x in signedQuotRemHelper, hence require
    
    413 426
                                     -- it is a reg.  FIXME: remove this restriction.
    
    414 427
                     Just $! (cmmMachOpFold platform (MO_S_Shr rep)
    
    415 428
                       [signedQuotRemHelper rep p, CmmLit (CmmInt p $ wordWidth platform)])
    
    416 429
             MO_S_Rem rep
    
    417
    -           | Just p <- exactLog2 n,
    
    430
    +           | Just p <- exactLog2 (narrowS rep n),
    
    418 431
                  CmmReg _ <- x ->   -- We duplicate x in signedQuotRemHelper, hence require
    
    419 432
                                     -- it is a reg.  FIXME: remove this restriction.
    
    420 433
                     -- We replace (x `rem` 2^p) by (x - (x `quot` 2^p) * 2^p).
    

  • testsuite/tests/cmm/opt/T25664.hs
    1
    +{-# OPTIONS_GHC -O -fno-full-laziness #-}
    
    2
    +{-# LANGUAGE MagicHash #-}
    
    3
    +
    
    4
    +import GHC.Exts
    
    5
    +import GHC.Int
    
    6
    +
    
    7
    +mb8 :: Int8 -> Int8
    
    8
    +{-# OPAQUE mb8 #-}
    
    9
    +mb8 (I8# i) = I8# (i `quotInt8#` (noinline intToInt8# 128#))
    
    10
    +
    
    11
    +mb16 :: Int16 -> Int16
    
    12
    +{-# OPAQUE mb16 #-}
    
    13
    +mb16 (I16# i) = I16# (i `quotInt16#` (noinline intToInt16# 32768#))
    
    14
    +
    
    15
    +main :: IO ()
    
    16
    +main = print (mb8 minBound) >> print (mb16 minBound)
    
    17
    +

  • testsuite/tests/cmm/opt/T25664.stdout
    1
    +1
    
    2
    +1

  • testsuite/tests/cmm/opt/all.T
    ... ... @@ -12,3 +12,6 @@ test('T25771', [cmm_src, only_ways(['optasm']),
    12 12
                     grep_errmsg(r'(12\.345|0\.6640625)',[1]),
    
    13 13
                     ],
    
    14 14
          compile, ['-ddump-cmm'])
    
    15
    +
    
    16
    +# Cmm should correctly account for word size when performing MUL/DIV/REM by a power of 2 optimization.
    
    17
    +test('T25664', normal, compile_and_run, [''])
    \ No newline at end of file