Skip to content
Snippets Groups Projects

Draft: Fix RunGhc for i386 and GHC >=9.4

Closed Jaro Reinders requested to merge i386 into master
2 files
+ 5
11
Compare changes
  • Side-by-side
  • Inline
Files
2
+ 5
9
@@ -80,8 +80,8 @@ mkStaticWrapper comp width = do
, "{-# LANGUAGE UnliftedFFITypes #-}"
, "{-# LANGUAGE MagicHash #-}"
, "module Main where"
, "import Data.Word"
, "import GHC.Exts"
, "import GHC.Word"
, "import GHC.Ptr (Ptr(Ptr))"
, "import qualified Data.ByteString as BS"
, "import qualified Data.ByteString.Unsafe as BS"
@@ -89,21 +89,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 $ " <> toBoxedWord width "test p"
]
hsType :: Width -> String
hsType W8 = "Word8#"
hsType W16 = "Word16#"
hsType W32 = "Word32#"
hsType W64 = "Word#"
hsType W64 = "Word64#"
toHsWord :: Width -> String -> String
toHsWord w x = "W# " <> parens (extendFn <> " " <> parens x)
where
extendFn
| w == W64 = ""
| otherwise = "extendWord" <> show (widthBits w) <> "#"
toBoxedWord :: Width -> String -> String
toBoxedWord w x = "W" <> show (widthBits w) <> "#" <> parens x
evalCmm :: EvalMethod -> Cmm -> IO Natural
evalCmm em cmm = do
Loading