Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype TypeMap x = TypeMap (Map TypeRep Any)
- type family Item x t
- data OfType a
- null :: TypeMap x -> Bool
- empty :: TypeMap x
- insert :: forall t x proxy. Typeable t => proxy t -> Item x t -> TypeMap x -> TypeMap x
- lookup :: forall t x proxy. Typeable t => proxy t -> TypeMap x -> Maybe (Item x t)
- map :: forall x y. (forall t. Typeable t => Proxy t -> Item x t -> Item y t) -> TypeMap x -> TypeMap y
- 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)
- type family Typed x t
- type family UnTyped x
- data ItemFun x y
- data ItemKleisli f x y
- newtype WithTypeable x = WithTypeable (forall t. Typeable t => Proxy t -> Typed x t)
- withTypeable :: WithTypeable x -> (Proxy# a -> TypeRep) -> Proxy () -> UnTyped x
- withTypeRep :: forall x proxy. (forall t. Typeable t => Proxy t -> Typed x t) -> proxy x -> TypeRep -> UnTyped x
Exposed functions
Map from types t
of kind *
to values of type Item x t
.
An extensible type family mapping types (as keys) to types of values,
parameterized by types x
.
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
data ItemKleisli f x y Source #
type UnTyped (ItemKleisli f x y) Source # | |
type Typed (ItemKleisli f x y) t Source # | |
newtype WithTypeable x Source #
WithTypeable (forall t. Typeable t => Proxy t -> Typed x t) |
withTypeable :: WithTypeable x -> (Proxy# a -> TypeRep) -> Proxy () -> UnTyped x Source #