Map package:tomland

TOML-specific combinators for converting between TOML and Haskell Map-like data types. There are two way to represent map-like structures with the tomland library.
  • Map structure with the key and value represented as key-value pairs:
    foo = [ {myKey = "name", myVal = 42} , {myKey =
    "otherName", myVal = 100} ] 
  • Map structure as a table with the TOML key as the map key:
    [foo] name = 42 otherName = 100 
You can find both types of the codecs in this module for different map-like structures. See the following table for the heads up: TODO: table Note: in case of the missing key on the TOML side an empty map structure is returned.
Bidirectional codec for Map. It takes birectional converter for keys and values and produces bidirectional codec for Map. Currently it works only with array of tables, so you need to specify Maps in TOML files like this:
myMap =
[ { name = "foo", payload = 42 }
, { name = "bar", payload = 69 }
]
TomlCodec for such TOML field can look like this:
Toml.map (Toml.text "name") (Toml.int "payload") "myMap"
If there's no key with the name "myMap" then empty Map is returned.
Prepends given key to all errors that contain key. This function is used to give better error messages. So when error happens we know all pieces of table key, not only the last one.
Implementation of Tagged Partial Bidirectional Isomorphism. This module contains the BiMap type that represents conversion between two types with the possibility of failure. See Toml.Codec.BiMap.Conversion for examples of BiMap with specific types. The BiMap concept is general and is not specific to TOML, but in this package most usages of BiMap are between TOML values and Haskell values.
Partial bidirectional isomorphism. BiMap a b contains two function:
  1. a -> Either e b
  2. b -> Either e a
If you think of types as sets then this data type can be illustrated by the following picture: BiMap also implements Category typeclass. And this instance can be described clearly by this illustration:
BiMap specialized to TOML error.
Type of errors for TOML BiMap.
Smart constructor for BiMap from a Haskell value (some primitive like Int or Value) to AnyValue.
Converts TomlBiMapError into pretty human-readable text.
Throw error on Left, or perform a given action with Right.
Bidirectional codec for HashMap. It takes birectional converter for keys and values and produces bidirectional codec for HashMap. It works with array of tables, so you need to specify HashMaps in TOML files like this:
myHashMap =
[ { name = "foo", payload = 42 }
, { name = "bar", payload = 69 }
]
TomlCodec for such TOML field can look like this:
Toml.hashMap (Toml.text "name") (Toml.int "payload") "myHashMap"
If there's no key with the name "myHashMap" then empty HashMap is returned.
Bidirectional codec for IntMap. It takes birectional converter for keys and values and produces bidirectional codec for IntMap. It works with array of tables, so you need to specify IntMaps in TOML files like this:
myIntMap =
[ { name = "foo", payload = 42 }
, { name = "bar", payload = 69 }
]
TomlCodec for such TOML field can look like this:
Toml.intMap (Toml.text "name") (Toml.int "payload") "myIntMap"
If there's no key with the name "myIntMap" then empty IntMap is returned.
This TomlCodec helps to convert TOML key-value pairs directly to HashMap using TOML keys as HashMap keys. It can be convenient if your HashMap keys are types like Text or Int and you want to work with raw TOML keys directly. For example, if you can write your HashMap in TOML like this:
[myHashMap]
key1 = "value1"
key2 = "value2"
This TomlCodec helps to convert TOML key-value pairs directly to IntMap using TOML Int keys as IntMap keys. For example, if you can write your IntMap in TOML like this:
[myIntMap]
1 = "value1"
2 = "value2"
This TomlCodec helps you to convert TOML key-value pairs directly to Map using TOML keys as Map keys. It can be convenient if your Map keys are types like Text or Int and you want to work with raw TOML keys directly. For example, if you have TOML like this:
[colours]
yellow = "#FFFF00"
red    = { red = 255, green = 0, blue = 0 }
pink   = "#FFC0CB"
You want to convert such TOML configuration into the following Haskell types:
data Rgb = Rgb
{ rgbRed   :: Int
, rgbGreen :: Int
, rgbBlue  :: Int
}

data Colour
= Hex Text
| RGB Rgb

colourCodec :: TomlCodec Colour
colourCodec = ...

data ColourConfig = ColourConfig
{ configColours :: Map Text Colour
}
And you want in the result to have a Map like this:
fromList
[ "yellow" -> Hex "#FFFF00"
, "pink"   -> Hex "#FFC0CB"
, "red"    -> Rgb 255 0 0
]
You can use tableMap to define TomlCodec in the following way:
colourConfigCodec :: TomlCodec ColourConfig
colourConfigCodec = ColourConfig
<$> Toml.tableMap Toml._KeyText colourCodec "colours" .= configColours
Hint: You can use _KeyText or _KeyString to convert betwen TOML keys and Map keys (or you can write your custom TomlBiMap). NOTE: Unlike the map codec, this codec is less flexible (i.e. it doesn't allow to have arbitrary structures as Keys, it works only for text-like keys), but can be helpful if you want to save a few keystrokes during TOML configuration. A similar TOML configuration, but suitable for the map codec will look like this:
colours =
[ { key = "yellow", hex = "#FFFF00" }
, { key = "pink",   hex = "#FFC0CB" }
, { key = "red",    rgb = { red = 255, green = 0, blue = 0 } }
]
This is an instance of Profunctor for Codec. But since there's no Profunctor type class in base or package with no dependencies (and we don't want to bring extra dependencies) this instance is implemented as a single top-level function. Useful when you want to parse newtypes. For example, if you had data type like this:
data Example = Example
{ foo :: Bool
, bar :: Text
}
Bidirectional TOML converter for this type will look like this:
exampleCodec :: TomlCodec Example
exampleCodec = Example
<$> Toml.bool "foo" .= foo
<*> Toml.text "bar" .= bar
Now if you change your type in the following way:
newtype Email = Email { unEmail :: Text }

data Example = Example
{ foo :: Bool
, bar :: Email
}
you need to patch your TOML codec like this:
exampleCodec :: TomlCodec Example
exampleCodec = Example
<$> Toml.bool "foo" .= foo
<*> dimap unEmail Email (Toml.text "bar") .= bar
Map of layer names and corresponding PrefixTrees.