tomland
Bidirectional TOML serialization
https://github.com/kowainik/tomland
| LTS Haskell 24.17: | 1.3.3.3@rev:3 | 
| Stackage Nightly 2025-10-31: | 1.3.3.3@rev:3 | 
| Latest on Hackage: | 1.3.3.3@rev:3 | 
tomland-1.3.3.3@sha256:5a1883fbe1a59bc3e70b3058ca2e1d0fa4add0727f1f3154fbb2f69339fd9429,9404Module 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 IntorTextyou can just use standard codecs likeToml.intandToml.text.
- If you want to parse newtypes, useToml.diwrapto wrap parsers for underlyingnewtyperepresentation.
- For parsing nested data types, use Toml.table. But it requires to specify this data type as TOML table in the.tomlfile.
- 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,Textor time types, that you can useToml.arrayOfand parse arrays of values.
- If you have sets of custom data types, use Toml.setorToml.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.
- tomlandseparates conversion between Haskell types and TOML values from matching values by keys. Converters between types and values have type- TomlBiMapand are named with capital letter started with underscore. Main type for TOML codecs is called- TomlCodec. To lift- TomlBiMapto- TomlCodecyou need to use- Toml.matchfunction.
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:
- tomlandis the only Haskell library that has pretty-printing.
- tomlandis compatible with the latest TOML spec while other libraries are not.
- tomlandis bidirectional, which means that your encoding and decoding are consistent with each other by construction.
- tomlandprovides abilities for- Genericand- DerivingViaderiving out-of-the-box.
- Despite being the fastest, toml-parserdoesn’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-parserdoesn’t have ways to convert TOML AST to custom Haskell types andhtoml*libraries use typeclasses-based approach viaaesonlibrary.
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 transformersdependency.
- Allow test case to work with OverloadedStrings
1.3.3.2 – Oct 5, 2022
- #395: Support GHC-9.2.4.
- Upgrade textto version2.
- Upgrade hedgehogandhspec.
🍁 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 hashablelower 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 decodeExactanddecodeFileExact.
- #325:
Add ability to one or multiline printing to PrintOptionsfor arrays.
- #329:
Add _Harcodedcodec andhardcodedcombinator.
- #333: Fix bug with parsing leading zeroes in numeric values.
- #334:
Escape unicode characters correctly in encode.
- #364:
Update GHC from 8.10.2to8.10.4.
- #358:
Upgrade parser-combinatorsupper 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 tableMaps as well.
- #338:
Allow megaparsec-9.0andhspec-megaparsec-2.2.
- Update GHC from 8.8.3to8.8.4, from8.10.1to8.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 Validationfromvalidation-selectiveinTomlEnv. This allows to accumulate and display all errors that occurs during the decoding phase. All previous decode functions return list of allTomlDecodeErrors.Note: Due to the specific of Validationdata type, there is noMonadinstanse ofCodecanymore. However, this doesn’t limit any previously released features.
- 
Add decodeValidation,decodeFileValidationfunctions to returnValidationinstead ofEither.
- 
#263: Simplify Codecabstraction. Instead of havingCodec r w c anow it isCodec TomlEnv TomlState c a.Remove BiCodecas it is simpleTomlCodecwith this change.
- 
#256, #278: Rename modules to simplify module structure. Migration guide: If you use Tomlmodule (as advised by the library) then no changes required in your code. If you import some particular modules fromtomlandhere is the renaming scheme you can use to apply to your imports:Old New Toml.BiToml.CodecToml.Bi.CombinatorsToml.Codec.CombinatorToml.Bi.MonadToml.Codec.TypesToml.Bi.CodeToml.Codec.CodeorToml.Codec.TypesorToml.Codec.ErrorToml.Bi.MapToml.Codec.BiMaporToml.Codec.BiMap.ConversionToml.GenericToml.Codec.GenericToml.EdslToml.Type.EdslToml.PrinterToml.Type.PrinterToml.PrefixTreeToml.Type.PrefixTreeorToml.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_Validateand codecsvalidateandvalidateIffor custom validation.
- 
#289: Add _CoerceTomlBiMap.
- 
#270: Add pairandtriplecodecs for tuples.
- 
#261: Implement tableMapcodec to use TOML keys asMapkeys.
- 
#243: Implement hashMap,tableHashMap,intMap,tableIntMapcodec combinators.
- 
Add intSetcodec.
- 
Add _KeyIntBiMapfor key-as-int approach.
- 
#242: Add HasCodecinstances forMap,HashMapandIntMapforGenericderiving.
- 
#272: Add TomlTablenewtype to be used in genericDerivingVia.
- 
#251: Implement ByteStringAsText,ByteStringAsBytes,LByteStringAsText,LByteStringAsBytesnewtypes. Add correspondingHasCodecinstances for these data types.
- 
#311: Reimplement custom TomlStateinstead of usingMaybeTandState.
- 
Rename ParseExceptiontoTomlParseError.
- 
Rename DecodeExceptiontoTomlDecodeError.
- 
Add TableArrayNotFoundconstructor toTomlDecodeError.
- 
Remove TrivialErrorandTypeMismatchconstructors of theTomlDecodeErrortype.
- 
#313: Store Keyin theBiMapErrorconstructor ofTomlDecodeError.
- 
Add decodeFileEitherandencodeToFilefunctions.
- 
Fix sumandproductbehaviour on missing fields. Now it returns the wrapper ofmemptyinstead of failure.
- 
#302: nonEmptycodec throwsTableArrayNotFoundinstead ofTableNotFound.
- 
#318: Export a function for parsing TOML keys parseKey.
- 
#310: Add tests on all kinds of TomlDecodeErrorwithdecodefunction.
- 
#218: Add tests for TOML validation. 
- 
#252: Move to hspec-*family of libraries fromtasty-*.
- 
#297: Tests parallelism and speed-up. 
- 
#246: Bump up megaparsecversion to8.0.0.
1.2.1.0 — Nov 6, 2019
- #203:
Implement codecs for Map-like data structures. (by @chshersh)
- #241:
Implement codecs for Monoidwrappers: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 dimatchcombinator for better support of sum types. (by @Nimor111)
- #219: Add INLINE pragmas to code. (by @willbasky)
- #204:
Implement bidirectional codecs to work with ByteStringas array of bytes. (by @crtschin)
- #201:
Implement setandhashSetcombinators for array of tables. (by @SanchayanMaity)
- #215: Move benchmarks to separate repository toml-benchmarks. (by @kutyel)
- #209:
Bump up parser-combinatorsto1.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 Genericbidirectional 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 enumBoundedcodec for nullary sum types (by @mxxo).
- 
#189: Breaking change: Implement custom table sorting by keys. Also fields of the PrintOptionsdata 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 indentfield, useprintOptionsIndentinstead. If you usedshouldSort, useprintOptionsSortinginstead and passNothinginstead ofFalseorJust compareinstead 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 tomlTableArraysfromTOML.
- #134: Pretty printer arrays of tables and golden tests.
- #143: Parser for arrays of tables.
- #155:
Add listandnonEmptycombinators 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 wrapperbydiwrap.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 MaybewithEitherinBiMap.
- 
#174: Add _LTextandlazyTextcodecs.
- 
#163: Move all time data types from nested DateTimetoValue.
- 
#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 BijectiontoCodec,BitoBiCodecandBiTomltoTomlCodec.
- 
#82: Breaking change: Remove maybeT. Adddioptionalinstead.Migration guide: replace Toml.maybeT Toml.int "foo"withToml.dioptional (Toml.int "foo").
- 
#95: Breaking change: Swap fields in BiMaps for consistency withlenspackage.Migration guide: reverse order of composition when using BiMaps.
- 
#98: Implement benchmarks for tomlandand compare withhtomlandhtoml-megaparseclibraries.
- 
#130: Added combinators to Toml.Bi.Combinators.
- 
#115: Added time combinators to Toml.BiMapandToml.Bi.Combinators.
- 
#99: Split Toml.Parserfile into smaller files.
- 
#22: Report proper type checking error during parsing. 
- 
#14: Add support for inline tables parsing. 
- 
#70: Add _TextByand_Readcombinators.
- 
#11: Add PrintOptions(sorting, indentation) for pretty printer.
- 
#17: Allow underscores in integers*. 
- 
#90: Migrate to megaparsec 7.0. 
- 
#85: Add Dategenerator for property-based tests.
- 
#88: Add Arraygenerator for property-based tests.
- 
#86: Improve Stringgenerator for property-based tests.
- 
#87: Improve Doublegenerator 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 PrismtoBiMap. RenamebijectionMakertomatch. Addstringcodec.
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 newtypewrappers.
- #58:
Add decodeFilefunction.
0.3
- 
#60: Breaking change: Replace ValuerwithPrism.Migration guide: replace any fooVwith 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 SemigroupandMonoidinstances forPrefixTreeandTOML. 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 tableparser work withmaybeP.
- #39:
Implement prettyExceptionfunction forDecodeException.
0.2.0
- Switch names for decodeandencodefunctions.
- #47:
Rename dimapBijectiontodimap. Introducemdimapcombinator.
- #37: Add tables support for bidirectional conversion.
0.1.0
- #16: Add parser for literal strings.
- Add IsStringinstance forKeydata 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 Valuetype as GADT.
- #4: Implement basic pretty-printer.
- #1: Implement types representing TOML configuration.
- Initially created.
