dhall-1.19.1: A configuration language guaranteed to terminate

Safe HaskellNone
LanguageHaskell2010

Dhall.Map

Contents

Description

Map type used to represent records and unions

Synopsis

Type

data Map k v Source #

A Map that remembers the original ordering of keys

This is primarily used so that formatting preserves field order

This is done primarily to avoid a dependency on insert-ordered-containers and also to improve performance

Instances
Functor (Map k) Source # 
Instance details

Defined in Dhall.Map

Methods

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

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

Foldable (Map k) Source # 
Instance details

Defined in Dhall.Map

Methods

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

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

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

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

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

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

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

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

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

null :: Map k a -> Bool #

length :: Map k a -> Int #

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

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

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

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

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

Traversable (Map k) Source # 
Instance details

Defined in Dhall.Map

Methods

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

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

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

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

Ord k => IsList (Map k v) Source # 
Instance details

Defined in Dhall.Map

Associated Types

type Item (Map k v) :: Type #

Methods

fromList :: [Item (Map k v)] -> Map k v #

fromListN :: Int -> [Item (Map k v)] -> Map k v #

toList :: Map k v -> [Item (Map k v)] #

(Eq k, Eq v) => Eq (Map k v) Source # 
Instance details

Defined in Dhall.Map

Methods

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

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

(Data k, Data v, Ord k) => Data (Map k v) Source # 
Instance details

Defined in Dhall.Map

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k v -> c (Map k v) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k v) #

toConstr :: Map k v -> Constr #

dataTypeOf :: Map k v -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k v)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k v)) #

gmapT :: (forall b. Data b => b -> b) -> Map k v -> Map k v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k v -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k v -> r #

gmapQ :: (forall d. Data d => d -> u) -> Map k v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k v -> m (Map k v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k v -> m (Map k v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k v -> m (Map k v) #

(Show k, Show v, Ord k) => Show (Map k v) Source # 
Instance details

Defined in Dhall.Map

Methods

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

show :: Map k v -> String #

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

Ord k => Semigroup (Map k v) Source # 
Instance details

Defined in Dhall.Map

Methods

(<>) :: Map k v -> Map k v -> Map k v #

sconcat :: NonEmpty (Map k v) -> Map k v #

stimes :: Integral b => b -> Map k v -> Map k v #

Ord k => Monoid (Map k v) Source # 
Instance details

Defined in Dhall.Map

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

type Item (Map k v) Source # 
Instance details

Defined in Dhall.Map

type Item (Map k v) = (k, v)

Construction

singleton :: k -> v -> Map k v Source #

Create a Map from a single key-value pair

>>> singleton "A" 1
fromList [("A",1)]

fromList :: Ord k => [(k, v)] -> Map k v Source #

Create a Map from a list of key-value pairs

fromList empty = mempty

fromList (x <|> y) = fromList x <> fromList y
>>> fromList [("B",1),("A",2)]  -- The map preserves order
fromList [("B",1),("A",2)]
>>> fromList [("A",1),("A",2)]  -- For duplicates, later values take precedence
fromList [("A",2)]

Sorting

sort :: Ord k => Map k v -> Map k v Source #

Sort the keys of a Map, forgetting the original ordering

sort (sort x) = sort x
>>> sort (fromList [("B",1),("A",2)])
fromList [("A",2),("B",1)]

isSorted :: Eq k => Map k v -> Bool Source #

Check if the keys of a Map are already sorted

isSorted (sort m) = True
>>> isSorted (fromList [("B",1),("A",2)])  -- Sortedness is based only on keys
False
>>> isSorted (fromList [("A",2),("B",1)])
True

Insertion

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

Insert a key-value pair into a Map, overriding any previous value stored underneath the same key, if present

insert = insertWith (\v _ -> v)
>>> insert "C" 1 (fromList [("B",2),("A",3)])  -- Values are inserted on left
fromList [("C",1),("B",2),("A",3)]
>>> insert "C" 1 (fromList [("C",2),("A",3)])  -- New value takes precedence
fromList [("C",1),("A",3)]

insertWith :: Ord k => (v -> v -> v) -> k -> v -> Map k v -> Map k v Source #

Insert a key-value pair into a Map, using the supplied function to combine the new value with any old value underneath the same key, if present

>>> insertWith (+) "C" 1 (fromList [("B",2),("A",3)])  -- No collision
fromList [("C",1),("B",2),("A",3)]
>>> insertWith (+) "C" 1 (fromList [("C",2),("A",3)])  -- Collision
fromList [("C",3),("A",3)]

Deletion/Update

delete :: Ord k => k -> Map k v -> Map k v Source #

Delete a key from a Map if present, otherwise return the original Map

>>> delete "B" (fromList [("C",1),("B",2),("A",3)])
fromList [("C",1),("A",3)]
>>> delete "D" (fromList [("C",1),("B",2),("A",3)])
fromList [("C",1),("B",2),("A",3)]

filter :: Ord k => (a -> Bool) -> Map k a -> Map k a Source #

Keep all values that satisfy the given predicate

>>> filter even (fromList [("C",3),("B",2),("A",1)])
fromList [("B",2)]
>>> filter odd (fromList [("C",3),("B",2),("A",1)])
fromList [("C",3),("A",1)]

mapMaybe :: Ord k => (a -> Maybe b) -> Map k a -> Map k b Source #

Transform all values in a Map using the supplied function, deleting the key if the function returns Nothing

>>> mapMaybe Data.Maybe.listToMaybe (fromList [("C",[1]),("B",[]),("A",[3])])
fromList [("C",1),("A",3)]

Query

lookup :: Ord k => k -> Map k v -> Maybe v Source #

Retrieve a key from a Map

lookup k mempty = empty

lookup k (x <> y) = lookup k y <|> lookup k x
>>> lookup "A" (fromList [("B",1),("A",2)])
Just 2
>>> lookup "C" (fromList [("B",1),("A",2)])
Nothing

member :: Ord k => k -> Map k v -> Bool Source #

Check if a key belongs to a Map

member k mempty = False

member k (x <> y) = member k x || member k y
>>> member "A" (fromList [("B",1),("A",2)])
True
>>> member "C" (fromList [("B",1),("A",2)])
False

uncons :: Ord k => Map k v -> Maybe (k, v, Map k v) Source #

Retrieve the first key, value of the Map, if present, and also returning the rest of the Map.

uncons mempty = empty

uncons (singleton k v) = (k, v, mempty)
>>> uncons (fromList [("C",1),("B",2),("A",3)])
Just ("C",1,fromList [("B",2),("A",3)])
>>> uncons (fromList [])
Nothing

Combine

union :: Ord k => Map k v -> Map k v -> Map k v Source #

Combine two Maps, preferring keys from the first Map

union = unionWith (\v _ -> v)
>>> union (fromList [("D",1),("C",2)]) (fromList [("B",3),("A",4)])
fromList [("D",1),("C",2),("B",3),("A",4)]
>>> union (fromList [("D",1),("C",2)]) (fromList [("C",3),("A",4)])
fromList [("D",1),("C",2),("A",4)]

unionWith :: Ord k => (v -> v -> v) -> Map k v -> Map k v -> Map k v Source #

Combine two Maps using a combining function for colliding keys

>>> unionWith (+) (fromList [("D",1),("C",2)]) (fromList [("B",3),("A",4)])
fromList [("D",1),("C",2),("B",3),("A",4)]
>>> unionWith (+) (fromList [("D",1),("C",2)]) (fromList [("C",3),("A",4)])
fromList [("D",1),("C",5),("A",4)]

intersection :: Ord k => Map k a -> Map k b -> Map k a Source #

Combine two Map on their shared keys, keeping the value from the first Map

intersection = intersectionWith (\v _ -> v)
>>> intersection (fromList [("C",1),("B",2)]) (fromList [("B",3),("A",4)])
fromList [("B",2)]

intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c Source #

Combine two Maps on their shared keys, using the supplied function to combine values from the first and second Map

>>> intersectionWith (+) (fromList [("C",1),("B",2)]) (fromList [("B",3),("A",4)])
fromList [("B",5)]

difference :: Ord k => Map k a -> Map k b -> Map k a Source #

Compute the difference of two Maps by subtracting all keys from the second Map from the first Map

>>> difference (fromList [("C",1),("B",2)]) (fromList [("B",3),("A",4)])
fromList [("C",1)]

Traversals

mapWithKey :: (k -> a -> b) -> Map k a -> Map k b Source #

Transform the values of a Map using their corresponding key

mapWithKey (pure id) = id

mapWithKey (liftA2 (.) f g) = mapWithKey f . mapWithKey g
mapWithKey f mempty = mempty

mapWithKey f (x <> y) = mapWithKey f x <> mapWithKey f y
>>> mapWithKey (,) (fromList [("B",1),("A",2)])
fromList [("B",("B",1)),("A",("A",2))]

traverseWithKey :: Ord k => Applicative f => (k -> a -> f b) -> Map k a -> f (Map k b) Source #

Traverse all of the key-value pairs in a Map, in their original order

>>> traverseWithKey (,) (fromList [("B",1),("A",2)])
("BA",fromList [("B",1),("A",2)])

traverseWithKey_ :: Ord k => Applicative f => (k -> a -> f ()) -> Map k a -> f () Source #

Traverse all of the key-value pairs in a Map, in their original order where the result of the computation can be forgotten.

>>> traverseWithKey_ (\k v -> print (k, v)) (fromList [("B",1),("A",2)])
("B",1)
("A",2)

foldMapWithKey :: (Monoid m, Ord k) => (k -> a -> m) -> Map k a -> m Source #

Fold all of the key-value pairs in a Map, in their original order

>>> foldMapWithKey (,) (fromList [("B",[1]),("A",[2])])
("BA",[1,2])

Conversions

toList :: Ord k => Map k v -> [(k, v)] Source #

Convert a Map to a list of key-value pairs in the original order of keys

>>> toList (fromList [("B",1),("A",2)])
[("B",1),("A",2)]

toMap :: Map k v -> Map k v Source #

Convert a Dhall.Map.Map to a Data.Map.Map

>>> toMap (fromList [("B",1),("A",2)]) -- Order is lost upon conversion
fromList [("A",2),("B",1)]

keys :: Map k v -> [k] Source #

Return the keys from a Map in their original order

>>> keys (fromList [("B",1),("A",2)])
["B","A"]