Why does sizeOf Word64 = 4?
John Meacham
john at repetae.net
Sat Nov 8 19:19:12 EST 2003
On Sat, Nov 08, 2003 at 06:32:35PM -0800, Ben Escoto wrote:
> 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?
sizeof returns the size of its argument, since the argument you passed
is a pointer, so it properly returns the size of a pointer, 32 bits or 4
bytes on your architecture.
to find the size of the actual datatype do something like
sizeOf (undefined :: Word16) => 2
sizeOf (undefined :: Word64) => 8
sizeOf never evaluates its arguments so it is okay to pass anything to
it of the type you are interested in.
John
--
---------------------------------------------------------------------------
John Meacham - California Institute of Technology, Alum. - john at foo.net
---------------------------------------------------------------------------
More information about the Glasgow-haskell-users
mailing list