module Data.TypeMap.Internal.Dynamic.Alt where
import Data.Typeable
import GHC.Prim (Any, Proxy#)
import Unsafe.Coerce
import qualified Data.Map as Map
import Data.TypeMap.Internal.Dynamic
(TypeMap(..), Item, Typed, UnTyped, ItemFun, ItemKleisli)
insert
:: forall t x proxy
. Typeable t => Item x t -> TypeMap x -> TypeMap x
insert v (TypeMap m) = TypeMap (Map.insert (typeRep (Proxy @t)) (coerce v) m)
where
coerce :: Item x t -> Any
coerce = unsafeCoerce
lookup
:: forall t x proxy
. Typeable t => TypeMap x -> Maybe (Item x t)
lookup (TypeMap m) = coerce (Map.lookup (typeRep (Proxy @t)) m)
where
coerce :: Maybe Any -> Maybe (Item x t)
coerce = unsafeCoerce
map
:: forall x y. (forall t. Typeable t => Item x t -> Item y t)
-> TypeMap x -> TypeMap y
map f (TypeMap m) = TypeMap (Map.mapWithKey f' m)
where
f' = withTypeRep @(ItemFun x y)
(Typed_ (f @t) :: forall t. Typeable t => Typed_ (ItemFun x y) t)
traverse
:: forall f x y
. Applicative f
=> (forall t. Typeable t => Item x t -> f (Item y t))
-> TypeMap x -> f (TypeMap y)
traverse f (TypeMap m) = TypeMap <$> Map.traverseWithKey f' m
where
f' = withTypeRep @(ItemKleisli f x y)
(Typed_ (f @t) :: forall t. Typeable t => Typed_ (ItemKleisli f x y) t)
newtype Typed_ x t = Typed_ (Typed x t)
newtype WithTypeable x
= WithTypeable (forall t. Typeable t => Typed_ x t)
withTypeable
:: WithTypeable x -> (Proxy# t -> TypeRep) -> UnTyped x
withTypeable = unsafeCoerce
withTypeRep
:: forall x
. (forall t. Typeable t => Typed_ x t)
-> TypeRep -> UnTyped x
withTypeRep f rep =
withTypeable (WithTypeable f :: WithTypeable x) (\_ -> rep)