{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE Rank2Types          #-}
module Data.TMap
       ( 
         TMap
         
       , empty
       , one
         
       , insert
       , delete
       , unionWith
       , union
       , map
       , adjust
         
       , lookup
       , member
       , size
       , keys
       ) where
import Prelude hiding (lookup, map)
import Data.Functor.Identity (Identity (..))
import Data.Typeable (Typeable)
import GHC.Exts (coerce)
import Type.Reflection (SomeTypeRep)
import qualified Data.TypeRepMap as F
type TMap = F.TypeRepMap Identity
empty :: TMap
empty :: TMap
empty = TMap
forall k (f :: k -> *). TypeRepMap f
F.empty
{-# INLINE empty #-}
one :: forall a . Typeable a => a -> TMap
one :: a -> TMap
one x :: a
x = TMap -> TMap
forall a b. Coercible a b => a -> b
coerce (Typeable a => Identity a -> TMap
forall k (a :: k) (f :: k -> *). Typeable a => f a -> TypeRepMap f
F.one @a @Identity (Identity a -> TMap) -> Identity a -> TMap
forall a b. (a -> b) -> a -> b
$ a -> Identity a
forall a b. Coercible a b => a -> b
coerce a
x)
{-# INLINE one #-}
insert :: forall a . Typeable a => a -> TMap -> TMap
insert :: a -> TMap -> TMap
insert x :: a
x = (TMap -> TMap) -> TMap -> TMap
forall a b. Coercible a b => a -> b
coerce (Typeable a => Identity a -> TMap -> TMap
forall k (a :: k) (f :: k -> *).
Typeable a =>
f a -> TypeRepMap f -> TypeRepMap f
F.insert @a @Identity (Identity a -> TMap -> TMap) -> Identity a -> TMap -> TMap
forall a b. (a -> b) -> a -> b
$ a -> Identity a
forall a b. Coercible a b => a -> b
coerce a
x)
{-# INLINE insert #-}
delete :: forall a . Typeable a => TMap -> TMap
delete :: TMap -> TMap
delete = Typeable a => TMap -> TMap
forall k (a :: k) (f :: k -> *).
Typeable a =>
TypeRepMap f -> TypeRepMap f
F.delete @a @Identity
{-# INLINE delete #-}
unionWith :: (forall x. Typeable x => x -> x -> x) -> TMap -> TMap -> TMap
unionWith :: (forall x. Typeable x => x -> x -> x) -> TMap -> TMap -> TMap
unionWith f :: forall x. Typeable x => x -> x -> x
f = (forall x. Typeable x => Identity x -> Identity x -> Identity x)
-> TMap -> TMap -> TMap
forall k (f :: k -> *).
(forall (x :: k). Typeable x => f x -> f x -> f x)
-> TypeRepMap f -> TypeRepMap f -> TypeRepMap f
F.unionWith forall x. Typeable x => Identity x -> Identity x -> Identity x
fId
  where
    fId :: forall y . Typeable y => Identity y -> Identity y -> Identity y
    fId :: Identity y -> Identity y -> Identity y
fId y1 :: Identity y
y1 y2 :: Identity y
y2 = y -> Identity y
forall a. a -> Identity a
Identity (y -> Identity y) -> y -> Identity y
forall a b. (a -> b) -> a -> b
$ y -> y -> y
forall x. Typeable x => x -> x -> x
f (Identity y -> y
forall a b. Coercible a b => a -> b
coerce Identity y
y1) (Identity y -> y
forall a b. Coercible a b => a -> b
coerce Identity y
y2)
{-# INLINE unionWith #-}
union :: TMap -> TMap -> TMap
union :: TMap -> TMap -> TMap
union = TMap -> TMap -> TMap
forall k (f :: k -> *).
TypeRepMap f -> TypeRepMap f -> TypeRepMap f
F.union
{-# INLINE union #-}
lookup :: forall a. Typeable a => TMap -> Maybe a
lookup :: TMap -> Maybe a
lookup = (TMap -> Maybe (Identity a)) -> TMap -> Maybe a
forall a b. Coercible a b => a -> b
coerce (Typeable a => TMap -> Maybe (Identity a)
forall k (a :: k) (f :: k -> *).
Typeable a =>
TypeRepMap f -> Maybe (f a)
F.lookup @a @Identity)
{-# INLINE lookup #-}
member :: forall a . Typeable a => TMap -> Bool
member :: TMap -> Bool
member = Typeable a => TMap -> Bool
forall k (a :: k) (f :: k -> *). Typeable a => TypeRepMap f -> Bool
F.member @a @Identity
{-# INLINE member #-}
size :: TMap -> Int
size :: TMap -> Int
size = TMap -> Int
forall k (f :: k -> *). TypeRepMap f -> Int
F.size
{-# INLINE size #-}
keys :: TMap -> [SomeTypeRep]
keys :: TMap -> [SomeTypeRep]
keys = TMap -> [SomeTypeRep]
forall k (f :: k -> *). TypeRepMap f -> [SomeTypeRep]
F.keys
{-# INLINE keys #-}
map :: (forall a. Typeable a => a -> a) -> TMap -> TMap
map :: (forall a. Typeable a => a -> a) -> TMap -> TMap
map f :: forall a. Typeable a => a -> a
f = (forall x. Typeable x => Identity x -> Identity x) -> TMap -> TMap
forall k (f :: k -> *) (g :: k -> *).
(forall (x :: k). Typeable x => f x -> g x)
-> TypeRepMap f -> TypeRepMap g
F.hoistWithKey ((x -> x) -> Identity x -> Identity x
forall a. (a -> a) -> Identity a -> Identity a
liftToIdentity x -> x
forall a. Typeable a => a -> a
f)
{-# INLINE map #-}
adjust :: Typeable a => (a -> a) -> TMap -> TMap
adjust :: (a -> a) -> TMap -> TMap
adjust f :: a -> a
f = (Identity a -> Identity a) -> TMap -> TMap
forall k (a :: k) (f :: k -> *).
Typeable a =>
(f a -> f a) -> TypeRepMap f -> TypeRepMap f
F.adjust ((a -> a) -> Identity a -> Identity a
forall a. (a -> a) -> Identity a -> Identity a
liftToIdentity a -> a
f)
{-# INLINE adjust #-}
liftToIdentity :: forall a. (a -> a) -> Identity a -> Identity a
liftToIdentity :: (a -> a) -> Identity a -> Identity a
liftToIdentity = (a -> a) -> Identity a -> Identity a
forall a b. Coercible a b => a -> b
coerce