[GHC] #16258: PowerPC Big-Endian: ArithInt16, ArithInt8, ArithWord16, and ArithWord8 fail
GHC
ghc-devs at haskell.org
Thu Jan 31 06:20:27 UTC 2019
#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
More information about the ghc-tickets
mailing list