| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Data.Aeson.KeyMap
Description
An abstract interface for maps from JSON keys to values.
Since: 2.0.0.0
Synopsis
- data KeyMap v
- null :: KeyMap v -> Bool
- lookup :: Key -> KeyMap v -> Maybe v
- (!?) :: KeyMap v -> Key -> Maybe v
- size :: KeyMap v -> Int
- member :: Key -> KeyMap a -> Bool
- empty :: KeyMap v
- singleton :: Key -> v -> KeyMap v
- insert :: Key -> v -> KeyMap v -> KeyMap v
- insertWith :: (a -> a -> a) -> Key -> a -> KeyMap a -> KeyMap a
- delete :: Key -> KeyMap v -> KeyMap v
- alterF :: Functor f => (Maybe v -> f (Maybe v)) -> Key -> KeyMap v -> f (KeyMap v)
- difference :: KeyMap v -> KeyMap v' -> KeyMap v
- union :: KeyMap v -> KeyMap v -> KeyMap v
- unionWith :: (v -> v -> v) -> KeyMap v -> KeyMap v -> KeyMap v
- unionWithKey :: (Key -> v -> v -> v) -> KeyMap v -> KeyMap v -> KeyMap v
- intersection :: KeyMap a -> KeyMap b -> KeyMap a
- intersectionWith :: (a -> b -> c) -> KeyMap a -> KeyMap b -> KeyMap c
- intersectionWithKey :: (Key -> a -> b -> c) -> KeyMap a -> KeyMap b -> KeyMap c
- alignWith :: (These a b -> c) -> KeyMap a -> KeyMap b -> KeyMap c
- alignWithKey :: (Key -> These a b -> c) -> KeyMap a -> KeyMap b -> KeyMap c
- fromList :: [(Key, v)] -> KeyMap v
- fromListWith :: (v -> v -> v) -> [(Key, v)] -> KeyMap v
- toList :: KeyMap v -> [(Key, v)]
- toAscList :: KeyMap v -> [(Key, v)]
- elems :: KeyMap v -> [v]
- fromHashMap :: HashMap Key v -> KeyMap v
- toHashMap :: KeyMap v -> HashMap Key v
- fromHashMapText :: HashMap Text v -> KeyMap v
- toHashMapText :: KeyMap v -> HashMap Text v
- coercionToHashMap :: Maybe (Coercion (HashMap Key v) (KeyMap v))
- fromMap :: Map Key v -> KeyMap v
- toMap :: KeyMap v -> Map Key v
- fromMapText :: Map Text v -> KeyMap v
- toMapText :: KeyMap v -> Map Text v
- coercionToMap :: Maybe (Coercion (Map Key v) (KeyMap v))
- map :: (a -> b) -> KeyMap a -> KeyMap b
- mapWithKey :: (Key -> a -> b) -> KeyMap a -> KeyMap b
- mapKeyVal :: (Key -> Key) -> (v1 -> v2) -> KeyMap v1 -> KeyMap v2
- traverse :: Applicative f => (v1 -> f v2) -> KeyMap v1 -> f (KeyMap v2)
- traverseWithKey :: Applicative f => (Key -> v1 -> f v2) -> KeyMap v1 -> f (KeyMap v2)
- foldr :: (a -> b -> b) -> b -> KeyMap a -> b
- foldr' :: (a -> b -> b) -> b -> KeyMap a -> b
- foldl :: (b -> a -> b) -> b -> KeyMap a -> b
- foldl' :: (b -> a -> b) -> b -> KeyMap a -> b
- foldMapWithKey :: Monoid m => (Key -> a -> m) -> KeyMap a -> m
- foldrWithKey :: (Key -> v -> a -> a) -> a -> KeyMap v -> a
- keys :: KeyMap v -> [Key]
- filter :: (v -> Bool) -> KeyMap v -> KeyMap v
- filterWithKey :: (Key -> v -> Bool) -> KeyMap v -> KeyMap v
- mapMaybe :: (a -> Maybe b) -> KeyMap a -> KeyMap b
- mapMaybeWithKey :: (Key -> v -> Maybe u) -> KeyMap v -> KeyMap u
- data Key
Map Type
A map from JSON key type Key to v.
Instances
| Arbitrary1 KeyMap Source # | Since: 2.0.3.0 | 
| Defined in Data.Aeson.KeyMap Methods liftArbitrary :: Gen a -> Gen (KeyMap a) # liftShrink :: (a -> [a]) -> KeyMap a -> [KeyMap a] # | |
| FromJSON1 KeyMap Source # | Since: 2.0.1.0 | 
| Defined in Data.Aeson.Types.FromJSON | |
| ToJSON1 KeyMap Source # | |
| Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> KeyMap a -> Value Source # liftToJSONList :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> [KeyMap a] -> Value Source # liftToEncoding :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> KeyMap a -> Encoding Source # liftToEncodingList :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> [KeyMap a] -> Encoding Source # | |
| Foldable KeyMap Source # | |
| Defined in Data.Aeson.KeyMap Methods fold :: Monoid m => KeyMap m -> m # foldMap :: Monoid m => (a -> m) -> KeyMap a -> m # foldMap' :: Monoid m => (a -> m) -> KeyMap a -> m # foldr :: (a -> b -> b) -> b -> KeyMap a -> b # foldr' :: (a -> b -> b) -> b -> KeyMap a -> b # foldl :: (b -> a -> b) -> b -> KeyMap a -> b # foldl' :: (b -> a -> b) -> b -> KeyMap a -> b # foldr1 :: (a -> a -> a) -> KeyMap a -> a # foldl1 :: (a -> a -> a) -> KeyMap a -> a # elem :: Eq a => a -> KeyMap a -> Bool # maximum :: Ord a => KeyMap a -> a # minimum :: Ord a => KeyMap a -> a # | |
| Traversable KeyMap Source # | |
| Functor KeyMap Source # | |
| Align KeyMap Source # | |
| Defined in Data.Aeson.KeyMap | |
| Semialign KeyMap Source # | |
| Zip KeyMap Source # | |
| Filterable KeyMap Source # | |
| Witherable KeyMap Source # | |
| Defined in Data.Aeson.KeyMap Methods wither :: Applicative f => (a -> f (Maybe b)) -> KeyMap a -> f (KeyMap b) # witherM :: Monad m => (a -> m (Maybe b)) -> KeyMap a -> m (KeyMap b) # filterA :: Applicative f => (a -> f Bool) -> KeyMap a -> f (KeyMap a) # witherMap :: Applicative m => (KeyMap b -> r) -> (a -> m (Maybe b)) -> KeyMap a -> m r # | |
| FoldableWithIndex Key KeyMap Source # | |
| Defined in Data.Aeson.KeyMap | |
| FunctorWithIndex Key KeyMap Source # | |
| TraversableWithIndex Key KeyMap Source # | |
| Defined in Data.Aeson.KeyMap | |
| SemialignWithIndex Key KeyMap Source # | |
| Defined in Data.Aeson.KeyMap | |
| ZipWithIndex Key KeyMap Source # | |
| FilterableWithIndex Key KeyMap Source # | |
| WitherableWithIndex Key KeyMap Source # | |
| value ~ Value => KeyValue Value (KeyMap value) Source # | Constructs a singleton  | 
| value ~ Value => KeyValueOmit Value (KeyMap value) Source # | |
| Lift v => Lift (KeyMap v :: TYPE LiftedRep) Source # | |
| Arbitrary v => Arbitrary (KeyMap v) Source # | Since: 2.0.3.0 | 
| CoArbitrary v => CoArbitrary (KeyMap v) Source # | Since: 2.0.3.0 | 
| Defined in Data.Aeson.KeyMap Methods coarbitrary :: KeyMap v -> Gen b -> Gen b # | |
| Function v => Function (KeyMap v) Source # | Since: 2.0.3.0 | 
| FromJSON v => FromJSON (KeyMap v) Source # | Since: 2.0.1.0 | 
| ToJSON v => ToJSON (KeyMap v) Source # | |
| Data v => Data (KeyMap v) Source # | |
| Defined in Data.Aeson.KeyMap Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeyMap v -> c (KeyMap v) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (KeyMap v) # toConstr :: KeyMap v -> Constr # dataTypeOf :: KeyMap v -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (KeyMap v)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (KeyMap v)) # gmapT :: (forall b. Data b => b -> b) -> KeyMap v -> KeyMap v # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeyMap v -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeyMap v -> r # gmapQ :: (forall d. Data d => d -> u) -> KeyMap v -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> KeyMap v -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeyMap v -> m (KeyMap v) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyMap v -> m (KeyMap v) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeyMap v -> m (KeyMap v) # | |
| Monoid (KeyMap v) Source # | |
| Semigroup (KeyMap v) Source # | |
| IsList (KeyMap v) Source # | Since: 2.0.2.0 | 
| Read v => Read (KeyMap v) Source # | |
| Show v => Show (KeyMap v) Source # | |
| NFData v => NFData (KeyMap v) Source # | |
| Defined in Data.Aeson.KeyMap | |
| Eq v => Eq (KeyMap v) Source # | |
| Ord v => Ord (KeyMap v) Source # | |
| Defined in Data.Aeson.KeyMap | |
| Hashable v => Hashable (KeyMap v) Source # | |
| Defined in Data.Aeson.KeyMap | |
| type Item (KeyMap v) Source # | |
| Defined in Data.Aeson.KeyMap | |
Query
lookup :: Key -> KeyMap v -> Maybe v Source #
Return the value to which the specified key is mapped, or Nothing if this map contains no mapping for the key.
(!?) :: KeyMap v -> Key -> Maybe v Source #
Return the value to which the specified key is mapped, or Nothing if this map contains no mapping for the key.
This is a flipped version of lookup.
Since: 2.1.1.0
Construction
Insertion
insert :: Key -> v -> KeyMap v -> KeyMap v Source #
Associate the specified value with the specified key in this map. If this map previously contained a mapping for the key, the old value is replaced.
insertWith :: (a -> a -> a) -> Key -> a -> KeyMap a -> KeyMap a Source #
Insert with a function combining new and old values, taken in that order.
Since: 2.1.1.0
Deletion
delete :: Key -> KeyMap v -> KeyMap v Source #
Remove the mapping for the specified key from this map if present.
Update
alterF :: Functor f => (Maybe v -> f (Maybe v)) -> Key -> KeyMap v -> f (KeyMap v) Source #
alterF can be used to insert, delete, or update a value in a map.
Combine
difference :: KeyMap v -> KeyMap v' -> KeyMap v Source #
Difference of two maps. Return elements of the first map not existing in the second.
unionWith :: (v -> v -> v) -> KeyMap v -> KeyMap v -> KeyMap v Source #
The union with a combining function.
unionWithKey :: (Key -> v -> v -> v) -> KeyMap v -> KeyMap v -> KeyMap v Source #
The union with a combining function.
intersection :: KeyMap a -> KeyMap b -> KeyMap a Source #
The (left-biased) intersection of two maps (based on keys).
intersectionWith :: (a -> b -> c) -> KeyMap a -> KeyMap b -> KeyMap c Source #
The intersection with a combining function.
intersectionWithKey :: (Key -> a -> b -> c) -> KeyMap a -> KeyMap b -> KeyMap c Source #
The intersection with a combining function.
alignWith :: (These a b -> c) -> KeyMap a -> KeyMap b -> KeyMap c Source #
Generalized union with combining function.
alignWithKey :: (Key -> These a b -> c) -> KeyMap a -> KeyMap b -> KeyMap c Source #
Generalized union with combining function.
Lists
fromList :: [(Key, v)] -> KeyMap v Source #
Construct a map with the supplied mappings. If the list contains duplicate mappings, the later mappings take precedence.
>>>fromList [("a", 'x'), ("a", 'y')]fromList [("a",'y')]
fromListWith :: (v -> v -> v) -> [(Key, v)] -> KeyMap v Source #
Construct a map from a list of elements. Uses the provided function, f, to merge duplicate entries with (f newVal oldVal).
toList :: KeyMap v -> [(Key, v)] Source #
Return a list of this map's keys and elements.
The order is not stable. Use toAscList for stable ordering.
toAscList :: KeyMap v -> [(Key, v)] Source #
Return a list of this map's elements in ascending order based of the textual key.
Maps
Traversal
Map
mapWithKey :: (Key -> a -> b) -> KeyMap a -> KeyMap b Source #
Map a function over all values in the map.
Since: 2.1.0.0
mapKeyVal :: (Key -> Key) -> (v1 -> v2) -> KeyMap v1 -> KeyMap v2 Source #
Transform the keys and values of a KeyMap.
traverseWithKey :: Applicative f => (Key -> v1 -> f v2) -> KeyMap v1 -> f (KeyMap v2) Source #
Folds
foldrWithKey :: (Key -> v -> a -> a) -> a -> KeyMap v -> a Source #
Reduce this map by applying a binary operator to all elements, using the given starting value (typically the right-identity of the operator).
Conversions
Filter
filter :: (v -> Bool) -> KeyMap v -> KeyMap v Source #
Filter all keys/values that satisfy some predicate.
filterWithKey :: (Key -> v -> Bool) -> KeyMap v -> KeyMap v Source #
Filter all keys/values that satisfy some predicate.
mapMaybeWithKey :: (Key -> v -> Maybe u) -> KeyMap v -> KeyMap u Source #
Map values and collect the Just results.