Safe Haskell | None |
---|---|
Language | Haskell2010 |
Map
type used to represent records and unions
Synopsis
- data Map k v
- empty :: Ord k => Map k v
- singleton :: k -> v -> Map k v
- fromList :: Ord k => [(k, v)] -> Map k v
- fromListWithKey :: Ord k => (k -> v -> v -> v) -> [(k, v)] -> Map k v
- fromMap :: Map k v -> Map k v
- unorderedSingleton :: k -> v -> Map k v
- unorderedFromList :: Ord k => [(k, v)] -> Map k v
- sort :: Map k v -> Map k v
- isSorted :: Eq k => Map k v -> Bool
- insert :: Ord k => k -> v -> Map k v -> Map k v
- insertWith :: Ord k => (v -> v -> v) -> k -> v -> Map k v -> Map k v
- delete :: Ord k => k -> Map k v -> Map k v
- filter :: Ord k => (a -> Bool) -> Map k a -> Map k a
- partition :: Ord k => (a -> Bool) -> Map k a -> (Map k a, Map k a)
- restrictKeys :: Ord k => Map k a -> Set k -> Map k a
- withoutKeys :: Ord k => Map k a -> Set k -> Map k a
- mapMaybe :: Ord k => (a -> Maybe b) -> Map k a -> Map k b
- lookup :: Ord k => k -> Map k v -> Maybe v
- member :: Ord k => k -> Map k v -> Bool
- uncons :: Ord k => Map k v -> Maybe (k, v, Map k v)
- size :: Map k v -> Int
- union :: Ord k => Map k v -> Map k v -> Map k v
- unionWith :: Ord k => (v -> v -> v) -> Map k v -> Map k v -> Map k v
- outerJoin :: Ord k => (a -> c) -> (b -> c) -> (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
- intersection :: Ord k => Map k a -> Map k b -> Map k a
- intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c
- difference :: Ord k => Map k a -> Map k b -> Map k a
- mapWithKey :: (k -> a -> b) -> Map k a -> Map k b
- traverseWithKey :: Ord k => Applicative f => (k -> a -> f b) -> Map k a -> f (Map k b)
- unorderedTraverseWithKey :: Ord k => Applicative f => (k -> a -> f b) -> Map k a -> f (Map k b)
- unorderedTraverseWithKey_ :: Ord k => Applicative f => (k -> a -> f ()) -> Map k a -> f ()
- foldMapWithKey :: (Monoid m, Ord k) => (k -> a -> m) -> Map k a -> m
- toList :: Ord k => Map k v -> [(k, v)]
- toAscList :: Map k v -> [(k, v)]
- toMap :: Map k v -> Map k v
- keys :: Map k v -> [k]
- keysSet :: Map k v -> Set k
- elems :: Ord k => Map k v -> [v]
Type
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
(Lift k, Lift v) => Lift (Map k v :: Type) Source # | |
Functor (Map k) Source # | |
Ord k => Foldable (Map k) Source # | |
Defined in Dhall.Map fold :: Monoid m => Map k m -> m # foldMap :: Monoid m => (a -> m) -> Map k a -> 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 # elem :: Eq a => a -> Map k a -> Bool # maximum :: Ord a => Map k a -> a # minimum :: Ord a => Map k a -> a # | |
Ord k => Traversable (Map k) Source # | |
Ord k => IsList (Map k v) Source # | |
(Ord k, Eq v) => Eq (Map k v) Source # | |
(Data k, Data v, Ord k) => Data (Map k v) Source # | |
Defined in Dhall.Map 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 :: forall r r'. (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) # | |
(Ord k, Ord v) => Ord (Map k v) Source # |
|
(Show k, Show v, Ord k) => Show (Map k v) Source # | |
Generic (Map k v) Source # | |
Ord k => Semigroup (Map k v) Source # | \x y z -> x <> (y <> z) == (x <> y) <> (z :: Map Int Int) |
Ord k => Monoid (Map k v) Source # | \x -> x <> mempty == (x :: Map Int Int) \x -> mempty <> x == (x :: Map Int Int) |
(NFData k, NFData v) => NFData (Map k v) Source # | |
type Rep (Map k v) Source # | |
type Item (Map k v) Source # | |
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 [("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)]
Note that this handling of duplicates means that fromList
is not a monoid
homomorphism:
>>>
fromList [(1, True)] <> fromList [(1, False)]
fromList [(1,True)]>>>
fromList ([(1, True)] <> [(1, False)])
fromList [(1,False)]
fromListWithKey :: Ord k => (k -> v -> v -> v) -> [(k, v)] -> Map k v Source #
Create a Map
from a list of key-value pairs with a combining function.
>>>
fromListWithKey (\k v1 v2 -> k ++ v1 ++ v2) [("B","v1"),("A","v2"),("B","v3")]
fromList [("B","Bv3v1"),("A","v2")]
Constructing unordered Map
s
unorderedSingleton :: k -> v -> Map k v Source #
Create a Map
from a single key-value pair.
Any further operations on this map will not retain the order of the keys.
>>>
unorderedSingleton "A" 1
fromList [("A",1)]
unorderedFromList :: Ord k => [(k, v)] -> Map k v Source #
Create a Map
from a list of key-value pairs
Any further operations on this map will not retain the order of the keys.
>>>
unorderedFromList []
fromList []>>>
unorderedFromList [("B",1),("A",2)] -- The map /doesn't/ preserve order
fromList [("A",2),("B",1)]>>>
unorderedFromList [("A",1),("A",2)] -- For duplicates, later values take precedence
fromList [("A",2)]
Sorting
sort :: 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
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)]
partition :: Ord k => (a -> Bool) -> Map k a -> (Map k a, Map k a) Source #
Split the map into values that do and don't satisfy the predicate
>>>
partition even (fromList [("C",3),("B",2),("A",1)])
(fromList [("B",2)],fromList [("C",3),("A",1)])>>>
partition odd (fromList [("C",3),("B",2),("A",1)])
(fromList [("C",3),("A",1)],fromList [("B",2)])
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
Combine
unionWith :: Ord k => (v -> v -> v) -> Map k v -> Map k v -> Map k v Source #
Combine two Map
s 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)]
outerJoin :: Ord k => (a -> c) -> (b -> c) -> (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c Source #
A generalised unionWith
.
>>>
outerJoin Left Left (\k a b -> Right (k, a, b)) (fromList [("A",1),("B",2)]) (singleton "A" 3)
fromList [("A",Right ("A",1,3)),("B",Left 2)]
This function is much inspired by the Data.Semialign.Semialign class.
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)])
unorderedTraverseWithKey :: Ord k => Applicative f => (k -> a -> f b) -> Map k a -> f (Map k b) Source #
Same as traverseWithKey
, except that the order of effects is not
necessarily the same as the order of the keys
unorderedTraverseWithKey_ :: Ord k => Applicative f => (k -> a -> f ()) -> Map k a -> f () Source #
Traverse all of the key-value pairs in a Map
, not preserving their
original order, where the result of the computation can be forgotten.
Note that this is a strict traversal, fully traversing the map even when the Applicative is lazy in the remaining elements.
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)]
toAscList :: Map k v -> [(k, v)] Source #
Convert a Map
to a list of key-value pairs in ascending order of keys
keys :: Map k v -> [k] Source #
Return the keys from a Map
in their original order
>>>
keys (fromList [("B",1),("A",2)])
["B","A"]