type-map-0.1.7.0: Type-indexed maps
Safe HaskellNone
LanguageHaskell2010

Data.TypeMap.Dynamic

Synopsis

Dynamic type maps

data TypeMap x Source #

Map from types t of kind * to values of type Item x t.

type family Item x t Source #

An extensible type family mapping types (as keys) to types of values, parameterized by types x.

Instances

Instances details
type Item (OfType a) t Source # 
Instance details

Defined in Data.TypeMap.Internal.Dynamic

type Item (OfType a) t = a

Basic operations

empty :: TypeMap x Source #

Empty type map.

null :: TypeMap x -> Bool Source #

Whether the map is empty.

size :: TypeMap x -> Int Source #

The number of elements in the map.

insert :: forall t x proxy. Typeable t => proxy t -> Item x t -> TypeMap x -> TypeMap x Source #

Insert an element indexed by type t.

(<:) :: forall t x proxy. Typeable t => TypeMap x -> (proxy t, Item x t) -> TypeMap x Source #

Infix version of insert to facilitate a literal-ish syntax:

empty
  <: (Proxy k1, v1)
  <: (Proxy k2, v2)

update :: forall t x proxy. Typeable t => proxy t -> (Item x t -> Maybe (Item x t)) -> TypeMap x -> TypeMap x Source #

Update an element indexed by type t.

alter :: forall t x proxy. Typeable t => proxy t -> (Maybe (Item x t) -> Maybe (Item x t)) -> TypeMap x -> TypeMap x Source #

Update a (possibly absent) element indexed by type t.

lookup :: forall t x proxy. Typeable t => proxy t -> TypeMap x -> Maybe (Item x t) Source #

Lookup an element indexed by type t.

delete :: forall t x proxy. Typeable t => proxy t -> TypeMap x -> TypeMap x Source #

Delete a key and its value from the map. Does nothing if the key does not exist.

Traversals and folds

map :: forall x y. (forall t. Typeable t => Proxy t -> Item x t -> Item y t) -> TypeMap x -> TypeMap y Source #

Map a function on all elements.

traverse :: forall f x y. Applicative f => (forall t. Typeable t => Proxy t -> Item x t -> f (Item y t)) -> TypeMap x -> f (TypeMap y) Source #

Traverse the type map. (map with effects.)

toList :: forall r. TypeMap (OfType r) -> [r] Source #

Reduce a constant type map into a plain list of values.

toListMap :: forall tm r. (forall t. Proxy t -> Item tm t -> r) -> TypeMap tm -> [r] Source #

Collapse a type map into a plain list of values.

Set-like operations

union :: forall x. TypeMap x -> TypeMap x -> TypeMap x Source #

Left-biased union of two maps; it keeps the first key if duplicates are found.

difference :: forall x. TypeMap x -> TypeMap x -> TypeMap x Source #

Difference of two maps; keep elements of the first map which are not in the second.

intersection :: forall x y. TypeMap x -> TypeMap y -> TypeMap x Source #

Intersection of two maps; keep elements of the first map which are also in the second.

Type-level mappings

data OfType a Source #

A constant mapping to type a. TypeMap (OfType a) is the type of maps from types to values of type a.

Instances

Instances details
type UnTyped (OfType a) Source # 
Instance details

Defined in Data.TypeMap.Internal.Dynamic

type UnTyped (OfType a) = a
type Typed (OfType a) t Source # 
Instance details

Defined in Data.TypeMap.Internal.Dynamic

type Typed (OfType a) t = a
type Item (OfType a) t Source # 
Instance details

Defined in Data.TypeMap.Internal.Dynamic

type Item (OfType a) t = a