Why does sizeOf Word64 = 4?

Ben Escoto bescoto at stanford.edu
Sat Nov 8 18:32:35 EST 2003


Hi, I'm trying to learn about Haskell's FFI (running 6.0.1 on linux)
and see the following weird behavior with ghci:

	Prelude> :module Data.Word Foreign.Storable Foreign.Ptr
	Prelude Foreign.Ptr Foreign.Storable Data.Word> sizeOf nullPtr
	4
	Prelude Foreign.Ptr Foreign.Storable Data.Word> sizeOf
	                                          (nullPtr :: Ptr Word64)
	4

Shouldn't "sizeOf nullPtr" return an error?  And sizeOf a Ptr Word64
should be 8 I think.  Also this program prints "4", when it seems it
should print "8":

	module Main where
	import Data.Word
	import Foreign.Storable
	import Foreign.Ptr
	import Foreign.StablePtr

	x :: Word64
	x = 5

	main = do x_sptr <- newStablePtr 5
	          putStrLn $ show $ sizeOf x_sptr

These are artificial examples, but I originally noticed this when
trying to decode a C structure.  Is this a bug in ghc or am I
misunderstanding what sizeOf is supposed to do?


-- 
Ben Escoto
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: not available
Url : http://haskell.org/pipermail/glasgow-haskell-users/attachments/20031108/ca7b48bd/attachment.bin


More information about the Glasgow-haskell-users mailing list