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

Enable testing of Word64#, et al on 32-bit platforms

parent e91bc499
No related branches found
No related tags found
1 merge request!10Enable testing of Word64# on 32-bit platforms
......@@ -6,11 +6,12 @@ module Main where
import GHC.Exts
import GHC.Ptr
import GHC.Word
import System.Posix (RTLDFlags(..), dlopen, dlsym, dlclose)
import System.Environment
import System.IO.MMap
foreign import prim "stg_trampoline" trampoline :: Addr# -> Addr# -> Word#
foreign import prim "stg_trampoline" trampoline :: Addr# -> Addr# -> Word64#
main :: IO ()
main = do
......@@ -18,5 +19,5 @@ main = do
(Ptr p, _, _, _) <- mmapFilePtr "test" ReadOnly Nothing
dl <- dlopen so [RTLD_NOW]
Ptr entry <- castFunPtrToPtr <$> dlsym dl "test"
print $ W# (trampoline entry p)
print $ W64# (trampoline entry p)
dlclose dl
......@@ -82,7 +82,7 @@ mkStaticWrapper comp width = do
, "{-# LANGUAGE UnliftedFFITypes #-}"
, "{-# LANGUAGE MagicHash #-}"
, "module Main where"
, "import Data.Word"
, "import GHC.Word"
, "import GHC.Exts"
, "import GHC.Ptr (Ptr(Ptr))"
, "import qualified Data.ByteString as BS"
......@@ -91,22 +91,17 @@ mkStaticWrapper comp width = do
, "main :: IO ()"
, "main = do"
, " buf <- BS.readFile \"test\""
, " BS.unsafeUseAsCString buf $ \\(Ptr p) -> print $ " <> toHsWord width "test p"
, " BS.unsafeUseAsCString buf $ \\(Ptr p) -> print $ " <> toHsWord64 width "test p"
]
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)
toHsWord64 :: Width -> String -> String
toHsWord64 w x = "W64# " <> parens (extendFn <> " " <> parens x)
where
extendFn
| w == W64 = ""
......@@ -119,7 +114,7 @@ evalCmm em cmm = do
return $ read out
-- | Evaluate an 'Expr'.
evalExpr :: EvalMethod -> Expr WordSize -> IO Natural
evalExpr :: EvalMethod -> Expr W64 -> IO Natural
evalExpr em = evalCmm em . toCmmDecl "test"
type Cmm = String
......
......@@ -103,9 +103,7 @@ allWidths =
[ SomeWidth (Proxy @W8)
, SomeWidth (Proxy @W16)
, SomeWidth (Proxy @W32)
#if WORD_SIZE_IN_BITS == 64
, SomeWidth (Proxy @W64)
#endif
]
forAllWidths :: (forall w. (KnownWidth w) => Proxy w -> r) -> [r]
......
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