tomland
Bidirectional TOML serialization
https://github.com/kowainik/tomland
Version on this page: | 1.2.1.0@rev:1 |
LTS Haskell 18.28: | 1.3.2.0 |
Stackage Nightly 2024-10-31: | 1.3.3.3 |
Latest on Hackage: | 1.3.3.3 |
tomland-1.2.1.0@sha256:7912ba07d22b24c17ede72c29e5e8d0409a5e41e5196ef2cf645669c77248b02,6717
Module documentation for 1.2.1.0
tomland
“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
Preamble: imports and language extensions
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
Data type: parsing and printing
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. - If you have sets of custom data types, use
Toml.set
orToml.HashSet
. Such sets are represented as array of tables in TOML. - For parsing sum types, use
Toml.dimatch
. This requires writing matching functions for the constructors of the sum type. 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
Benchmarks and comparison with other libraries
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 :slightly_smiling_face:
Acknowledgement
Icons made by Freepik from www.flaticon.com is licensed by CC 3.0 BY.
Changes
Changelog
tomland uses PVP Versioning. The changelog is available on GitHub.
1.2.1.0 — Nov 6, 2019
- #203:
Implement codecs for
Map
-like data structures. (by @chshersh) - #241:
Implement codecs for
Monoid
wrappers:all
,any
,sum
,product
,first
,last
. (by @vrom911)
1.2.0.0 — Oct 12, 2019
- #216: Refactor TOML parser significantly. Check for some validation errors. (by @chshersh)
- #213: Support GHC-8.8.1. (by @vrom911)
- #226:
Add
dimatch
combinator for better support of sum types. (by @Nimor111) - #219: Add INLINE pragmas to code. (by @willbasky)
- #204:
Implement bidirectional codecs to work with
ByteString
as array of bytes. (by @crtschin) - #201:
Implement
set
andhashSet
combinators for array of tables. (by @SanchayanMaity) - #215: Move benchmarks to separate repository toml-benchmarks. (by @kutyel)
- #209:
Bump up
parser-combinators
to1.2.0
. (by @vrom911) - #198: Improve test generators. (by @gabrielelana , @chshersh )
1.1.0.1 — Jul 10, 2019
- #206: Fix in parser of inline tables inside tables, add tests for official TOML examples (by @jiegillet)
1.1.0.0 — Jul 8, 2019
-
#154: Implement
Generic
bidirectional codecs (by @chshersh). -
#145: Add support for inline table arrays (by @jiegillet).
-
#195: Fix an exponential parser behavior for parsing table of arrays (by @jiegillet).
-
#190: Add
enumBounded
codec for nullary sum types (by @mxxo). -
#189: Breaking change: Implement custom table sorting by keys. Also fields of the
PrintOptions
data type were renamed according to style guide (by @ramanshah).Before:
data PrintOptions = PrintOptions { shouldSort :: Bool , indent :: Int } deriving (Show)
Now:
data PrintOptions = PrintOptions { printOptionsSorting :: !(Maybe (Key -> Key -> Ordering)) , printOptionsIndent :: !Int }
Migration guide: If you used
indent
field, useprintOptionsIndent
instead. If you usedshouldSort
, useprintOptionsSorting
instead and passNothing
instead ofFalse
orJust compare
instead ofTrue
.
1.0.1.0 — May 17, 2019
- #177:
Add a more extensive property generator for
Piece
. - #187:
Bump up to
hedgehog-1.0
. - Support GHC 8.6.5
1.0.0 — Jan 14, 2019
-
#13: Support array of tables.
- #131:
Uncommenting
tomlTableArrays
fromTOML
. - #134: Pretty printer arrays of tables and golden tests.
- #143: Parser for arrays of tables.
- #155:
Add
list
andnonEmpty
combinators for coding lists of custom user types. - #142: Adding EDSL support for arrays of tables.
- #144: Added tests for arrays of tables.
- #131:
Uncommenting
-
#140: Breaking change: Replace
wrapper
bydiwrap
.Migration guide: change
Toml.wrapper Toml.text "foo"
toToml.diwrap (Toml.text "foo")
. -
#152: Breaking change: Removing
mdimap
.Migration guide: change
Toml.mdimap showX parseX (Toml.text "foo")
toToml.textBy showX parseX "foo"
. -
#137: Replace
Maybe
withEither
inBiMap
. -
#174: Add
_LText
andlazyText
codecs. -
#163: Move all time data types from nested
DateTime
toValue
. -
#146: Allow underscores in floats.
-
#64: Integer parser doesn’t accept leading zeros.
-
#50: Add property-based tests for encoder and decoder.
-
#119: Add property-based tests for
BiMap
. -
#149: Removing records syntax from
PrefixTree
.
0.5.0 — Nov 12, 2018
-
#81: Breaking change: Rename data types.
Migration guide: rename
Bijection
toCodec
,Bi
toBiCodec
andBiToml
toTomlCodec
. -
#82: Breaking change: Remove
maybeT
. Adddioptional
instead.Migration guide: replace
Toml.maybeT Toml.int "foo"
withToml.dioptional (Toml.int "foo")
. -
#95: Breaking change: Swap fields in
BiMap
s for consistency withlens
package.Migration guide: reverse order of composition when using
BiMap
s. -
#98: Implement benchmarks for
tomland
and compare withhtoml
andhtoml-megaparsec
libraries. -
#130: Added combinators to
Toml.Bi.Combinators
. -
#115: Added time combinators to
Toml.BiMap
andToml.Bi.Combinators
. -
#99: Split
Toml.Parser
file into smaller files. -
#22: Report proper type checking error during parsing.
-
#14: Add support for inline tables parsing.
-
#70: Add
_TextBy
and_Read
combinators. -
#11: Add
PrintOptions
(sorting, indentation) for pretty printer. -
#17: Allow underscores in integers*.
-
#90: Migrate to megaparsec 7.0.
-
#85: Add
Date
generator for property-based tests. -
#88: Add
Array
generator for property-based tests. -
#86: Improve
String
generator for property-based tests. -
#87: Improve
Double
generator for property-based tests. -
Add support for GHC 8.6.1. Add support for GHC 8.4.4. Drop support for GHC 8.0.2.
-
#109: Add function
decodeToml
.
0.4.0
- #54:
Add support for sum types.
Rename
Prism
toBiMap
. RenamebijectionMaker
tomatch
. Addstring
codec.
0.3.1
- #19: Add proper parsing of floating point numbers.
- #15: Add parsing of multiline strings.
- #40: Support full-featured string parser.
- #18: Add dates parsing.
- Add useful combinators for
newtype
wrappers. - #58:
Add
decodeFile
function.
0.3
-
#60: Breaking change: Replace
Valuer
withPrism
.Migration guide: replace any
fooV
with corresponding prism_Foo
. -
#66: Breaking change: Introduce consistent names according to Haskell types.
Migration guide: see issue details to know which names to use.
-
#8: Create EDSL for easier TOML data type writing.
-
#10: Add
Semigroup
andMonoid
instances forPrefixTree
andTOML
. Add property tests on laws. -
#20: Add parsing of hexadecimal, octal, and binary integer numbers.
-
#26: Implement unit tests for TOML parsers. Allow terminating commas inside an array. Allow comments before and after any value inside an array. Allow keys to be literal strings.
0.2.1
- Make
table
parser work withmaybeP
. - #39:
Implement
prettyException
function forDecodeException
.
0.2.0
- Switch names for
decode
andencode
functions. - #47:
Rename
dimapBijection
todimap
. Introducemdimap
combinator. - #37: Add tables support for bidirectional conversion.
0.1.0
- #16: Add parser for literal strings.
- Add
IsString
instance forKey
data type. - #38: Add bidirectional converter for array.
- #21: Report expected vs. actual type error in parsing.
- #44:
Add bidirectional converter for
Maybe
.
0.0.0
- #3:
Implement basic TOML parser with
megaparsec
. - #7:
Implement type safe version of
Value
type as GADT. - #4: Implement basic pretty-printer.
- #1: Implement types representing TOML configuration.
- Initially created.