typerep-map-0.3.0: Efficient implementation of a dependent map with types as keys

Safe HaskellNone
LanguageHaskell2010

Data.TypeRepMap

Contents

Description

A version of TMap parametrized by an interpretation f. This sort of parametrization may be familiar to users of vinyl records.

TypeRepMap f is a more efficient replacement for DMap TypeRep f (where DMap is from the dependent-map package).

Here is an example of using Maybe as an interpretation, with a comparison to TMap:

     TMap              TypeRepMap Maybe
--------------       -------------------
 Int  -> 5             Int  -> Just 5
 Bool -> True          Bool -> Nothing
 Char -> 'x'           Char -> Just 'x'

In fact, a TMap is defined as TypeRepMap Identity.

Since TypeRep is poly-kinded, the interpretation can use any kind for the keys. For instance, we can use the Symbol kind to use TypeRepMap as an extensible record:

newtype Field name = F (FType name)

type family FType (name :: Symbol) :: Type
type instance FType "radius" = Double
type instance FType "border-color" = RGB
type instance FType "border-width" = Double

       TypeRepMap Field
--------------------------------------
 "radius"       -> F 5.7
 "border-color" -> F (rgb 148 0 211)
 "border-width" -> F 0.5
Synopsis

Map type

data TypeRepMap (f :: k -> Type) Source #

TypeRepMap is a heterogeneous data structure similar in its essence to Map with types as keys, where each value has the type of its key. In addition to that, each value is wrapped in an interpretation f.

Here is an example of using Maybe as an interpretation, with a comparison to Map:

 Map String (Maybe String)          TypeRepMap Maybe
---------------------------       ---------------------
 "Int"  -> Just "5"                 Int  -> Just 5
 "Bool" -> Just "True"              Bool -> Just True
 "Char" -> Nothing                  Char -> Nothing

The runtime representation of TypeRepMap is an array, not a tree. This makes lookup significantly more efficient.

Instances
IsList (TypeRepMap f) Source #
fromList . toList == 'id'

Creates TypeRepMap from a list of WrapTypeables.

>>> show $ fromList [WrapTypeable $ Identity True, WrapTypeable $ Identity 'a']
TypeRepMap [Bool, Char]
Instance details

Defined in Data.TypeRepMap.Internal

Associated Types

type Item (TypeRepMap f) :: * #

Show (TypeRepMap f) Source #

Shows only keys.

Instance details

Defined in Data.TypeRepMap.Internal

Semigroup (TypeRepMap f) Source #

Uses union to combine TypeRepMaps.

Instance details

Defined in Data.TypeRepMap.Internal

Monoid (TypeRepMap f) Source # 
Instance details

Defined in Data.TypeRepMap.Internal

type Item (TypeRepMap f) Source # 
Instance details

Defined in Data.TypeRepMap.Internal

Construction

empty :: TypeRepMap f Source #

A TypeRepMap with no values stored in it.

size empty == 0
member @a empty == False

one :: forall a f. Typeable a => f a -> TypeRepMap f Source #

Construct a TypeRepMap with a single element.

size (one x) == 1
member @a (one (x :: f a)) == True

Modification

insert :: forall a f. Typeable a => f a -> TypeRepMap f -> TypeRepMap f Source #

Insert a value into a TypeRepMap.

size (insert v tm) >= size tm
member @a (insert (x :: f a) tm) == True

delete :: forall a (f :: KindOf a -> Type). Typeable a => TypeRepMap f -> TypeRepMap f Source #

Delete a value from a TypeRepMap.

size (delete @a tm) <= size tm
member @a (delete @a tm) == False
>>> tm = delete @Bool $ insert (Just True) $ one (Just 'a')
>>> size tm
1
>>> member @Bool tm
False
>>> member @Char tm
True

adjust :: forall a f. Typeable a => (f a -> f a) -> TypeRepMap f -> TypeRepMap f Source #

Update a value at a specific key with the result of the provided function. When the key is not a member of the map, the original map is returned.

>>> trmap = fromList @(TypeRepMap Identity) [WrapTypeable $ Identity "a"]
>>> lookup @String $ adjust (fmap (++ "ww")) trmap
Just (Identity "aww")

hoist :: (forall x. f x -> g x) -> TypeRepMap f -> TypeRepMap g Source #

Map over the elements of a TypeRepMap.

>>> tm = insert (Identity True) $ one (Identity 'a')
>>> lookup @Bool tm
Just (Identity True)
>>> lookup @Char tm
Just (Identity 'a')
>>> tm2 = hoist ((:[]) . runIdentity) tm
>>> lookup @Bool tm2
Just [True]
>>> lookup @Char tm2
Just "a"

hoistA :: Applicative t => (forall x. f x -> t (g x)) -> TypeRepMap f -> t (TypeRepMap g) Source #

hoistWithKey :: forall f g. (forall x. Typeable x => f x -> g x) -> TypeRepMap f -> TypeRepMap g Source #

unionWith :: (forall x. f x -> f x -> f x) -> TypeRepMap f -> TypeRepMap f -> TypeRepMap f Source #

The union of two TypeRepMaps using a combining function.

union :: TypeRepMap f -> TypeRepMap f -> TypeRepMap f Source #

The (left-biased) union of two TypeRepMaps. It prefers the first map when duplicate keys are encountered, i.e. union == unionWith const.

Query

lookup :: forall a f. Typeable a => TypeRepMap f -> Maybe (f a) Source #

Lookup a value of the given type in a TypeRepMap.

>>> x = lookup $ insert (Identity (11 :: Int)) empty
>>> x :: Maybe (Identity Int)
Just (Identity 11)
>>> x :: Maybe (Identity ())
Nothing

member :: forall a (f :: KindOf a -> Type). Typeable a => TypeRepMap f -> Bool Source #

Check if a value of the given type is present in a TypeRepMap.

>>> member @Char $ one (Identity 'a')
True
>>> member @Bool $ one (Identity 'a')
False

size :: TypeRepMap f -> Int Source #

Get the amount of elements in a TypeRepMap.

keys :: TypeRepMap f -> [SomeTypeRep] Source #

Return the list of SomeTypeRep from the keys.

IsList

data WrapTypeable f where Source #

Existential wrapper around Typeable indexed by f type parameter. Useful for TypeRepMap structure creation form list of WrapTypeables.

Constructors

WrapTypeable :: Typeable a => f a -> WrapTypeable f 
Instances
Show (WrapTypeable f) Source # 
Instance details

Defined in Data.TypeRepMap.Internal