Safe Haskell | None |
---|---|
Language | Haskell2010 |
A hash map linking keys' and values' type parameters existentially.
Synopsis
- data HashMap10 k m
- data (k :: Type -> Type) :** (m :: Type -> Type) = (k a) :** (m a)
- empty :: HashMap10 k m
- insert :: forall a k m. (GEq k, Hashable1 k) => k a -> m a -> HashMap10 k m -> HashMap10 k m
- lookup :: forall a k m. (GEq k, Hashable1 k) => k a -> HashMap10 k m -> Maybe (m a)
- findWithDefault :: forall a k m. (GEq k, Hashable1 k) => m a -> k a -> HashMap10 k m -> m a
- toList :: HashMap10 k m -> [k :** m]
- fromList :: (GEq k, Hashable1 k) => [k :** m] -> HashMap10 k m
- type Hashable1 k = forall x. Hashable (k x)
- type Show1 k = forall x. Show (k x)
- type Portray1 k = forall x. Portray (k x)
- type Diff1 k = forall x. Diff (k x)
HashMap10
A "dependent" hash map, where elements' type parameters match their keys'.
Instances
data (k :: Type -> Type) :** (m :: Type -> Type) infixr 5 #
A pair of k a
and m a
for any (existential) a
.
This is a lot like a dependent pair, in that it contains a left-hand-side
value that's meant to identify a type, and a right-hand-side parameterized
by that type. For example, the true dependent pair type (in e.g. Idris)
(n :: Nat ** Vec n Bool)
could be approximated in Haskell as
SInt :** Ap10 Bool Vec
.
This can be used to represent one field of a Representable10
, where k
is
set to Rep10 f
. The k a
identifies which field (and locks down its
type), and the m a
provides its value.
(k a) :** (m a) infixr 5 |
Instances
Traversable10WithIndex ((:**) k :: (Type -> Type) -> Type) | |
Defined in Data.Ten.Sigma imapTraverse10 :: Applicative g => ((k :** n) -> r) -> (forall (a :: k0). Index10 ((:**) k) a -> m a -> g (n a)) -> (k :** m) -> g r # | |
Traversable10 ((:**) k :: (Type -> Type) -> Type) | |
Defined in Data.Ten.Sigma mapTraverse10 :: forall f m n r. Applicative f => ((k :** n) -> r) -> (forall (a :: k0). m a -> f (n a)) -> (k :** m) -> f r # | |
Foldable10WithIndex ((:**) k :: (Type -> Type) -> Type) | |
Defined in Data.Ten.Sigma | |
Functor10WithIndex ((:**) k :: (Type -> Type) -> Type) | |
Functor10 ((:**) k :: (Type -> Type) -> Type) | |
Defined in Data.Ten.Sigma | |
Foldable10 ((:**) k :: (Type -> Type) -> Type) | |
Defined in Data.Ten.Sigma | |
(GEq k, Entails k (Eq :!: m)) => Eq (k :** m) | |
(forall a. Show (k a), Entails k (Show :!: m)) => Show (k :** m) | |
(forall a. NFData (k a), Entails k (NFData :!: m)) => NFData (k :** m) | |
Defined in Data.Ten.Sigma | |
(forall a. Portray (k a), Entails k (Portray :!: m)) => Portray (k :** m) | |
Defined in Data.Ten.Sigma | |
(TestEquality k, forall a. Portray (k a), forall a. Diff (k a), Entails k (Portray :!: m), Entails k (Diff :!: m)) => Diff (k :** m) | |
type Index10 ((:**) k :: (Type -> Type) -> Type) | |
insert :: forall a k m. (GEq k, Hashable1 k) => k a -> m a -> HashMap10 k m -> HashMap10 k m Source #
Insert a new pair into a HashMap10
lookup :: forall a k m. (GEq k, Hashable1 k) => k a -> HashMap10 k m -> Maybe (m a) Source #
Find an entry based on its key, if present.
findWithDefault :: forall a k m. (GEq k, Hashable1 k) => m a -> k a -> HashMap10 k m -> m a Source #
Find an entry based on its key, or return the given fallback value.
fromList :: (GEq k, Hashable1 k) => [k :** m] -> HashMap10 k m Source #
Build a map from a list of (k :**
m) entries.