defaultable-map-1.0.2: Applicative maps
Safe HaskellNone
LanguageHaskell2010

Defaultable.Map.Generalized

Description

This module exports an API that is similar to Defaultable.Map, except the utilities have been generalized further to work with any Map-like type.

The only utility that cannot be generalized in this way is lookup, so that is the only function missing from this module. Other than the missing lookup function, this module is a drop-in replacement for the Defaultable.Map module.

Also, keep in mind that these generalized utilities may have worse type inference (especially you omit type annotations) and in some cases might also be more inefficient. If this is an issue for you then you'll need to create your own local module specializing these utilities to your Map-like type of interest.

Synopsis

Documentation

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

Construction

fromMap :: map value -> Defaultable map value Source #

Generalized version of fromMap

singleton :: IsList (map value) => Item (map value) -> Defaultable map value Source #

Generalized version of singleton

fromList :: IsList (map value) => [Item (map value)] -> Defaultable map value Source #

Generalized version of fromList

insert Source #

Arguments

:: (IsList (map value), Apply map, forall a. Monoid (map a)) 
=> Item (map value) 
-> Defaultable map value 
-> Defaultable map value 

Generalized version of insert

withDefault Source #

Arguments

:: (Apply map, forall a. Monoid (map a)) 
=> Defaultable map value 
-> value 
-> Defaultable map value 

Generalized version of withDefault

Query

toMap :: Defaultable map value -> map value Source #

Generalized version of toMap

toDefault :: Defaultable map value -> Maybe value Source #

Generalized version of toDefault