Copyright | (c) Daan Leijen 2002 (c) Joachim Breitner 2011 (c) Matthew West 2012 |
---|---|
License | BSD-style |
Stability | experimental |
Portability | Uses GHC extensions |
Safe Haskell | None |
Language | Haskell2010 |
Based on Data.IntSet, this module provides multi-dimensional sets of
Enums
. Keys are built using :&
and terminated with S
. They are stored
using Int
s 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
s.Int
newtype AppleID = AppleID Int newtype TreeID = TreeID Int type Orchard = EnumMapSet (TreeID :& S AppleID) applePresent = member (TreeID 4 :& K AppleID 32) orchard
- type EnumMapSet k = EnumMapMap k ()
- newtype S k = S k
- data k :& t = !k :& !t
- class Eq k => IsKey k
- class SubKey k1 k2 v where
- type Result k1 k2 v :: *
- null :: IsKey k => EnumMapSet k -> Bool
- size :: IsKey k => EnumMapSet k -> Int
- member :: (SubKey k1 k2 (), IsKey k1, IsKey k2) => k1 -> EnumMapSet k2 -> Bool
- lookup :: (SubKey k1 k2 (), IsKey k1, IsKey k2) => k1 -> EnumMapSet k2 -> Maybe (Result k1 k2 ())
- empty :: IsKey k => EnumMapSet k
- singleton :: (IsKey k, SubKey k k (), Result k k () ~ ()) => k -> EnumMapSet k
- insert :: (IsKey k, SubKey k k (), Result k k () ~ ()) => k -> EnumMapSet k -> EnumMapSet k
- delete :: (SubKey k1 k2 (), IsKey k1, IsKey k2) => k1 -> EnumMapSet k2 -> EnumMapSet k2
- union :: IsKey k => EnumMapSet k -> EnumMapSet k -> EnumMapSet k
- difference :: IsKey k => EnumMapSet k -> EnumMapSet k -> EnumMapSet k
- intersection :: IsKey k => EnumMapSet k -> EnumMapSet k -> EnumMapSet k
- map :: (IsKey k1, IsKey k2, SubKey k2 k2 (), Result k2 k2 () ~ ()) => (k1 -> k2) -> EnumMapSet k1 -> EnumMapSet k2
- foldr :: IsKey k => (k -> t -> t) -> t -> EnumMapSet k -> t
- all :: IsKey k => (k -> Bool) -> EnumMapSet k -> Bool
- toList :: IsKey k => EnumMapSet k -> [k]
- fromList :: (IsKey k, SubKey k k (), Result k k () ~ ()) => [k] -> EnumMapSet k
- keys :: IsKey k => EnumMapSet k -> [k]
- findMin :: IsKey k => EnumMapSet k -> k
- minView :: IsKey k => EnumMapSet k -> Maybe (k, EnumMapSet k)
- deleteFindMin :: IsKey k => EnumMapSet k -> (k, EnumMapSet k)
Documentation
type EnumMapSet k = EnumMapMap k () Source
Keys are terminated with the S
type.
singleKey :: S Int singleKey = S 5
S k |
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 |
Multiple keys are joined by the (:&
) constructor.
multiKey :: Int :& Int :& K Int multiKey = 5 :& 6 :& K 5
!k :& !t infixr 3 |
(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 |
emptySubTrees, emptySubTrees_, removeEmpties, unsafeJoinKey, empty, null, size, alter, mapMaybeWithKey, mapWithKey, traverseWithKey, foldr, foldrWithKey, keysSet, fromSet, findMin, minViewWithKey, union, unionWithKey, difference, differenceWithKey, intersection, intersectionWithKey, equal, nequal
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
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
null :: IsKey k => EnumMapSet k -> Bool Source
size :: IsKey k => EnumMapSet k -> Int 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
empty :: IsKey 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
union :: IsKey k => EnumMapSet k -> EnumMapSet k -> EnumMapSet k Source
difference :: IsKey k => EnumMapSet k -> EnumMapSet k -> EnumMapSet k Source
intersection :: IsKey k => EnumMapSet k -> EnumMapSet k -> EnumMapSet k Source
Map
map :: (IsKey k1, IsKey k2, SubKey k2 k2 (), Result k2 k2 () ~ ()) => (k1 -> k2) -> EnumMapSet k1 -> EnumMapSet k2 Source
is the set obtained by applying map
f sf
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
Lists
toList :: IsKey k => EnumMapSet k -> [k] Source
keys :: IsKey k => EnumMapSet k -> [k] Source
Min/Max
findMin :: IsKey k => EnumMapSet k -> k Source
minView :: IsKey k => EnumMapSet k -> Maybe (k, EnumMapSet k) Source
deleteFindMin :: IsKey k => EnumMapSet k -> (k, EnumMapSet k) Source