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

T229: Fix name of WORD_SIZE macro

parent 82a50c40
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CPP #-}
#include "MachDeps.h"
import Data.Array.MArray
import Data.Array.IO
import Data.Word
......@@ -7,7 +9,7 @@ import Data.Word
main :: IO ()
main = do
-- This should fail due to integer overflow
#if WORD_SIZE == 8
#if WORD_SIZE_IN_BITS == 64
m <- newArray_ (0,2^62-1) :: IO (IOUArray Int Word32) -- allocates 0 bytes
readArray m 17 >>= print -- Read some random location in address space
#else
......
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