Alternative to sizeof(int) macro

Hi,

In GHC some types depend on ARCH (e.g. Word).
It may be 4 bytes or 8 bytes.

My first attempt was to use sizeof macro from CPP, but it turns out that CPP in GHC doesn’t have such thing. Why sizeof is not defined? I thought that Haskell CPP is the same as GCC one.

{-# LANGUAGE CPP #-}

foo  :: Word -> String
#if sizeof(int) == 4
foo = foo32 . fromIntegral
#elseif sizeof(int) = 8
foo = foo64 . fromIntegral
#else
#error "Bad int size" ## sizeof(int)
#endif

I found in cabal docs that it must define ARCH macro, but cabal run foo runs without them:

#if i386_HOST_ARCH
#elseif x86_64_HOST_ARCH

I can use Template Haskell, but is there another compile time option to make foo function polymorphic?

1 Like

Maybe:

import Data.Bits (finiteBitSize)

wordSize :: Int
wordSize = finiteBitSize (0 :: Word)
1 Like

You can include “MachDeps.h” and use WORD_SIZE_IN_BITS as follows:

#include "MachDeps.h"

#if WORD_SIZE_IN_BITS == 64
foo = ...
#elif WORD_SIZE_IN_BITS == 32
foo = ...
#else
# error unsupported WORD_SIZE_IN_BITS config
#endif

1 Like