Skip to content
Snippets Groups Projects
Commit 2f6565cf authored by Ben Gamari's avatar Ben Gamari Committed by Marge Bot
Browse files

testsuite: Add testcases for various machop issues

There were found by the test-primops testsuite.
parent 35bbc251
No related branches found
No related tags found
No related merge requests found
Showing with 72 additions and 0 deletions
TOP=../../../..
include $(TOP)/mk/boilerplate.mk
include $(TOP)/mk/test.mk
test(bits64 buffer) {
return (%zx64(%shra(242::bits8, 1)));
}
249
test(bits64 buffer) {
return (%sx64((~(bits32[buffer])) >> (31::bits64)));
}
1
test(bits64 buffer) {
bits64 ret;
ret = %zx64(%quot(%lobits8(0x00e1::bits16), 3::bits8));
// ^^^^^^^^^^^^^^^^^^^^^^
// == -31 signed
// ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
// == -10 signed
// ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
// == 0xf6 unsigned
return (ret);
}
246
test(bits64 buffer) {
return (%zx64(%shrl(bits16[buffer + (128 :: bits64)], (1 :: bits64))) & (64711 :: bits64));
}
16576
{-# LANGUAGE GHCForeignImportPrim #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE MagicHash #-}
-- | This module is the driver for the Cmm machop tests. It expects to be
-- linked with an object file (typically compiled Cmm) exposing a procedure
-- named `test` which'
--
-- - takes a single pointer argument pointing to a buffer containing
-- [0..bufferSz] (truncated to Word8).
--
-- - returns a Word#
--
-- The driver will print the returned result.
module Main where
import GHC.Exts
import GHC.Ptr
import qualified Data.ByteString as BS
import qualified Data.ByteString.Unsafe as BS
foreign import prim "test" test :: Addr# -> Word#
bufferSz :: Int
bufferSz = 1*1024*1024
main :: IO ()
main = do
let buf = BS.pack $ map fromIntegral [0..bufferSz]
BS.unsafeUseAsCString buf $ \(Ptr p) -> do
print $ W# (test p)
setTestOpts(extra_files(['TestMachOp.hs']))
def cmm_test(name):
test(name, normal, multi_compile_and_run,
['TestMachOp', [(name+'.cmm', '')], ''])
cmm_test('T20626a')
cmm_test('T20626b')
cmm_test('T20638')
cmm_test('T20634')
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment