enummapmap-0.1.0: Map of maps using Enum types as keys

PortabilityUses GHC extensions
MaintainerStability : experimental
Safe HaskellNone

Data.EnumMapSet

Contents

Description

Based on Data.IntSet.

Synopsis

Documentation

type EnumMapSet k = EnumMapMap k ()Source

data K k Source

Keys are terminated with the K type

 singleKey :: K Int
 singleKey = K 5

Constructors

K !k 

Instances

Eq k => Eq (K k) 
Show k => Show (K k) 
Enum k => IsEmm (K k) 
Enum k => IsEmm (K k) 
Enum k => IsEmm (K k) 
Show v => Show (EnumMapMap (K k) v) 
Show v => Show (EnumMapMap (K k) v) 
NFData v => NFData (EnumMapMap (K k) v) 
NFData v => NFData (EnumMapMap (K k) v) 

data k :& t Source

Multiple keys are joined by the (:&) constructor and terminated with K.

 multiKey :: Int :& Int :& K Int
 multiKey = 5 :& 6 :& K 5

Constructors

!k :& !t 

Instances

(Eq k, Eq t) => Eq (:& k t) 
(Show v, Show (EnumMapMap t v)) => Show (EnumMapMap (:& k t) v) 
(Show k, Show t) => Show (:& k t) 
(NFData v, NFData (EnumMapMap t v)) => NFData (EnumMapMap (:& k t) v) 
(Enum k, IsEmm t) => IsEmm (:& k t) 
IsSplit (:& k t) Z 
IsSplit (:& k t) Z 
(IsSplit t n, Enum k) => IsSplit (:& k t) (N n) 

Query

null :: IsEmm k => EnumMapSet k -> BoolSource

size :: IsEmm k => EnumMapSet k -> IntSource

member :: IsEmm k => k -> EnumMapSet k -> BoolSource

Construction

empty :: IsEmm k => EnumMapSet kSource

singleton :: IsEmm k => k -> EnumMapSet kSource

insert :: IsEmm k => k -> EnumMapSet k -> EnumMapSet kSource

delete :: IsEmm k => k -> EnumMapSet k -> EnumMapSet kSource

Combine

union :: IsEmm k => EnumMapSet k -> EnumMapSet k -> EnumMapSet kSource

Map

map :: (IsEmm k1, IsEmm k2) => (k1 -> k2) -> EnumMapSet k1 -> EnumMapSet k2Source

map f s is the set obtained by applying f to each element of s.

It's worth noting that the size of the result may be smaller if, for some (x,y), x /= y && f x == f y

Folds

foldr :: IsEmm k => (k -> t -> t) -> t -> EnumMapSet k -> tSource

Lists

toList :: IsEmm k => EnumMapSet k -> [k]Source

fromList :: IsEmm k => [k] -> EnumMapSet kSource