defaultable-map-1.0.2: Applicative maps
Safe HaskellSafe-Inferred
LanguageHaskell2010

Defaultable.Map

Description

This module provides a Defaultable type constructor for extending Map-like types with a valid Applicative and Alternative instance. If you're looking for an "Applicative Map" then you are in the right place!

The Defaultable type constructor can be used to wrap any Map-like, such as Data.Map.Map or Data.HashMap.HashMap.

For convenience, this module also includes a concrete API wrapping Data.Map.Map since that's the most common case. If you are interested in a more general API that works with other Map types then check out the Defaultable.Map.Generalized module.

The Applicative instance enables the use of the ApplicativeDo language extension. For example, suppose that you created the following three Defaultable Maps:

firstNames, lastNames, handles :: Defaultable (Map Int) String
firstNames = fromList [(0, "Gabriella"    ), (1, "Oscar"), (2, "Edgar"    )                  ]
lastNames  = fromList [(0, "Gonzalez"     ),               (2, "Codd"     ), (3, "Bryant"   )]
handles    = fromList [(0, "GabriellaG439"), (1, "posco"),                   (3, "avibryant")]

Then you can use ApplicativeDo notation to create an "inner join" of these various maps, like this:

>>> :set -XApplicativeDo
>>> do firstName <- firstNames; lastName <- lastNames; return (firstName, lastName)
Defaultable (fromList [(0,("Gabriella","Gonzalez")),(2,("Edgar","Codd"))]) Nothing

… and you can join as many of these maps as you want by adding statements to these ApplicativeDo blocks:

{-# LANGUAGE ApplicativeDo #-}

innerJoins :: Defaultable (Map Int) (String, String, String)
innerJoins = do
    firstName <- firstNames
    lastName  <- lastNames
    handles   <- handles
    return (firstName, lastName, handles)
>>> innerJoins
Defaultable (fromList [(0,("Gabriella","Gonzalez","GabriellaG439"))]) Nothing

The Alternative instance for Defaultable is also important, too, because you can use Alternative operations to create "left/right joins" and something similar to an outer join, like this:

leftJoin :: Defaultable (Map Int) (String, Maybe String)
leftJoin = do
    firstName <- firstNames
    lastName  <- optional lastNames
    return (firstName, lastName)

rightJoin :: Defaultable (Map Int) (Maybe String, String)
rightJoin = do
    firstName <- optional firstNames
    lastName  <- lastNames
    return (firstName, lastName)


similarToOuterJoin :: Defaultable (Map Int) (Maybe String, Maybe String)
similarToOuterJoin = do
    firstName <- optional firstNames
    lastName  <- optional lastNames
    return (firstName, lastName)
>>> leftJoin
Defaultable (fromList [(0,("Gabriella",Just "Gonzalez")),(1,("Oscar",Nothing)),(2,("Edgar",Just "Codd"))]) Nothing
>>> rightJoin
Defaultable (fromList [(0,(Just "Gabriella","Gonzalez")),(2,(Just "Edgar","Codd")),(3,(Nothing,"Bryant"))]) Nothing
>>> similarToOuterJoin
Defaultable (fromList [(0,(Just "Gabriella",Just "Gonzalez")),(1,(Just "Oscar",Nothing)),(2,(Just "Edgar",Just "Codd")),(3,(Nothing,Just "Bryant"))]) (Just (Nothing,Nothing))

You can also do more interesting multiway joins where any combiination of the inputs may be optional:

complexJoin :: Defaultable (Map Int) (Maybe String, String, Maybe String)
complexJoin = do
    firstName <- optional firstNames
    lastName  <- lastNames
    handle    <- optional handles
    return (firstName, lastName, handle)
>>> complexJoin
Defaultable (fromList [(0,(Just "Gabriella","Gonzalez",Just "GabrielG439")),(2,(Just "Edgar","Codd",Nothing)),(3,(Nothing,"Bryant",Just "avibryant"))]) Nothing
Synopsis

Comparison

This package is similar to the total-map package, which also provides an "Applicative Map" type. However, there are a couple of differences.

The first difference is that this package does not require you to supply a default value in order to get a valid Applicative instance. In other words the default value is optional. In contrast, the total-map package requires you to supply a default value. That means that the lookup function from this package can return Nothing, whereas the analogous (!) operator from the total-map package always returns a value.

However, the benefit of this tradeoff is that this package can provide an Alternative instance for Defaultable, whereas the total-map package does not have a valid Alternative instance. Furthermore, the Alternative instance enables support for left/right/"outer" joins as noted above.

Also, sometimes you just need an Applicative Map without a default value.

The other key difference compared to total-map is that this package works with Map-like types other than Data.Map.Map, whereas total-map is hard-coded to Data.Map.Map. The only caveat is that if you use the Defaultable type to wrap other Map-like types (such as Data.HashMap.HashMap) then you need to create your own utility functions, such as a new lookup function for a Defaultable HashMap. However, this is not hard to do, as you'll see if you consult the source code for each utility function.

Type

data Defaultable map value Source #

A Defaultable type is a Map-like type that is extended with an optional default value. This default value can be used as a fallback if a lookup into the Map-like type does not find a matching key.

The type variables are:

  • map: The Map-like type to wrap (typically including the type of key, but not the type of the value)
  • value The type of each value stored in the Map-like type

For example, you will typically have a type like Defaultable (Map key) value or Defaultable IntMap value.

You can build a Defaultable value using:

You can transform and combine Defaultable values using:

  • (<|>) - Concatenate two Defaultable values, preferring keys and defaults from the left one
  • do notation, if you enable ApplicativeDo
  • withDefault - To extend a Defaultable value with a default value

You can query a Defaultable value using:

Note that the Applicative instance for this type is only valid for map type constructors that satisfy the following extra law:

Given:

• mf :: map (a -> b)
• mx :: map a
• kf :: (a -> b) -> c
• kx :: a -> c

  (mf <.> mx) <> fmap kf mf <> fmap kx mx
= (mf <.> mx) <> fmap kx mx <> fmap kf mf

… where map is the first type parameter that implements Apply and Monoid.

The intuition here is if that map is a Map-like type then we can think of those three expressions as having a set of keys associated with them, such that:

Given:

• keys :: map a -> Set key

keys (mf <.> mx) = keys (fmap kf mf) `intersection` keys (fmap kx mx)

So normally the following equality would not be true:

  fmap kf mf <> fmap kx mx
= fmap kx mx <> fmap kf mf

… because the result would change if there was a key collision. Then the order in which we union (<>) the two maps would change the result.

However, if you union yet another map (mf <.> mx) that shadows the colliding keys then result remains the same.

Constructors

Defaultable 

Fields

  • (map value)

    The underlying Map-like type

  • (Maybe value)

    An optional default value to return if a key is missing

Instances

Instances details
Functor map => Functor (Defaultable map) Source # 
Instance details

Defined in Defaultable.Map

Methods

fmap :: (a -> b) -> Defaultable map a -> Defaultable map b #

(<$) :: a -> Defaultable map b -> Defaultable map a #

(Apply map, forall a. Monoid (map a)) => Applicative (Defaultable map) Source # 
Instance details

Defined in Defaultable.Map

Methods

pure :: a -> Defaultable map a #

(<*>) :: Defaultable map (a -> b) -> Defaultable map a -> Defaultable map b #

liftA2 :: (a -> b -> c) -> Defaultable map a -> Defaultable map b -> Defaultable map c #

(*>) :: Defaultable map a -> Defaultable map b -> Defaultable map b #

(<*) :: Defaultable map a -> Defaultable map b -> Defaultable map a #

Foldable map => Foldable (Defaultable map) Source # 
Instance details

Defined in Defaultable.Map

Methods

fold :: Monoid m => Defaultable map m -> m #

foldMap :: Monoid m => (a -> m) -> Defaultable map a -> m #

foldMap' :: Monoid m => (a -> m) -> Defaultable map a -> m #

foldr :: (a -> b -> b) -> b -> Defaultable map a -> b #

foldr' :: (a -> b -> b) -> b -> Defaultable map a -> b #

foldl :: (b -> a -> b) -> b -> Defaultable map a -> b #

foldl' :: (b -> a -> b) -> b -> Defaultable map a -> b #

foldr1 :: (a -> a -> a) -> Defaultable map a -> a #

foldl1 :: (a -> a -> a) -> Defaultable map a -> a #

toList :: Defaultable map a -> [a] #

null :: Defaultable map a -> Bool #

length :: Defaultable map a -> Int #

elem :: Eq a => a -> Defaultable map a -> Bool #

maximum :: Ord a => Defaultable map a -> a #

minimum :: Ord a => Defaultable map a -> a #

sum :: Num a => Defaultable map a -> a #

product :: Num a => Defaultable map a -> a #

Traversable map => Traversable (Defaultable map) Source # 
Instance details

Defined in Defaultable.Map

Methods

traverse :: Applicative f => (a -> f b) -> Defaultable map a -> f (Defaultable map b) #

sequenceA :: Applicative f => Defaultable map (f a) -> f (Defaultable map a) #

mapM :: Monad m => (a -> m b) -> Defaultable map a -> m (Defaultable map b) #

sequence :: Monad m => Defaultable map (m a) -> m (Defaultable map a) #

(Apply map, forall a. Monoid (map a)) => Alternative (Defaultable map) Source # 
Instance details

Defined in Defaultable.Map

Methods

empty :: Defaultable map a #

(<|>) :: Defaultable map a -> Defaultable map a -> Defaultable map a #

some :: Defaultable map a -> Defaultable map [a] #

many :: Defaultable map a -> Defaultable map [a] #

(Apply map, forall a. Monoid (map a)) => Alt (Defaultable map) Source # 
Instance details

Defined in Defaultable.Map

Methods

(<!>) :: Defaultable map a -> Defaultable map a -> Defaultable map a #

some :: Applicative (Defaultable map) => Defaultable map a -> Defaultable map [a] #

many :: Applicative (Defaultable map) => Defaultable map a -> Defaultable map [a] #

(Apply map, forall a. Monoid (map a)) => Apply (Defaultable map) Source # 
Instance details

Defined in Defaultable.Map

Methods

(<.>) :: Defaultable map (a -> b) -> Defaultable map a -> Defaultable map b #

(.>) :: Defaultable map a -> Defaultable map b -> Defaultable map b #

(<.) :: Defaultable map a -> Defaultable map b -> Defaultable map a #

liftF2 :: (a -> b -> c) -> Defaultable map a -> Defaultable map b -> Defaultable map c #

Generic1 (Defaultable map :: Type -> Type) Source # 
Instance details

Defined in Defaultable.Map

Associated Types

type Rep1 (Defaultable map) :: k -> Type #

Methods

from1 :: forall (a :: k). Defaultable map a -> Rep1 (Defaultable map) a #

to1 :: forall (a :: k). Rep1 (Defaultable map) a -> Defaultable map a #

(Eq value, Eq (map value)) => Eq (Defaultable map value) Source # 
Instance details

Defined in Defaultable.Map

Methods

(==) :: Defaultable map value -> Defaultable map value -> Bool #

(/=) :: Defaultable map value -> Defaultable map value -> Bool #

(Typeable map, Data value, Data (map value)) => Data (Defaultable map value) Source # 
Instance details

Defined in Defaultable.Map

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Defaultable map value -> c (Defaultable map value) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Defaultable map value) #

toConstr :: Defaultable map value -> Constr #

dataTypeOf :: Defaultable map value -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Defaultable map value)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Defaultable map value)) #

gmapT :: (forall b. Data b => b -> b) -> Defaultable map value -> Defaultable map value #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Defaultable map value -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Defaultable map value -> r #

gmapQ :: (forall d. Data d => d -> u) -> Defaultable map value -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Defaultable map value -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Defaultable map value -> m (Defaultable map value) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Defaultable map value -> m (Defaultable map value) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Defaultable map value -> m (Defaultable map value) #

(Ord value, Ord (map value)) => Ord (Defaultable map value) Source # 
Instance details

Defined in Defaultable.Map

Methods

compare :: Defaultable map value -> Defaultable map value -> Ordering #

(<) :: Defaultable map value -> Defaultable map value -> Bool #

(<=) :: Defaultable map value -> Defaultable map value -> Bool #

(>) :: Defaultable map value -> Defaultable map value -> Bool #

(>=) :: Defaultable map value -> Defaultable map value -> Bool #

max :: Defaultable map value -> Defaultable map value -> Defaultable map value #

min :: Defaultable map value -> Defaultable map value -> Defaultable map value #

(Show value, Show (map value)) => Show (Defaultable map value) Source # 
Instance details

Defined in Defaultable.Map

Methods

showsPrec :: Int -> Defaultable map value -> ShowS #

show :: Defaultable map value -> String #

showList :: [Defaultable map value] -> ShowS #

Generic (Defaultable map value) Source # 
Instance details

Defined in Defaultable.Map

Associated Types

type Rep (Defaultable map value) :: Type -> Type #

Methods

from :: Defaultable map value -> Rep (Defaultable map value) x #

to :: Rep (Defaultable map value) x -> Defaultable map value #

(Apply map, forall a. Monoid (map a), Semigroup value) => Semigroup (Defaultable map value) Source #

Not the same as the Semigroup instance for the underlying map type

Instance details

Defined in Defaultable.Map

Methods

(<>) :: Defaultable map value -> Defaultable map value -> Defaultable map value #

sconcat :: NonEmpty (Defaultable map value) -> Defaultable map value #

stimes :: Integral b => b -> Defaultable map value -> Defaultable map value #

(Apply map, forall a. Monoid (map a), Monoid value) => Monoid (Defaultable map value) Source #

Not the same as the Monoid instance for the underlying map type

Instance details

Defined in Defaultable.Map

Methods

mempty :: Defaultable map value #

mappend :: Defaultable map value -> Defaultable map value -> Defaultable map value #

mconcat :: [Defaultable map value] -> Defaultable map value #

(NFData value, NFData (map value)) => NFData (Defaultable map value) Source # 
Instance details

Defined in Defaultable.Map

Methods

rnf :: Defaultable map value -> () #

type Rep1 (Defaultable map :: Type -> Type) Source # 
Instance details

Defined in Defaultable.Map

type Rep1 (Defaultable map :: Type -> Type) = D1 ('MetaData "Defaultable" "Defaultable.Map" "defaultable-map-1.0.2-inplace" 'False) (C1 ('MetaCons "Defaultable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 map) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Maybe)))
type Rep (Defaultable map value) Source # 
Instance details

Defined in Defaultable.Map

type Rep (Defaultable map value) = D1 ('MetaData "Defaultable" "Defaultable.Map" "defaultable-map-1.0.2-inplace" 'False) (C1 ('MetaCons "Defaultable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (map value)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe value))))

data Map k a #

A Map from keys k to values a.

The Semigroup operation for Map is union, which prefers values from the left operand. If m1 maps a key k to a value a1, and m2 maps the same key to a different value a2, then their union m1 <> m2 maps k to a1.

Instances

Instances details
Bifoldable Map

Since: containers-0.6.3.1

Instance details

Defined in Data.Map.Internal

Methods

bifold :: Monoid m => Map m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Map a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Map a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Map a b -> c #

Eq2 Map

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Map a c -> Map b d -> Bool #

Ord2 Map

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Map a c -> Map b d -> Ordering #

Show2 Map

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Map a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Map a b] -> ShowS #

Functor (Map k) 
Instance details

Defined in Data.Map.Internal

Methods

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

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

Foldable (Map k)

Folds in order of increasing key.

Instance details

Defined in Data.Map.Internal

Methods

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 #

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)

Traverses in order of increasing key.

Instance details

Defined in Data.Map.Internal

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) #

Eq k => Eq1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftEq :: (a -> b -> Bool) -> Map k a -> Map k b -> Bool #

Ord k => Ord1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> Map k a -> Map k b -> Ordering #

(Ord k, Read k) => Read1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Map k a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Map k a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Map k a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Map k a] #

Show k => Show1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Map k a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Map k a] -> ShowS #

Ord k => Alt (Map k) 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Map k a -> Map k a -> Map k a #

some :: Applicative (Map k) => Map k a -> Map k [a] #

many :: Applicative (Map k) => Map k a -> Map k [a] #

Ord k => Apply (Map k)

A 'Map k' is not Applicative, but it is an instance of Apply

Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

liftF2 :: (a -> b -> c) -> Map k a -> Map k b -> Map k c #

Ord k => Bind (Map k)

A 'Map k' is not a Monad, but it is an instance of Bind

Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

Ord k => IsList (Map k v)

Since: containers-0.5.6.2

Instance details

Defined in Data.Map.Internal

Associated Types

type Item (Map k v) #

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 a) => Eq (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

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

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

(Data k, Data a, Ord k) => Data (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

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

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

toConstr :: Map k a -> Constr #

dataTypeOf :: Map k a -> DataType #

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

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

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

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

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

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

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

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

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

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

(Ord k, Ord v) => Ord (Map k v) 
Instance details

Defined in Data.Map.Internal

Methods

compare :: Map k v -> Map k v -> Ordering #

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

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

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

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

max :: Map k v -> Map k v -> Map k v #

min :: Map k v -> Map k v -> Map k v #

(Ord k, Read k, Read e) => Read (Map k e) 
Instance details

Defined in Data.Map.Internal

Methods

readsPrec :: Int -> ReadS (Map k e) #

readList :: ReadS [Map k e] #

readPrec :: ReadPrec (Map k e) #

readListPrec :: ReadPrec [Map k e] #

(Show k, Show a) => Show (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

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

show :: Map k a -> String #

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

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

Defined in Data.Map.Internal

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) 
Instance details

Defined in Data.Map.Internal

Methods

mempty :: Map k v #

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

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

(NFData k, NFData a) => NFData (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

rnf :: Map k a -> () #

type Item (Map k v) 
Instance details

Defined in Data.Map.Internal

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

Construction

fromMap :: Map key value -> Defaultable (Map key) value Source #

Create a Defaultable Map from a Map

>>> fromMap (Map.fromList [('A',1),('B',2),('B',3)])
Defaultable (fromList [('A',1),('B',3)]) Nothing

singleton :: (key, value) -> Defaultable (Map key) value Source #

Create a Defaultable Map from a single key-value pair

>>> singleton ('A', 1)
Defaultable (fromList [('A',1)]) Nothing

fromList :: Ord key => [(key, value)] -> Defaultable (Map key) value Source #

Create a Defaultable Map from a list of key-value pairs

>>> fromList [('A',1),('B',2),('B',3)]
Defaultable (fromList [('A',1),('B',3)]) Nothing

insert Source #

Arguments

:: Ord key 
=> (key, value) 
-> Defaultable (Map key) value 
-> Defaultable (Map key) value 

Insert a key-value pair into a Defaultable Map

>>> let example = fromList [('A', 1)]
>>> insert ('B', 2) example
Defaultable (fromList [('A',1),('B',2)]) Nothing
>>> insert ('A', 0) example
Defaultable (fromList [('A',0)]) Nothing

For bulk updates, you should instead use fromList/fromMap with (<|>):

>>> fromList [('A',0),('B', 2), ('C', 3)] <|> example
Defaultable (fromList [('A',0),('B',2),('C',3)]) Nothing

withDefault Source #

Arguments

:: Ord key 
=> Defaultable (Map key) value 
-> value 
-> Defaultable (Map key) value 

Add a default value to a Defaultable Map that is returned as a fallback if a lookup cannot find a matching key

>>> let example = fromList [('A',1)] `withDefault` 2
>>> lookup 'A' example
Just 1
>>> lookup 'B' example
Just 2

Query

lookup :: Ord key => key -> Defaultable (Map key) value -> Maybe value Source #

Lookup the value at a key in the map

If the key is missing this falls back to returning the default value if present

lookup is an Monad morphism, meaning that lookup distributes over Monad operatiorns:

lookup (return x) = return x

lookup (do x <- m; f x) = do x <- lookup m; lookup (f x)

lookup is also an Alternative morphism, meaning that lookup distributes over Alternative operations:

lookup empty = empty

lookup (l <|> r) = lookup l <|> lookup r
>>> let example = fromList [('A',1)]
>>> lookup 'A' example
Just 1
>>> lookup 'B' example
Nothing
>>> lookup 'B' (example `withDefault` 2)
Just 2

toMap :: Defaultable (Map key) value -> Map key value Source #

Extract the underlying map from a Defaultable map

toDefault :: Defaultable (Map key) value -> Maybe value Source #

Extract the default value from a Defaultable map