Skip to content
Snippets Groups Projects
Commit 59ed6ef3 authored by Ben Gamari's avatar Ben Gamari :turtle:
Browse files

Dynamically probe word size

parent e7d5ce0b
No related branches found
No related tags found
1 merge request!10Enable testing of Word64# on 32-bit platforms
......@@ -7,9 +7,16 @@ TEST_GHC="${TEST_GHC:-ghc}"
CABAL="${CABAL:-cabal}"
EMULATOR="${EMULATOR:-}"
if "$TEST_GHC" --info | grep -q '("target word size","8")'; then
echo "Found 64-bit target"
else
echo "Found 32-bit target"
CABAL_ARGS="-ftarget-32-bit"
fi
build_runit() {
ALLOW_NEWER="--allow-newer=base"
"$CABAL" build $ALLOW_NEWER -w "$TEST_GHC" run-it
"$CABAL" build $ALLOW_NEWER -w "$TEST_GHC" $CABAL_ARGS run-it
RUNIT="$("$CABAL" list-bin $ALLOW_NEWER -w "$TEST_GHC" run-it)"
echo "runit is $RUNIT"
}
......@@ -23,7 +30,7 @@ run() {
if [[ -n "$EMULATOR" ]]; then
args+=( "--emulator=$EMULATOR" )
fi
"$CABAL" run -w "$BOOT_GHC" test-primops -- "${args[@]}" "$@"
"$CABAL" run -w "$BOOT_GHC" $CABAL_ARGS test-primops -- "${args[@]}" "$@"
}
repl() {
......
{-# LANGUAGE CPP #-}
-- | Utilities for running GHC and evaluating Cmm via @run-it@.
module RunGhc
( EvalMethod(..)
......@@ -95,8 +97,13 @@ mkStaticWrapper comp width = do
hsType :: Width -> String
hsType W8 = "Word8#"
hsType W16 = "Word16#"
#if defined(WORD_SIZE_32BIT)
hsType W32 = "Word32#"
hsType W64 = "Word64#"
#else
hsType W32 = "Word32#"
hsType W64 = "Word#"
#endif
toHsWord :: Width -> String -> String
toHsWord w x = "W# " <> parens (extendFn <> " " <> parens x)
......
......@@ -30,9 +30,9 @@ import Data.Proxy
import Test.QuickCheck hiding ((.&.))
import Prelude hiding (truncate)
#if WORD_SIZE_IN_BITS == 32
#if defined(WORD_SIZE_32BIT)
type WordSize = W32
#elif WORD_SIZE_IN_BITS == 64
#elif defined(WORD_SIZE_64BIT)
type WordSize = W64
#else
#error unknown word size
......
......@@ -8,9 +8,19 @@ copyright: (c) 2021 Ben Gamari
synopsis:
A QuickCheck testsuite for GHC's Cmm pipeline.
flag target-32bit
description: Set to True when the compiler-under-test targets a
platform with 32-bit word-size.
default: False
manual: True
executable test-primops
main-is: Main.hs
hs-source-dirs: src
if flag(target-32bit)
cpp-options: -DWORD_SIZE_32BIT
else
cpp-options: -DWORD_SIZE_64BIT
other-modules: Width,
Number,
Expr,
......
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