“A library is like an island in the middle of a vast sea of ignorance, particularly if the library is very tall and the surrounding area has been flooded.”
― Lemony Snicket, Horseradish
Bidirectional TOML serialization. The following blog post has more details about library design:
This README contains a basic usage example of the tomland
library. All code
below can be compiled and run with the following command:
cabal new-run readme
Since this is a literate haskell file, we need to specify all our language extensions and imports up front.
{-# OPTIONS -Wno-unused-top-binds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative ((<|>))
import Control.Category ((>>>))
import Data.Text (Text)
import Toml (TomlBiMap, TomlCodec, (.=))
import qualified Data.Text.IO as TIO
import qualified Toml
tomland
is mostly designed for qualified imports and intended to be imported
as follows:
import Toml (TomlCodec, (.=)) -- add 'TomlBiMap' and 'Key' here optionally
import qualified Toml
We're going to parse TOML configuration from examples/readme.toml
file.
This static configuration is captured by the following Haskell data type:
data Settings = Settings
{ settingsPort :: !Port
, settingsDescription :: !Text
, settingsCodes :: [Int]
, settingsMail :: !Mail
, settingsUsers :: ![User]
}
data Mail = Mail
{ mailHost :: !Host
, mailSendIfInactive :: !Bool
}
data User
= Admin !Integer -- id of admin
| Client !Text -- name of the client
deriving stock (Show)
newtype Port = Port Int
newtype Host = Host Text
Using tomland
library, you can write bidirectional converters for these types
using the following guidelines and helper functions:
- If your fields are some simple basic types like
Int
orText
you can just use standard codecs likeToml.int
andToml.text
. - If you want to parse
newtype
s, useToml.diwrap
to wrap parsers for underlyingnewtype
representation. - For parsing nested data types, use
Toml.table
. But this requires to specify this data type as TOML table in.toml
file. - If you have lists of custom data types, use
Toml.list
. Such lists are represented as array of tables in TOML. If you have lists of primitive types likeInt
,Bool
,Double
,Text
or time types, that you can useToml.arrayOf
and parse arrays of values. tomland
separates conversion between Haskell types and TOML values from matching values by keys. Converters between types and values have typeTomlBiMap
and are named with capital letter started with underscore. Main type for TOML codecs is calledTomlCodec
. To liftTomlBiMap
toTomlCodec
you need to useToml.match
function.
settingsCodec :: TomlCodec Settings
settingsCodec = Settings
<$> Toml.diwrap (Toml.int "server.port") .= settingsPort
<*> Toml.text "server.description" .= settingsDescription
<*> Toml.arrayOf Toml._Int "server.codes" .= settingsCodes
<*> Toml.table mailCodec "mail" .= settingsMail
<*> Toml.list userCodec "user" .= settingsUsers
mailCodec :: TomlCodec Mail
mailCodec = Mail
<$> Toml.diwrap (Toml.text "host") .= mailHost
<*> Toml.bool "send-if-inactive" .= mailSendIfInactive
_Admin :: TomlBiMap User Integer
_Admin = Toml.prism Admin $ \case
Admin i -> Right i
other -> Toml.wrongConstructor "Admin" other
_Client :: TomlBiMap User Text
_Client = Toml.prism Client $ \case
Client n -> Right n
other -> Toml.wrongConstructor "Client" other
userCodec :: TomlCodec User
userCodec =
Toml.match (_Admin >>> Toml._Integer) "id"
<|> Toml.match (_Client >>> Toml._Text) "name"
And now we're ready to parse our TOML and print the result back to see whether everything is okay.
main :: IO ()
main = do
tomlExample <- TIO.readFile "examples/readme.toml"
let res = Toml.decode settingsCodec tomlExample
case res of
Left err -> print err
Right settings -> TIO.putStrLn $ Toml.encode settingsCodec settings
tomland
is compared with other libraries. Since it uses 2-step approach with
converting text to intermediate AST and only then decoding Haskell type from
this AST, benchmarks are also implemented in a way to reflect this difference.
Library | parse :: Text -> AST | transform :: AST -> Haskell |
---|---|---|
tomland |
305.5 μs |
1.280 μs |
htoml |
852.8 μs |
33.37 μs |
htoml-megaparsec |
295.0 μs |
33.62 μs |
toml-parser |
164.6 μs |
1.101 μs |
You may see that tomland
is not the fastest one (though still very fast). But
performance hasn’t been optimized so far and:
toml-parser
doesn’t support the array of tables and because of that it’s hardly possible to specify the list of custom data types in TOML with this library.tomland
supports latest TOML spec whilehtoml
andhtoml-megaparsec
don’t have support for all types, values and formats.tomland
is the only library that has pretty-printing.toml-parser
doesn’t have ways to convert TOML AST to custom Haskell types andhtoml*
libraries use typeclasses-based approach viaaeson
library.tomland
is bidirectional 🙂
Icons made by Freepik from www.flaticon.com is licensed by CC 3.0 BY.