type-map-0.1.0.0: Type-indexed maps

Safe HaskellNone
LanguageHaskell2010

Data.TypeMap.Internal.Dynamic

Contents

Synopsis

Exposed functions

newtype TypeMap x Source #

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

Constructors

TypeMap (Map TypeRep Any) 

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

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

null :: TypeMap x -> Bool Source #

Whether the map is empty.

empty :: TypeMap x Source #

Empty type 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.

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

Lookup an element indexed by type t.

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 map.

Unsafe internals

type family Typed x t Source #

Instances

type Typed (OfType a) t Source # 
type Typed (OfType a) t = a
type Typed (ItemFun x y) t Source # 
type Typed (ItemFun x y) t = Item x t -> Item y t
type Typed (ItemKleisli f x y) t Source # 
type Typed (ItemKleisli f x y) t = Item x t -> f (Item y t)

type family UnTyped x Source #

Instances

type UnTyped (OfType a) Source # 
type UnTyped (OfType a) = a
type UnTyped (ItemFun x y) Source # 
type UnTyped (ItemFun x y) = Any * -> Any *
type UnTyped (ItemKleisli f x y) Source # 
type UnTyped (ItemKleisli f x y) = Any * -> f (Any *)

data ItemFun x y Source #

Instances

type UnTyped (ItemFun x y) Source # 
type UnTyped (ItemFun x y) = Any * -> Any *
type Typed (ItemFun x y) t Source # 
type Typed (ItemFun x y) t = Item x t -> Item y t

data ItemKleisli f x y Source #

Instances

type UnTyped (ItemKleisli f x y) Source # 
type UnTyped (ItemKleisli f x y) = Any * -> f (Any *)
type Typed (ItemKleisli f x y) t Source # 
type Typed (ItemKleisli f x y) t = Item x t -> f (Item y t)

newtype WithTypeable x Source #

Constructors

WithTypeable (forall t. Typeable t => Proxy t -> Typed x t) 

withTypeRep :: forall x proxy. (forall t. Typeable t => Proxy t -> Typed x t) -> proxy x -> TypeRep -> UnTyped x Source #