map-syntax-0.2: Syntax sugar for defining maps

Safe HaskellNone
LanguageHaskell2010

Data.Map.Syntax

Contents

Description

An API implementing a convenient syntax for defining maps. This module was born from the observation that a list of tuples is semantically ambiguous about how duplicate keys should be handled. Additionally, the syntax is inherently rather cumbersome and difficult to work with. This API takes advantage of do notation to provide a very light syntax for defining maps while at the same time eliminating the semantic ambiguity of alists.

Here's an example:

foo :: MapSyntax Text
foo = do
  "firstName" ## "John"
  "lastName"  ## "Smith"

Synopsis

Core API

data MapSyntaxM k v a Source

A monad providing convenient syntax for defining maps.

type MapSyntax k v = MapSyntaxM k v () Source

Convenient type alias that will probably be used most of the time.

runMap :: Ord k => MapSyntaxM k v a -> Either [k] (Map k v) Source

Runs the MapSyntaxM monad to generate a map.

(##) :: k -> v -> MapSyntax k v infixr 0 Source

Forces an entry to be added. If the key already exists, its value is overwritten.

(#!) :: k -> v -> MapSyntax k v infixr 0 Source

Tries to add an entry, but if the key already exists, then runMap will return a Left with the list of offending keys. This may be useful if name collisions are bad and you want to know when they occur.

(#?) :: k -> v -> MapSyntax k v infixr 0 Source

Inserts into the map only if the key does not already exist. If the key does exist, it silently continues without overwriting or generating an error indication.

mapK :: (k1 -> k2) -> MapSyntaxM k1 v a -> MapSyntax k2 v Source

Maps a function over all the keys.

mapV :: (v1 -> v2) -> MapSyntaxM k v1 a -> MapSyntax k v2 Source

Maps a function over all the values.

runMapSyntax Source

Arguments

:: Monoid map 
=> (k -> map -> Maybe v)

Function that gets a key's value

-> (k -> v -> map -> map)

Function to force-insert a key-value pair into the map

-> MapSyntaxM k v a 
-> Either [k] map 

Runs the MapSyntaxM monad to generate a map.

runMapSyntax' Source

Arguments

:: Monoid map 
=> (k -> v -> v -> Maybe v)

Function to handle duplicate key insertion, similar to the first argument to insertWith. If this function returns Nothing, then this is interpreted as an error. If it is a Just, then the resulting value will be inserted into the map.

-> (k -> map -> Maybe v)

Function that gets a key's value

-> (k -> v -> map -> map)

Function to force-insert a key-value pair into the map

-> MapSyntaxM k v a 
-> Either [k] map 

Runs the MapSyntaxM monad to generate a map. This function gives you the full power of insertWith when duplicate keys are encountered.

Example:

runMapSyntax' (\k new_val old_val -> Just $ old_val ++ new_val)

Lower level functions

data DupStrat Source

Strategy to use for duplicates

Constructors

Replace 
Ignore 
Error 

data ItemRep k v Source

Representation of an indivdual item in a map

Constructors

ItemRep 

Fields

irStrat :: DupStrat
 
irKey :: k
 
irVal :: v
 

addStrat :: DupStrat -> k -> v -> MapSyntax k v Source

Low level add function for adding a specific DupStrat, key, and value.