rec-def-0.2: Recursively defined values
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Recursive.Map

Description

The type RMap a b is like Map a b, but allows recursive definitions:

>>> :{
  let m1 = RM.insert 23 "Hello" m2
      m2 = RM.insert 42 "World" m1
  in RM.get m1
 :}
fromList [(23,"Hello"),(42,"World")]

All functions in this API are monotone with regard to the ordering of maps that uses the discrete order on its elements. Furthermore, we only include functions where the key set does not depend on the actual values of the maps.

This means that maps defined recursively using functions like insertWith can be used to construct cyclic data structures:

>>> :{
  let m = RM.insertWith (++) 23 "Hi" m
  in take 20 $ RM.get m M.! 23
 :}
"HiHiHiHiHiHiHiHiHiHi"

And because the APIs provided by this package work similar to cyclic data structures, we can use them inside these maps:

>>> :{
  let m = RM.insertWith RS.union 23 (RS.singleton "Hi") m
  in RM.get m
 :}
fromList [(23,fromList ["Hi"])]

I am looking for a concice but useful example for this feature to be put here!

An alternative would be to order these maps using a pointwise order on the maps of elements (and do a simple fixed-point iteration underneath). But then we could provide a general unionWith function, because not every function passed to it would be monotone.

Synopsis

Documentation

data RMap a b Source #

Like Map, but admits recursive definitions.

get :: RMap a b -> Map a b Source #

Extracts the value of a MSet

mk :: Map a b -> RMap a b Source #

RM.get (RM.mk m) === m

empty :: RMap a b Source #

RM.get RM.empty === M.empty

singleton :: a -> b -> RMap a b Source #

RM.get (RM.singleton k v) === M.singleton k v

insert :: Ord a => a -> b -> RMap a b -> RMap a b Source #

RM.get (RM.insert k v m) === M.insert k v (RM.get m)

insertWith :: Ord a => (b -> b -> b) -> a -> b -> RMap a b -> RMap a b Source #

RM.get (RM.insertWith (applyFun2 f) k v m) === M.insertWith (applyFun2 f) k v (RM.get m)

insertWithKey :: Ord a => (a -> b -> b -> b) -> a -> b -> RMap a b -> RMap a b Source #

RM.get (RM.insertWithKey (applyFun3 f) k v m) === M.insertWithKey (applyFun3 f) k v (RM.get m)

delete :: Ord a => a -> RMap a b -> RMap a b Source #

RM.get (RM.delete k m) === M.delete k (RM.get m)

adjust :: Ord a => (b -> b) -> a -> RMap a b -> RMap a b Source #

RM.get (RM.adjust (applyFun f) k m) === M.adjust (applyFun f) k (RM.get m)

adjustWithKey :: Ord a => (a -> b -> b) -> a -> RMap a b -> RMap a b Source #

RM.get (RM.adjustWithKey (applyFun2 f) k m) === M.adjustWithKey (applyFun2 f) k (RM.get m)

union :: Ord a => RMap a b -> RMap a b -> RMap a b Source #

RM.get (RM.union m1 m2) === M.union (RM.get m1) (RM.get m2)

unionWith :: Ord a => (b -> b -> b) -> RMap a b -> RMap a b -> RMap a b Source #

RM.get (RM.unionWith (applyFun2 f) m1 m2) === M.unionWith (applyFun2 f) (RM.get m1) (RM.get m2)

unionWithKey :: Ord a => (a -> b -> b -> b) -> RMap a b -> RMap a b -> RMap a b Source #

RM.get (RM.unionWithKey (applyFun3 f) m1 m2) === M.unionWithKey (applyFun3 f) (RM.get m1) (RM.get m2)

intersection :: Ord a => RMap a b -> RMap a b -> RMap a b Source #

RM.get (RM.intersection m1 m2) === M.intersection (RM.get m1) (RM.get m2)

intersectionWith :: Ord a => (b -> b -> b) -> RMap a b -> RMap a b -> RMap a b Source #

RM.get (RM.intersectionWith (applyFun2 f) m1 m2) === M.intersectionWith (applyFun2 f) (RM.get m1) (RM.get m2)

intersectionWithKey :: Ord a => (a -> b -> b -> b) -> RMap a b -> RMap a b -> RMap a b Source #

RM.get (RM.intersectionWithKey (applyFun3 f) m1 m2) === M.intersectionWithKey (applyFun3 f) (RM.get m1) (RM.get m2)

member :: Ord a => a -> RMap a b -> RBool Source #

RB.get (RM.member k m) === M.member k (RM.get m)

notMember :: Ord a => a -> RMap a b -> RDualBool Source #

RDB.get (RM.notMember n r1) === M.notMember n (RM.get r1)

disjoint :: Ord a => RMap a b -> RMap a b -> RDualBool Source #

RDB.get (RM.disjoint m1 m2) === M.disjoint (RM.get m1) (RM.get m2)

null :: Ord a => RMap a b -> RDualBool Source #

RDB.get (RM.null m) === M.null (RM.get m)

fromSet :: (a -> b) -> RSet a -> RMap a b Source #

RM.get (RM.singleton k v) === M.singleton k v

keysSet :: RMap a b -> RSet a Source #

RS.get (RM.keysSet m) === M.keysSet (RM.get m)

restrictKeys :: Ord a => RMap a b -> RSet a -> RMap a b Source #

RM.get (RM.restrictKeys m s) === M.restrictKeys (RM.get m) (RS.get s)