{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
module Data.TypeRep.OptimalVector
(
TypeRepMap (..)
, empty
, insert
, lookup
, size
, TF (..)
, fromList
) where
import Prelude hiding (lookup)
import Control.Arrow ((&&&))
import Data.Kind (Type)
import Data.Proxy (Proxy (..))
import Data.Typeable (Typeable, typeRep, typeRepFingerprint)
import Data.Word (Word64)
import GHC.Base (Any, Int (..), Int#, uncheckedIShiftRA#, (+#), (-#), (<#))
import GHC.Exts (inline, sortWith)
import GHC.Fingerprint (Fingerprint (..))
import Unsafe.Coerce (unsafeCoerce)
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as Unboxed
data TypeRepMap (f :: k -> Type) = TypeRepMap
{ fingerprintAs :: Unboxed.Vector Word64
, fingerprintBs :: Unboxed.Vector Word64
, anys :: V.Vector Any
}
fromAny :: Any -> f a
fromAny = unsafeCoerce
empty :: TypeRepMap f
empty = TypeRepMap mempty mempty mempty
insert :: forall a f . Typeable a => a -> TypeRepMap f -> TypeRepMap f
insert = undefined
lookup :: forall a f . Typeable a => TypeRepMap f -> Maybe (f a)
lookup tVect = fromAny . (anys tVect V.!)
<$> binarySearch (typeRepFingerprint $ typeRep $ Proxy @a)
(fingerprintAs tVect)
(fingerprintBs tVect)
size :: TypeRepMap f -> Int
size = Unboxed.length . fingerprintAs
binarySearch :: Fingerprint -> Unboxed.Vector Word64 -> Unboxed.Vector Word64 -> Maybe Int
binarySearch (Fingerprint a b) fpAs fpBs =
let
!(I# len) = Unboxed.length fpAs
checkfpBs :: Int# -> Maybe Int
checkfpBs i =
case i <# len of
0# -> Nothing
_ | a /= Unboxed.unsafeIndex fpAs (I# i) -> Nothing
| b == Unboxed.unsafeIndex fpBs (I# i) -> Just (I# i)
| otherwise -> checkfpBs (i +# 1#)
in
inline (checkfpBs (binSearchHelp (-1#) len))
where
binSearchHelp :: Int# -> Int# -> Int#
binSearchHelp l r = case l <# (r -# 1#) of
0# -> r
_ ->
let m = uncheckedIShiftRA# (l +# r) 1# in
if Unboxed.unsafeIndex fpAs (I# m) < a
then binSearchHelp m r
else binSearchHelp l m
data TF f where
TF :: Typeable a => f a -> TF f
fromF :: Typeable a => f a -> Proxy a
fromF _ = Proxy
fromList :: forall f . [TF f] -> TypeRepMap f
fromList tfs = TypeRepMap (Unboxed.fromList fpAs) (Unboxed.fromList fpBs) (V.fromList ans)
where
(fpAs, fpBs) = unzip $ fmap (\(Fingerprint a b) -> (a, b)) fps
(fps, ans) = unzip $ sortWith fst $ map (fp &&& an) tfs
fp :: TF f -> Fingerprint
fp (TF x) = typeRepFingerprint $ typeRep $ fromF x
an :: TF f -> Any
an (TF x) = unsafeCoerce x