ten-unordered-containers-0.1.0.1: A package providing one unordered container.
Safe HaskellNone
LanguageHaskell2010

Data.Ten.HashMap

Description

A hash map linking keys' and values' type parameters existentially.

Synopsis

HashMap10

data HashMap10 k m Source #

A "dependent" hash map, where elements' type parameters match their keys'.

Instances

Instances details
Traversable10WithIndex (HashMap10 k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.HashMap

Methods

imapTraverse10 :: Applicative g => (HashMap10 k n -> r) -> (forall (a :: k0). Index10 (HashMap10 k) a -> m a -> g (n a)) -> HashMap10 k m -> g r #

Traversable10 (HashMap10 k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.HashMap

Methods

mapTraverse10 :: forall f m n r. Applicative f => (HashMap10 k n -> r) -> (forall (a :: k0). m a -> f (n a)) -> HashMap10 k m -> f r #

Foldable10WithIndex (HashMap10 k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.HashMap

Methods

ifoldMap10 :: Monoid w => (forall (a :: k0). Index10 (HashMap10 k) a -> m a -> w) -> HashMap10 k m -> w #

Functor10WithIndex (HashMap10 k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.HashMap

Methods

imap10 :: (forall (a :: k0). Index10 (HashMap10 k) a -> m a -> n a) -> HashMap10 k m -> HashMap10 k n #

Functor10 (HashMap10 k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.HashMap

Methods

fmap10 :: (forall (a :: k0). m a -> n a) -> HashMap10 k m -> HashMap10 k n #

Foldable10 (HashMap10 k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.HashMap

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> HashMap10 k m -> w #

(GEq k, Hashable1 k) => IsList (HashMap10 k m) Source # 
Instance details

Defined in Data.Ten.HashMap

Associated Types

type Item (HashMap10 k m) #

Methods

fromList :: [Item (HashMap10 k m)] -> HashMap10 k m #

fromListN :: Int -> [Item (HashMap10 k m)] -> HashMap10 k m #

toList :: HashMap10 k m -> [Item (HashMap10 k m)] #

(GEq k, Entails k (Eq :!: m)) => Eq (HashMap10 k m) Source # 
Instance details

Defined in Data.Ten.HashMap

Methods

(==) :: HashMap10 k m -> HashMap10 k m -> Bool #

(/=) :: HashMap10 k m -> HashMap10 k m -> Bool #

(Show1 k, Entails k (Show :!: m)) => Show (HashMap10 k m) Source # 
Instance details

Defined in Data.Ten.HashMap

Methods

showsPrec :: Int -> HashMap10 k m -> ShowS #

show :: HashMap10 k m -> String #

showList :: [HashMap10 k m] -> ShowS #

(Portray1 k, Entails k (Portray :!: m)) => Portray (HashMap10 k m) Source # 
Instance details

Defined in Data.Ten.HashMap

Methods

portray :: HashMap10 k m -> Portrayal #

(TestEquality k, GEq k, Hashable1 k, Portray1 k, Diff1 k, Entails k (Portray :!: m), Entails k (Diff :!: m)) => Diff (HashMap10 k m) Source # 
Instance details

Defined in Data.Ten.HashMap

Methods

diff :: HashMap10 k m -> HashMap10 k m -> Maybe Portrayal #

Generic1 (HashMap10 k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.HashMap

Associated Types

type Rep1 (HashMap10 k) :: k -> Type #

Methods

from1 :: forall (a :: k0). HashMap10 k a -> Rep1 (HashMap10 k) a #

to1 :: forall (a :: k0). Rep1 (HashMap10 k) a -> HashMap10 k a #

type Index10 (HashMap10 k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.HashMap

type Index10 (HashMap10 k :: (Type -> Type) -> Type) = k
type Item (HashMap10 k m) Source # 
Instance details

Defined in Data.Ten.HashMap

type Item (HashMap10 k m) = k :** m
type Rep1 (HashMap10 k :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Ten.HashMap

type Rep1 (HashMap10 k :: (Type -> Type) -> Type) = D1 ('MetaData "HashMap10" "Data.Ten.HashMap" "ten-unordered-containers-0.1.0.1-inplace" 'True) (C1 ('MetaCons "HashMap10" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (HashMap (Exists k) :.: Rec1 ((:**) k))))

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.

Constructors

(k a) :** (m a) infixr 5 

Instances

Instances details
Traversable10WithIndex ((:**) k :: (Type -> Type) -> Type) 
Instance details

Defined in Data.Ten.Sigma

Methods

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) 
Instance details

Defined in Data.Ten.Sigma

Methods

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) 
Instance details

Defined in Data.Ten.Sigma

Methods

ifoldMap10 :: Monoid w => (forall (a :: k0). Index10 ((:**) k) a -> m a -> w) -> (k :** m) -> w #

Functor10WithIndex ((:**) k :: (Type -> Type) -> Type) 
Instance details

Defined in Data.Ten.Sigma

Methods

imap10 :: (forall (a :: k0). Index10 ((:**) k) a -> m a -> n a) -> (k :** m) -> k :** n #

Functor10 ((:**) k :: (Type -> Type) -> Type) 
Instance details

Defined in Data.Ten.Sigma

Methods

fmap10 :: (forall (a :: k0). m a -> n a) -> (k :** m) -> k :** n #

Foldable10 ((:**) k :: (Type -> Type) -> Type) 
Instance details

Defined in Data.Ten.Sigma

Methods

foldMap10 :: Monoid w => (forall (a :: k0). m a -> w) -> (k :** m) -> w #

(GEq k, Entails k (Eq :!: m)) => Eq (k :** m) 
Instance details

Defined in Data.Ten.Sigma

Methods

(==) :: (k :** m) -> (k :** m) -> Bool #

(/=) :: (k :** m) -> (k :** m) -> Bool #

(forall a. Show (k a), Entails k (Show :!: m)) => Show (k :** m) 
Instance details

Defined in Data.Ten.Sigma

Methods

showsPrec :: Int -> (k :** m) -> ShowS #

show :: (k :** m) -> String #

showList :: [k :** m] -> ShowS #

(forall a. NFData (k a), Entails k (NFData :!: m)) => NFData (k :** m) 
Instance details

Defined in Data.Ten.Sigma

Methods

rnf :: (k :** m) -> () #

(forall a. Portray (k a), Entails k (Portray :!: m)) => Portray (k :** m) 
Instance details

Defined in Data.Ten.Sigma

Methods

portray :: (k :** m) -> Portrayal #

(TestEquality k, forall a. Portray (k a), forall a. Diff (k a), Entails k (Portray :!: m), Entails k (Diff :!: m)) => Diff (k :** m) 
Instance details

Defined in Data.Ten.Sigma

Methods

diff :: (k :** m) -> (k :** m) -> Maybe Portrayal #

type Index10 ((:**) k :: (Type -> Type) -> Type) 
Instance details

Defined in Data.Ten.Sigma

type Index10 ((:**) k :: (Type -> Type) -> Type) = k

empty :: HashMap10 k m Source #

An empty HashMap10.

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.

toList :: HashMap10 k m -> [k :** m] Source #

Convert to a list of (:**) in unspecified order.

fromList :: (GEq k, Hashable1 k) => [k :** m] -> HashMap10 k m Source #

Build a map from a list of (k :** m) entries.

Miscellaneous

type Hashable1 k = forall x. Hashable (k x) Source #

type Show1 k = forall x. Show (k x) Source #

type Portray1 k = forall x. Portray (k x) Source #

type Diff1 k = forall x. Diff (k x) Source #