{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
#ifdef UNSAFETRICKS
{-# LANGUAGE MagicHash #-}
#endif
module Data.HashTable.Internal.UnsafeTricks
( Key
, toKey
, fromKey
, emptyRecord
, deletedRecord
, keyIsEmpty
, keyIsDeleted
, writeDeletedElement
, makeEmptyVector
) where
import Control.Monad.Primitive
import Data.Vector.Mutable (MVector)
import qualified Data.Vector.Mutable as M
#ifdef UNSAFETRICKS
import GHC.Exts
import Unsafe.Coerce
#endif
#ifdef UNSAFETRICKS
type Key a = Any
#else
data Key a = Key !a
| EmptyElement
| DeletedElement
deriving (Show)
#endif
emptyRecord :: Key a
deletedRecord :: Key a
keyIsEmpty :: Key a -> Bool
keyIsDeleted :: Key a -> Bool
makeEmptyVector :: PrimMonad m => Int -> m (MVector (PrimState m) (Key a))
writeDeletedElement :: PrimMonad m =>
MVector (PrimState m) (Key a) -> Int -> m ()
toKey :: a -> Key a
fromKey :: Key a -> a
#ifdef UNSAFETRICKS
data TombStone = EmptyElement
| DeletedElement
{-# NOINLINE emptyRecord #-}
emptyRecord :: Key a
emptyRecord = TombStone -> Key a
forall a b. a -> b
unsafeCoerce TombStone
EmptyElement
{-# NOINLINE deletedRecord #-}
deletedRecord :: Key a
deletedRecord = TombStone -> Key a
forall a b. a -> b
unsafeCoerce TombStone
DeletedElement
{-# INLINE keyIsEmpty #-}
keyIsEmpty :: Key a -> Bool
keyIsEmpty Key a
a = Int# -> Bool
isTrue# (Int#
x# Int# -> Int# -> Int#
==# Int#
1#)
where
!x# :: Int#
x# = Key a -> Key a -> Int#
forall a. a -> a -> Int#
reallyUnsafePtrEquality# Key a
a Key a
forall a. Key a
emptyRecord
{-# INLINE keyIsDeleted #-}
keyIsDeleted :: Key a -> Bool
keyIsDeleted Key a
a = Int# -> Bool
isTrue# (Int#
x# Int# -> Int# -> Int#
==# Int#
1#)
where
!x# :: Int#
x# = Key a -> Key a -> Int#
forall a. a -> a -> Int#
reallyUnsafePtrEquality# Key a
a Key a
forall a. Key a
deletedRecord
{-# INLINE toKey #-}
toKey :: a -> Key a
toKey = a -> Key a
forall a b. a -> b
unsafeCoerce
{-# INLINE fromKey #-}
fromKey :: Key a -> a
fromKey = Key a -> a
forall a b. a -> b
unsafeCoerce
#else
emptyRecord = EmptyElement
deletedRecord = DeletedElement
keyIsEmpty EmptyElement = True
keyIsEmpty _ = False
keyIsDeleted DeletedElement = True
keyIsDeleted _ = False
toKey = Key
fromKey (Key x) = x
fromKey _ = error "impossible"
#endif
{-# INLINE makeEmptyVector #-}
makeEmptyVector :: Int -> m (MVector (PrimState m) (Key a))
makeEmptyVector Int
m = Int -> Key a -> m (MVector (PrimState m) (Key a))
forall (m :: * -> *) a.
PrimMonad m =>
Int -> a -> m (MVector (PrimState m) a)
M.replicate Int
m Key a
forall a. Key a
emptyRecord
{-# INLINE writeDeletedElement #-}
writeDeletedElement :: MVector (PrimState m) (Key a) -> Int -> m ()
writeDeletedElement MVector (PrimState m) (Key a)
v Int
i = MVector (PrimState m) (Key a) -> Int -> Key a -> m ()
forall (m :: * -> *) a.
PrimMonad m =>
MVector (PrimState m) a -> Int -> a -> m ()
M.unsafeWrite MVector (PrimState m) (Key a)
v Int
i Key a
forall a. Key a
deletedRecord