module Data.TagBits
(
unsafeGetTagBits
, unsafeIsEvaluated
) where
#if __GLASGOW_HASKELL__ >= 608
#define HAS_TAGS
#define HAS_INFO_TABLE
import Data.Bits ((.&.))
import Data.Functor ((<$>))
import Unsafe.Coerce (unsafeCoerce)
import System.IO.Unsafe (unsafePerformIO)
import Foreign (plusPtr, castPtr, peek)
import GHC.Prim
import GHC.Exts
import Data.Word
#include "ghcconfig.h"
#if SIZEOF_VOID_P == 8
type HalfWord = Word32
#else
type HalfWord = Word16
#endif
#if i386_BUILD_ARCH
#define TABLES_NEXT_TO_CODE
#define CLOSURE_TYPE_OFFSET SIZEOF_INT
#else
#define CLOSURE_TYPE_OFFSET (SIZEOF_INT * 2)
#endif
getInfoTablePtr :: a -> Ptr HalfWord
getInfoTablePtr i = case unpackClosure# i of
(# p, _, _ #) -> Ptr p
newtype ClosureType = ClosureType HalfWord
getClosureType :: a -> IO ClosureType
getClosureType a = ClosureType <$>
peek (castPtr (getInfoTablePtr a) `plusPtr` CLOSURE_TYPE_OFFSET)
isConstructor :: ClosureType -> Bool
isConstructor (ClosureType i) = i >= 1 && i <= 8
isIndirection :: ClosureType -> Bool
isIndirection (ClosureType i) = i >= 28 && i <= 32
unsafeIsConstructorOrIndirection :: a -> Bool
unsafeIsConstructorOrIndirection a = unsafePerformIO $ do
ty <- getClosureType a
return (isConstructor ty || isIndirection ty)
#endif
unsafeGetTagBits :: a -> Word
#ifdef HAS_TAGS
unsafeGetTagBits a = unsafeCoerce (Box a) .&. (SIZEOF_VOID_P 1)
data Box a = Box a
#else
unsafeGetTagBits _ = 0
#endif
unsafeIsEvaluated :: a -> Bool
unsafeIsEvaluated a = unsafeGetTagBits a > 0
#ifdef HAS_INFO_TABLE
|| unsafeIsConstructorOrIndirection a
#endif