tomland
Bidirectional TOML serialization
https://github.com/kowainik/tomland
Version on this page: | 1.3.3.3 |
LTS Haskell 23.0: | 1.3.3.3 |
Stackage Nightly 2024-12-18: | 1.3.3.3@rev:1 |
Latest on Hackage: | 1.3.3.3@rev:1 |
tomland-1.3.3.3@sha256:877635f30fc7eeebc7b79283baeec1b7904365973cc3fd98c86f9d147eeef575,9147
Module documentation for 1.3.3.3
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
tomland
is a Haskell library for Bidirectional TOML
Serialization. It provides the composable interface for implementing
TOML codecs. If you want to use
TOML as a configuration for your tool or application, you can use
tomland
to easily convert in both ways between textual TOML
representation and Haskell types.
✍️ tomland
supports TOML spec version 0.5.0.
The following blog post has more details about the library design and internal implementation details:
This README contains a basic usage example of the tomland
library. All code
below can be compiled and run with the following command:
cabal 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 Data.Text (Text)
import Data.Time (Day)
import Toml (TomlCodec, (.=))
import qualified Data.Text.IO as TIO
import qualified Toml
tomland
is 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. The configuration
contains the following description of our data:
server.port = 8080
server.codes = [ 5, 10, 42 ]
server.description = """
This is production server.
Don't touch it!
"""
[mail]
host = "smtp.gmail.com"
send-if-inactive = false
[[user]]
guestId = 42
[[user]]
guestId = 114
[[user]]
login = "Foo Bar"
createdAt = 2020-05-19
The above static configuration describes Settings
for some
server. It has several top-level fields, a table with the name mail
and an array of tables with the name user
that stores list of
different types of users.
We can model such TOML using the following Haskell data types:
data Settings = Settings
{ settingsPort :: !Port
, settingsDescription :: !Text
, settingsCodes :: [Int]
, settingsMail :: !Mail
, settingsUsers :: ![User]
}
data Mail = Mail
{ mailHost :: !Host
, mailSendIfInactive :: !Bool
}
data User
= Guest !Integer -- id of guest
| Registered !RegisteredUser -- login and createdAt of registered user
data RegisteredUser = RegisteredUser
{ registeredUserLogin :: !Text
, registeredUserCreatedAt :: !Day
}
newtype Port = Port Int
newtype Host = Host Text
Using the tomland
library, you can write bidirectional converters for these types
with the following guidelines and helper functions:
- If your fields are some simple primitive 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 it requires to specify this data type as TOML table in the.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 the 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
matchGuest :: User -> Maybe Integer
matchGuest = \case
Guest i -> Just i
_ -> Nothing
matchRegistered :: User -> Maybe RegisteredUser
matchRegistered = \case
Registered u -> Just u
_ -> Nothing
userCodec :: TomlCodec User
userCodec =
Toml.dimatch matchGuest Guest (Toml.integer "guestId")
<|> Toml.dimatch matchRegistered Registered registeredUserCodec
registeredUserCodec :: TomlCodec RegisteredUser
registeredUserCodec = RegisteredUser
<$> Toml.text "login" .= registeredUserLogin
<*> Toml.day "createdAt" .= registeredUserCreatedAt
And now we are ready to parse our TOML and print the result back to see whether everything is okay.
main :: IO ()
main = do
tomlRes <- Toml.decodeFileEither settingsCodec "examples/readme.toml"
case tomlRes of
Left errs -> TIO.putStrLn $ Toml.prettyTomlDecodeErrors errs
Right settings -> TIO.putStrLn $ Toml.encode settingsCodec settings
Benchmarks and comparison with other libraries
You can find benchmarks of the tomland
library in the following repository:
Since tomland
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 |
In addition to the above numbers, tomland
has several features that
make it unique:
tomland
is the only Haskell library that has pretty-printing.tomland
is compatible with the latest TOML spec while other libraries are not.tomland
is bidirectional, which means that your encoding and decoding are consistent with each other by construction.tomland
provides abilities forGeneric
andDerivingVia
deriving out-of-the-box.- Despite being the fastest,
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. In addition,toml-parser
doesn’t have ways to convert TOML AST to custom Haskell types andhtoml*
libraries use typeclasses-based approach viaaeson
library.
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.3.3.3 – Jun 7, 2024
- Support up to GHC-9.10.
- Remove
transformers
dependency. - Allow test case to work with
OverloadedStrings
1.3.3.2 – Oct 5, 2022
- #395: Support GHC-9.2.4.
- Upgrade
text
to version2
. - Upgrade
hedgehog
andhspec
.
🍁 1.3.3.1 — Nov 8, 2021
- Disable building executables by default
- Bump up dependencies:
- Allow
bytestring-0.11.*
- Allow
hashable-1.4.0.0
- Allow
megaparsec-9.2.0
- Allow
time-1.13
- Allow
transformers-0.6.*
- Allow
🥞 1.3.3.0 — Mar 14, 2021
- #370: Support GHC-9.0.1.
- #368:
Upgrade
hashable
lower bound to 1.3.1.0. - Sort keys in pretty printing by default.
🐂 1.3.2.0 — Feb 12, 2021
- #186:
Implement TOML difference. Add
decodeExact
anddecodeFileExact
. - #325:
Add ability to one or multiline printing to
PrintOptions
for arrays. - #329:
Add
_Harcoded
codec andhardcoded
combinator. - #333: Fix bug with parsing leading zeroes in numeric values.
- #334:
Escape unicode characters correctly in
encode
. - #364:
Update GHC from
8.10.2
to8.10.4
. - #358:
Upgrade
parser-combinators
upper bound to allow1.3
.
1.3.1.0 — Sep 21, 2020
- #331: Support hexidecimal, octal and binary values with underscores.
- #335:
Consider table array keys in
tableMap
s as well. - #338:
Allow
megaparsec-9.0
andhspec-megaparsec-2.2
. - Update GHC from
8.8.3
to8.8.4
, from8.10.1
to8.10.2
.
1.3.0.0 — May 19, 2020
-
#253: Support GHC-8.10.1. Move to GHC-8.8.3 from 8.8.1.
-
Drop support of GHC-8.2.2.
-
#271: Use
Validation
fromvalidation-selective
inTomlEnv
. This allows to accumulate and display all errors that occurs during the decoding phase. All previous decode functions return list of allTomlDecodeError
s.Note: Due to the specific of
Validation
data type, there is noMonad
instanse ofCodec
anymore. However, this doesn’t limit any previously released features. -
Add
decodeValidation
,decodeFileValidation
functions to returnValidation
instead ofEither
. -
#263: Simplify
Codec
abstraction. Instead of havingCodec r w c a
now it isCodec TomlEnv TomlState c a
.Remove
BiCodec
as it is simpleTomlCodec
with this change. -
#256, #278: Rename modules to simplify module structure.
Migration guide: If you use
Toml
module (as advised by the library) then no changes required in your code. If you import some particular modules fromtomland
here is the renaming scheme you can use to apply to your imports:Old New Toml.Bi
Toml.Codec
Toml.Bi.Combinators
Toml.Codec.Combinator
Toml.Bi.Monad
Toml.Codec.Types
Toml.Bi.Code
Toml.Codec.Code
orToml.Codec.Types
orToml.Codec.Error
Toml.Bi.Map
Toml.Codec.BiMap
orToml.Codec.BiMap.Conversion
Toml.Generic
Toml.Codec.Generic
Toml.Edsl
Toml.Type.Edsl
Toml.Printer
Toml.Type.Printer
Toml.PrefixTree
Toml.Type.PrefixTree
orToml.Type.Key
-
#283: Documentation improvements:
- Add Codec Tables to each kind of codecs with examples
- Add high-level description to each reexported module
- Add @since annotations
- Improve README
- Add more examples into functions
-
#237: Add
BiMap
_Validate
and codecsvalidate
andvalidateIf
for custom validation. -
#289: Add
_Coerce
TomlBiMap
. -
#270: Add
pair
andtriple
codecs for tuples. -
#261: Implement
tableMap
codec to use TOML keys asMap
keys. -
#243: Implement
hashMap
,tableHashMap
,intMap
,tableIntMap
codec combinators. -
Add
intSet
codec. -
Add
_KeyInt
BiMap
for key-as-int approach. -
#242: Add
HasCodec
instances forMap
,HashMap
andIntMap
forGeneric
deriving. -
#272: Add
TomlTable
newtype to be used in genericDerivingVia
. -
#251: Implement
ByteStringAsText
,ByteStringAsBytes
,LByteStringAsText
,LByteStringAsBytes
newtypes. Add correspondingHasCodec
instances for these data types. -
#311: Reimplement custom
TomlState
instead of usingMaybeT
andState
. -
Rename
ParseException
toTomlParseError
. -
Rename
DecodeException
toTomlDecodeError
. -
Add
TableArrayNotFound
constructor toTomlDecodeError
. -
Remove
TrivialError
andTypeMismatch
constructors of theTomlDecodeError
type. -
#313: Store
Key
in theBiMapError
constructor ofTomlDecodeError
. -
Add
decodeFileEither
andencodeToFile
functions. -
Fix
sum
andproduct
behaviour on missing fields. Now it returns the wrapper ofmempty
instead of failure. -
#302:
nonEmpty
codec throwsTableArrayNotFound
instead ofTableNotFound
. -
#318: Export a function for parsing TOML keys
parseKey
. -
#310: Add tests on all kinds of
TomlDecodeError
withdecode
function. -
#218: Add tests for TOML validation.
-
#252: Move to
hspec-*
family of libraries fromtasty-*
. -
#297: Tests parallelism and speed-up.
-
#246: Bump up
megaparsec
version to8.0.0
.
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.