type-map-0.1.2.0: Type-indexed maps

Safe HaskellNone
LanguageHaskell2010

Data.TypeMap.Dynamic.Alt

Description

Type-application-based interface.

Synopsis

Documentation

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

type Item (OfType a) t Source # 
type Item (OfType a) t = a

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 => Item x t -> TypeMap x -> TypeMap x Source #

Insert an element indexed by type t.

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

Lookup an element indexed by type t.

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

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

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.

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

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

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

type UnTyped (OfType a) Source # 
type UnTyped (OfType a) = a
type Typed (OfType a) t Source # 
type Typed (OfType a) t = a
type Item (OfType a) t Source # 
type Item (OfType a) t = a