[GHC] #16258: PowerPC Big-Endian: ArithInt16, ArithInt8, ArithWord16, and ArithWord8 fail

#16258: PowerPC Big-Endian: ArithInt16, ArithInt8, ArithWord16, and ArithWord8 fail -------------------------------------+------------------------------------- Reporter: trommler | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 8.7 Keywords: Big-endian | Operating System: Unknown/Multiple Architecture: powerpc64 | Type of failure: Incorrect result Test Case: | at runtime primops/should_run/ArithInt16, | Blocked By: primops/should_run/ArithWord16, | primops/should_run/ArithWord8, | primops/should_run/ArithInt8 | Blocking: | Related Tickets: #16222 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The tests were run on a PowerMac G5 running Linux, PowerMacs are big- endian. I reduced the issue to this program where I get the incorrect answer `25132`: {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} module Main where import GHC.Exts main :: IO () main = do putStrLn $ show (apply2 plusInt16# (50) (50)) apply2 :: (Int16# -> Int16# -> Int16#) -> Int -> Int -> Int apply2 op (I# a) (I# b) = let (# sa, sb #) = (# narrowInt16# a, narrowInt16# b #) r = op sa sb in I# (extendInt16# r) {-# NOINLINE apply2 #-} }}} Curiously, when I inline `plusInt16#` and remove the op parameter the result is correct. The test passes on little-endian PowerPC 64-bit. Note: This is bug is different form #16222 that deals with the C calling convention. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16258 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16258: PowerPC Big-Endian: ArithInt16, ArithInt8, ArithWord16, and ArithWord8 fail -------------------------------------+------------------------------------- Reporter: trommler | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 8.7 Resolution: | Keywords: Big-endian Operating System: Unknown/Multiple | Architecture: powerpc64 Type of failure: Incorrect result | Test Case: at runtime | primops/should_run/ArithInt16, | primops/should_run/ArithWord16, | primops/should_run/ArithWord8, | primops/should_run/ArithInt8 Blocked By: | Blocking: Related Tickets: #16222 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by trommler): * owner: (none) => trommler Comment: I am going to look into this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16258#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16258: PowerPC Big-Endian: ArithInt16, ArithInt8, ArithWord16, and ArithWord8 fail -------------------------------------+------------------------------------- Reporter: trommler | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 8.7 Resolution: | Keywords: Big-endian Operating System: Unknown/Multiple | Architecture: powerpc64 Type of failure: Incorrect result | Test Case: at runtime | primops/should_run/ArithInt16, | primops/should_run/ArithWord16, | primops/should_run/ArithWord8, | primops/should_run/ArithInt8 Blocked By: | Blocking: Related Tickets: #16222 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by trommler: Old description:
The tests were run on a PowerMac G5 running Linux, PowerMacs are big- endian.
I reduced the issue to this program where I get the incorrect answer `25132`: {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-}
module Main where
import GHC.Exts
main :: IO () main = do putStrLn $ show (apply2 plusInt16# (50) (50))
apply2 :: (Int16# -> Int16# -> Int16#) -> Int -> Int -> Int apply2 op (I# a) (I# b) = let (# sa, sb #) = (# narrowInt16# a, narrowInt16# b #) r = op sa sb in I# (extendInt16# r) {-# NOINLINE apply2 #-} }}}
Curiously, when I inline `plusInt16#` and remove the op parameter the result is correct.
The test passes on little-endian PowerPC 64-bit.
Note: This is bug is different form #16222 that deals with the C calling convention.
New description: The tests were run on a PowerMac G5 running Linux, PowerMacs are big- endian. I reduced the issue to this program where I get the incorrect answer `25132`: {{{#!hs {-# LANGUAGE BangPatterns #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} module Main where import GHC.Exts main :: IO () main = do putStrLn $ show (apply2 plusInt16# (50) (50)) apply2 :: (Int16# -> Int16# -> Int16#) -> Int -> Int -> Int apply2 op (I# a) (I# b) = let (# sa, sb #) = (# narrowInt16# a, narrowInt16# b #) r = op sa sb in I# (extendInt16# r) {-# NOINLINE apply2 #-} }}} Curiously, when I inline `plusInt16#` and remove the op parameter the result is correct. The test passes on little-endian PowerPC 64-bit. Note: This bug is different from #16222, which deals with the C calling convention. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16258#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16258: PowerPC Big-Endian: ArithInt16, ArithInt8, ArithWord16, and ArithWord8 fail -------------------------------------+------------------------------------- Reporter: trommler | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 8.7 Resolution: | Keywords: Big-endian Operating System: Unknown/Multiple | Architecture: powerpc64 Type of failure: Incorrect result | Test Case: at runtime | primops/should_run/ArithInt16, | primops/should_run/ArithWord16, | primops/should_run/ArithWord8, | primops/should_run/ArithInt8 Blocked By: | Blocking: Related Tickets: #16222 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by trommler): In Cmm I find the following 16 bit store to the stack: {{{ R1 = _s1MY::P64; // CmmAssign I64[Sp] = stg_ap_n_info; // CmmStore I16[Sp + 8] = _s1N6::I16; // CmmStore call stg_ap_n_fast(R2, R1) args: 24, res: 8, upd: 8; // CmmCall }}} This is most likely wrong, it should probably be a 64 bit store. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16258#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16258: PowerPC Big-Endian: ArithInt16, ArithInt8, ArithWord16, and ArithWord8 fail -------------------------------------+------------------------------------- Reporter: trommler | Owner: trommler Type: bug | Status: new Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 8.7 Resolution: | Keywords: Big-endian Operating System: Unknown/Multiple | Architecture: powerpc64 Type of failure: Incorrect result | Test Case: at runtime | primops/should_run/ArithInt16, | primops/should_run/ArithWord16, | primops/should_run/ArithWord8, | primops/should_run/ArithInt8 Blocked By: | Blocking: Related Tickets: #16222 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by trommler): I found the issue, patch is coming. Small integer values passed on the stack are not promoted to word size (stack slot size). We can get away with that on little endian systems where the small integer ends up in the Right (TM) place for a word size read. On big endian the small integer is written into the most significant bits of a word and the least significant bits contain random values. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16258#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16258: PowerPC Big-Endian: ArithInt16, ArithInt8, ArithWord16, and ArithWord8 fail -------------------------------------+------------------------------------- Reporter: trommler | Owner: trommler Type: bug | Status: patch Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 8.7 Resolution: | Keywords: Big-endian Operating System: Unknown/Multiple | Architecture: powerpc64 Type of failure: Incorrect result | Test Case: at runtime | primops/should_run/ArithInt16, | primops/should_run/ArithWord16, | primops/should_run/ArithWord8, | primops/should_run/ArithInt8 Blocked By: | Blocking: Related Tickets: #16222 | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/286 -------------------------------------+------------------------------------- Changes (by trommler): * status: new => patch * differential: => https://gitlab.haskell.org/ghc/ghc/merge_requests/286 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16258#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16258: PowerPC Big-Endian: ArithInt16, ArithInt8, ArithWord16, and ArithWord8 fail -------------------------------------+------------------------------------- Reporter: trommler | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: 8.10.1 Component: Compiler | Version: 8.7 Resolution: | Keywords: Big-endian Operating System: Unknown/Multiple | Architecture: powerpc64 Type of failure: Incorrect result | Test Case: at runtime | primops/should_run/ArithInt16, | primops/should_run/ArithWord16, | primops/should_run/ArithWord8, | primops/should_run/ArithInt8 Blocked By: | Blocking: Related Tickets: #16222 | Differential Rev(s): Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/286 -------------------------------------+------------------------------------- Changes (by trommler): * owner: trommler => (none) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/16258#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#16258: PowerPC Big-Endian: ArithInt16, ArithInt8, ArithWord16, and ArithWord8 fail
-------------------------------------+-------------------------------------
Reporter: trommler | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone: 8.10.1
Component: Compiler | Version: 8.7
Resolution: | Keywords: Big-endian
Operating System: Unknown/Multiple | Architecture: powerpc64
Type of failure: Incorrect result | Test Case:
at runtime | primops/should_run/ArithInt16,
| primops/should_run/ArithWord16,
| primops/should_run/ArithWord8,
| primops/should_run/ArithInt8
Blocked By: | Blocking:
Related Tickets: #16222 | Differential Rev(s):
Wiki Page: | https://gitlab.haskell.org/ghc/ghc/merge_requests/286
-------------------------------------+-------------------------------------
Comment (by Marge Bot
participants (1)
-
GHC