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

PortabilityUses GHC extensions
Stabilityexperimental
Safe HaskellNone

Data.EnumMapSet

Contents

Description

Based on Data.IntSet, this module provides multi-dimensional sets of Enums. Keys are built using :& and terminated with S. They are stored using Ints so 2 keys that Enum to the same Int value will overwrite each other. The intension is that the Enum types will actually be newtype Ints.

 newtype AppleID = AppleID Int
 newtype TreeID = TreeID Int
 type Orchard = EnumMapSet (TreeID :& S AppleID)
 applePresent = member (TreeID 4 :& K AppleID 32) orchard

Synopsis

Documentation

type EnumMapSet k = EnumMapMap k ()Source

newtype S k Source

Keys are terminated with the S type.

 singleKey :: S Int
 singleKey = S 5

Constructors

S k 

Instances

Eq k => Eq (S k) 
Show k => Show (S k) 
(Eq (S k), Enum k, Eq k) => IsKey (S k) 
HasSKey (S k) 
Enum k => SubKeyS (K k) (S k) 
Enum k => SubKeyS (K k) (S k) 
Enum k => SubKey (S k) (S k) () 
(Enum k1, ~ * k1 k2) => SubKey (S k1) (:& k2 t2) () 
(Enum k1, ~ * k1 k2) => SubKeyS (:& k1 t) (S k2) 
(Enum k1, ~ * k1 k2) => SubKeyS (:& k1 t) (S k2) 

data k :& t Source

Multiple keys are joined by the (:&) constructor.

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

Constructors

!k :& !t 

Instances

(Enum k1, ~ * k1 k2) => SubKey (S k1) (:& k2 t2) () 
(Enum k1, ~ * k1 k2) => SubKey (K k1) (:& k2 t2) v 
(Enum k1, ~ * k1 k2) => SubKey (K k1) (:& k2 t2) v 
(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) 
(NFData k, NFData t) => NFData (:& k t) 
(Eq (:& k t), Eq k, Enum k, IsKey t, HasSKey t) => IsKey (:& k t) 
HasSKey t => HasSKey (:& k t) 
IsSplit (:& k t) Z 
IsSplit (:& k t) Z 
(Enum k1, ~ * k1 k2) => SubKeyS (:& k1 t) (S k2) 
(Enum k1, ~ * k1 k2) => SubKeyS (:& k1 t) (S k2) 
(IsSplit t n, Enum k) => IsSplit (:& k t) (N n) 
(Enum k, IsKey t1, IsKey t2, SubKeyS t1 t2) => SubKeyS (:& k t1) (:& k t2) 
(Enum k, IsKey t1, IsKey t2, SubKey t1 t2 v) => SubKey (:& k t1) (:& k t2) v 

Query

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

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

member :: (SubKey k1 k2 (), IsKey k1, IsKey k2) => k1 -> EnumMapSet k2 -> BoolSource

lookup :: (SubKey k1 k2 (), IsKey k1, IsKey k2) => k1 -> EnumMapSet k2 -> Maybe (Result k1 k2 ())Source

Lookup a subtree in an EnumMapSet.

 ems = fromList [1 :& 2 :& K 3, 1 :& 2 :& K 4]
 lookup (1 :& K 2) ems == fromList [K 3, K 4]
 lookup (1 :& 2 :& K 3) -- ERROR: Use 'member' to check for a key.

Construction

empty :: IsKey k => EnumMapSet kSource

singleton :: (IsKey k, SubKey k k (), Result k k () ~ ()) => k -> EnumMapSet kSource

insert :: (IsKey k, SubKey k k (), Result k k () ~ ()) => k -> EnumMapSet k -> EnumMapSet kSource

delete :: (SubKey k1 k2 (), IsKey k1, IsKey k2) => k1 -> EnumMapSet k2 -> EnumMapSet k2Source

Combine

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

Map

map :: (IsKey k1, IsKey k2, SubKey k2 k2 (), Result k2 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 :: IsKey k => (k -> t -> t) -> t -> EnumMapSet k -> tSource

Lists

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

fromList :: (IsKey k, SubKey k k (), Result k k () ~ ()) => [k] -> EnumMapSet kSource

keys :: IsKey k => EnumMapSet k -> [k]Source