tomland-1.3.3.0: Bidirectional TOML serialization
Copyright(c) 2018-2021 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Toml.Codec.Combinator.Map

Description

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:

Haskell TypeTOMLTomlCodec
Map Int Textx = [{k = 42, v = "foo"}]map (int "k") (text "v") "x"
Map Text Intx = {a = 42, b = 11}tableMap _KeyText int "x"
HashMap Int Textx = [{k = 42, v = "foo"}]hashMap (int "k") (text "v") "x"
HashMap Text Intx = {a = 42, b = 11}tableHashMap _KeyText int "x"
IntMap Textx = [{k = 42, v = "foo"}]intMap (int "k") (text "v") "x"
IntMap Textx = {1 = "one", 2 = "two"}tableIntMap _KeyInt text "x"

Note: in case of the missing key on the TOML side an empty map structure is returned.

Since: 1.3.0.0

Synopsis

Map codecs

map Source #

Arguments

:: forall k v. Ord k 
=> TomlCodec k

Codec for Map keys

-> TomlCodec v

Codec for Map values

-> Key

TOML key where Map is stored

-> TomlCodec (Map k v)

Codec for the Map

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.

Since: 1.2.1.0

tableMap Source #

Arguments

:: forall k v. Ord k 
=> TomlBiMap Key k

Bidirectional converter between TOML Keys and Map keys

-> (Key -> TomlCodec v)

Codec for Map values for the corresponding Key

-> Key

Table name for Map

-> TomlCodec (Map k v) 

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 } }
    ]

Since: 1.3.0.0

HashMap codecs

hashMap Source #

Arguments

:: forall k v. (Eq k, Hashable k) 
=> TomlCodec k

Codec for HashMap keys

-> TomlCodec v

Codec for HashMap values

-> Key

TOML key where HashMap is stored

-> TomlCodec (HashMap k v)

Codec for the HashMap

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.

Since: 1.3.0.0

tableHashMap Source #

Arguments

:: forall k v. (Eq k, Hashable k) 
=> TomlBiMap Key k

Bidirectional converter between TOML Keys and HashMap keys

-> (Key -> TomlCodec v)

Codec for HashMap values for the corresponding Key

-> Key

Table name for HashMap

-> TomlCodec (HashMap k v) 

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"

Since: 1.3.0.0

IntMap codecs

intMap Source #

Arguments

:: forall v. TomlCodec Int

Codec for IntMap keys

-> TomlCodec v

Codec for IntMap values

-> Key

TOML key where IntMap is stored

-> TomlCodec (IntMap v)

Codec for the IntMap

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.

Since: 1.3.0.0

tableIntMap Source #

Arguments

:: forall v. TomlBiMap Key Int

Bidirectional converter between TOML Keys and IntMap keys

-> (Key -> TomlCodec v)

Codec for IntMap values for the corresponding Key

-> Key

Table name for IntMap

-> TomlCodec (IntMap v) 

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"

Since: 1.3.0.0