yarn-lock-0.4.0: Represent and parse yarn.lock files

MaintainerProfpatsch
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell2010

Data.MultiKeyedMap

Description

Still very much experimental and missing lots of functions and testing.

Internally, a MKMap is two maps, a keyMap referencing an intermediate key (whose type can be chosen freely and which is incremented sequentially), and a valueMap going from intermediate key to final value.

A correct implementation guarantees that

  1. the internal structure can’t be corrupted by operations declared safe
  2. adding and removing keys does not make values inaccessible (thus leaking memory) and doesn’t insert unnecessary values

Synopsis

Documentation

data MKMap k v Source #

A Map-like structure where multiple keys can point to the same value, with corresponding abstracted interface.

Internally, we use two maps connected by an intermediate key. The intermediate key (ik) can be anything implementing Ord (for Map), Bounded (to get the first value) and Enum (for succ).

Instances

Functor (MKMap k) Source # 

Methods

fmap :: (a -> b) -> MKMap k a -> MKMap k b #

(<$) :: a -> MKMap k b -> MKMap k a #

Foldable (MKMap k) Source # 

Methods

fold :: Monoid m => MKMap k m -> m #

foldMap :: Monoid m => (a -> m) -> MKMap k a -> m #

foldr :: (a -> b -> b) -> b -> MKMap k a -> b #

foldr' :: (a -> b -> b) -> b -> MKMap k a -> b #

foldl :: (b -> a -> b) -> b -> MKMap k a -> b #

foldl' :: (b -> a -> b) -> b -> MKMap k a -> b #

foldr1 :: (a -> a -> a) -> MKMap k a -> a #

foldl1 :: (a -> a -> a) -> MKMap k a -> a #

toList :: MKMap k a -> [a] #

null :: MKMap k a -> Bool #

length :: MKMap k a -> Int #

elem :: Eq a => a -> MKMap k a -> Bool #

maximum :: Ord a => MKMap k a -> a #

minimum :: Ord a => MKMap k a -> a #

sum :: Num a => MKMap k a -> a #

product :: Num a => MKMap k a -> a #

Traversable (MKMap k) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> MKMap k a -> f (MKMap k b) #

sequenceA :: Applicative f => MKMap k (f a) -> f (MKMap k a) #

mapM :: Monad m => (a -> m b) -> MKMap k a -> m (MKMap k b) #

sequence :: Monad m => MKMap k (m a) -> m (MKMap k a) #

(Eq k, Ord k, Eq v) => Eq (MKMap k v) Source # 

Methods

(==) :: MKMap k v -> MKMap k v -> Bool #

(/=) :: MKMap k v -> MKMap k v -> Bool #

(Show k, Show v) => Show (MKMap k v) Source # 

Methods

showsPrec :: Int -> MKMap k v -> ShowS #

show :: MKMap k v -> String #

showList :: [MKMap k v] -> ShowS #

at :: Ord k => MKMap k v -> k -> v Source #

Find value at key. Partial. See !.

(!) :: Ord k => MKMap k v -> k -> v infixl 9 Source #

Operator alias of at.

mkMKMap Source #

Arguments

:: (Ord k, Ord ik, Enum ik, Bounded ik) 
=> Proxy ik

type of intermediate key

-> MKMap k v

new map

Create a MKMap given a type for the internally used intermediate key.

fromList Source #

Arguments

:: (Ord k, Ord ik, Enum ik, Bounded ik) 
=> Proxy ik

type of intermediate key

-> [(NonEmpty k, v)]

list of (key, value)

-> MKMap k v

new map

Build a map from a list of key/value pairs.

toList :: MKMap k v -> [(NonEmpty k, v)] Source #

Convert the map to a list of key/value pairs.

insert :: Ord k => k -> v -> MKMap k v -> MKMap k v Source #

Equivalent to insert, if the key doesn’t exist a new singleton key is added.

flattenKeys :: Ord k => MKMap k v -> Map k v Source #

“Unlink” keys that are pointing to the same value.

Returns a normal map.

keys :: Ord k => MKMap k v -> [k] Source #

Return a list of all keys.

values :: MKMap k v -> [v] Source #

Return a list of all values.