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

Copyright(c) Daan Leijen 2002 (c) Joachim Breitner 2011 (c) Matthew West 2012
LicenseBSD-style
Stabilityexperimental
PortabilityUses GHC extensions
Safe HaskellNone
LanguageHaskell2010

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

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) 
Enum s => SafeCopy (S s) 
(SafeCopy (S k), IsKey (S k), (~) * (Result (S k) (S k) ()) (), SubKey (S k) (S k) ()) => SafeCopy (EnumMapSet (S k)) 
(Enum k, Eq k) => IsKey (S k) 
Enum k => SubKey (S k) (S k) () 
(Enum k1, (~) * k1 k2) => SubKey (S k1) ((:&) k2 t2) () 
Show v => Show (EnumMapMap (S k) v) 
Typeable (* -> *) S 
data EnumMapMap (S k) = KSC (EMS k) 
type Result (S k) (S k) () = () 
type Result (S k1) ((:&) k2 t2) () = EnumMapSet t2 

data k :& t infixr 3 Source

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

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

Constructors

!k :& !t infixr 3 

Instances

(Foldable (EnumMapMap t), Enum k, Eq k, IsKey t, HasSKey t) => Foldable (EnumMapMap ((:&) k t)) 
(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) 
(Enum a, SafeCopy b) => SafeCopy ((:&) a b) 
(Eq k, Enum k, IsKey t, HasSKey t) => IsKey ((:&) k t) 
Typeable (* -> * -> *) (:&) 
(Enum k, IsKey t1, IsKey t2, SubKey t1 t2 v) => SubKey ((:&) k t1) ((:&) k t2) v 
type Result (S k1) ((:&) k2 t2) () = EnumMapSet t2 
type Result (K k1) ((:&) k2 t2) v = EnumMapMap t2 v 
type Result (K k1) ((:&) k2 t2) v = EnumMapMap t2 v 
data EnumMapMap ((:&) k t) = KCC (EMM k (EnumMapMap t v)) 
type Result ((:&) k t1) ((:&) k t2) v = Result t1 t2 v 

class Eq k => IsKey k Source

Instances

(Enum k, Eq k) => IsKey (S k) 
(Enum k, Eq k) => IsKey (K k) 
(Enum k, Eq k) => IsKey (K k) 
(Eq k, Enum k, IsKey t, HasSKey t) => IsKey ((:&) k t) 

class SubKey k1 k2 v Source

Minimal complete definition

member, singleton, lookup, insert, insertWithKey, delete

Associated Types

type Result k1 k2 v :: * Source

k1 should be a prefix of k2. If k1 ~ k2 then the Result will be v.

Result (K ID1) (ID1 :& K ID2) v        ~ EnumMapMap (K ID2) v
Result (ID1 :& K ID2) (ID1 :& K ID2) v ~ v
Result (ID1 :& K ID2) (K ID1) v        -- ERROR
Result (ID2 :& K ID1) (ID1 :& K ID2)   -- ERROR

Instances

Enum k => SubKey (S k) (S k) () 
Enum k => SubKey (K k) (K k) v 
Enum k => SubKey (K k) (K k) v 
(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 
(Enum k, IsKey t1, IsKey t2, SubKey t1 t2 v) => SubKey ((:&) k t1) ((:&) k t2) v 

Query

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

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

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

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

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

Combine

Map

map :: (IsKey k1, IsKey k2, SubKey k2 k2 (), Result k2 k2 () ~ ()) => (k1 -> k2) -> EnumMapSet k1 -> EnumMapSet k2 Source

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 -> t Source

all :: IsKey k => (k -> Bool) -> EnumMapSet k -> Bool Source

Lists

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

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

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

Min/Max