toml-parser: TOML 1.0.0 parser

[ library, text ] [ Propose Tags ]

TOML parser using generated lexers and parsers with careful attention to the TOML 1.0.0 semantics for defining tables.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 1.0.0.0, 1.0.1.0, 1.1.0.0, 1.1.1.0, 1.2.0.0, 1.2.1.0, 1.3.0.0, 1.3.1.0, 1.3.1.1, 1.3.1.2, 1.3.1.3, 1.3.2.0, 2.0.0.0
Change log ChangeLog.md
Dependencies array (>=0.5 && <0.6), base (>=4.14 && <4.20), containers (>=0.5 && <0.8), prettyprinter (>=1.7 && <1.8), text (>=0.2 && <3), time (>=1.9 && <1.13), toml-parser, transformers (>=0.5 && <0.7) [details]
License ISC
Copyright 2023 Eric Mertens
Author Eric Mertens
Maintainer emertens@gmail.com
Category Text
Source repo head: git clone https://github.com/glguy/toml-parser(tag main)
Uploaded by EricMertens at 2024-01-05T23:44:25Z
Distributions Arch:1.3.1.3, Fedora:1.3.0.0, LTSHaskell:1.3.2.0, NixOS:1.3.2.0, Stackage:2.0.0.0, openSUSE:1.3.2.0
Reverse Dependencies 5 direct, 167 indirect [details]
Executables toml-benchmarker
Downloads 3549 total (276 in the last 30 days)
Rating 2.5 (votes: 4) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2024-01-06 [all 1 reports]

Readme for toml-parser-1.3.1.2

[back to package description]

TOML Parser

This package implements a validating parser for TOML 1.0.0.

This package uses an alex-generated lexer and happy-generated parser.

It also provides a pair of classes for serializing into and out of TOML.

Package Structure

---
title: Package Structure
---
stateDiagram-v2
    classDef important font-weight:bold;

    TOML:::important --> ApplicationTypes:::important : decode
    ApplicationTypes --> TOML : encode
    TOML --> [Token]: Toml.Lexer
    [Token] --> [Expr]: Toml.Parser
    [Expr] --> Table : Toml.Semantics
    Table --> ApplicationTypes : Toml.FromValue
    ApplicationTypes --> Table : Toml.ToValue
    Table --> TOML : Toml.Pretty

The highest-level interface to this package is to define FromValue and ToTable instances for your application-specific datatypes. These can be used with encode and decode to convert to and from TOML.

For low-level access to the TOML format, the lexer, parser, and validator are available for direct use. The diagram above shows how the different modules enable you to advance through the increasingly high-level TOML representations.

Examples

This file uses markdown-unlit to ensure that its code typechecks and stays in sync with the rest of the package.

import GHC.Generics (Generic)
import QuoteStr (quoteStr)
import Test.Hspec (Spec, hspec, it, shouldBe)
import Toml (parse, decode, encode, Value(..))
import Toml.FromValue (Result(Success), FromValue(fromValue), parseTableFromValue, reqKey)
import Toml.FromValue.Generic (genericParseTable)
import Toml.ToValue (ToValue(toValue), ToTable(toTable), defaultTableToValue, table, (.=))
import Toml.ToValue.Generic (genericToTable)

main :: IO ()
main = hspec (parses >> decodes >> encodes)

Using the raw parser

Consider this sample TOML text from the TOML specification.

fruitStr :: String
fruitStr = [quoteStr|
[[fruits]]
name = "apple"

[fruits.physical]  # subtable
color = "red"
shape = "round"

[[fruits.varieties]]  # nested array of tables
name = "red delicious"

[[fruits.varieties]]
name = "granny smith"


[[fruits]]
name = "banana"

[[fruits.varieties]]
name = "plantain"
|]

Parsing using this package generates the following value

parses :: Spec
parses = it "parses" $
    parse fruitStr
    `shouldBe`
    Right (table [
        ("fruits", Array [
            Table (table [
                ("name", String "apple"),
                ("physical", Table (table [
                    ("color", String "red"),
                    ("shape", String "round")])),
                ("varieties", Array [
                    Table (table [("name", String "red delicious")]),
                    Table (table [("name", String "granny smith")])])]),
            Table (table [
                ("name", String "banana"),
                ("varieties", Array [
                    Table (table [("name", String "plantain")])])])])])

Using decoding classes

Here's an example of defining datatypes and deserializers for the TOML above. The FromValue typeclass is used to encode each datatype into a TOML value. Instances can be derived for simple record types. More complex examples can be manually derived.

newtype Fruits = Fruits { fruits :: [Fruit] }
    deriving (Eq, Show, Generic)

data Fruit = Fruit { name :: String, physical :: Maybe Physical, varieties :: [Variety] }
    deriving (Eq, Show, Generic)

data Physical = Physical { color :: String, shape :: String }
    deriving (Eq, Show, Generic)

newtype Variety = Variety String
    deriving (Eq, Show, Generic)

instance FromValue Fruits where
    fromValue = parseTableFromValue genericParseTable

instance FromValue Fruit where
    fromValue = parseTableFromValue genericParseTable

instance FromValue Physical where
    fromValue = parseTableFromValue (Physical <$> reqKey "color" <*> reqKey "shape")

instance FromValue Variety where
    fromValue = parseTableFromValue (Variety <$> reqKey "name")

We can run this example on the original value to deserialize it into domain-specific datatypes.

decodes :: Spec
decodes = it "decodes" $
    decode fruitStr
    `shouldBe`
    Success [] (Fruits [
        Fruit
            "apple"
            (Just (Physical "red" "round"))
            [Variety "red delicious", Variety "granny smith"],
        Fruit "banana" Nothing [Variety "plantain"]])

Using encoding classes

The ToValue class is for all datatypes that can be encoded into TOML. The more specialized ToTable class is for datatypes that encode into tables and are thus elligible to be top-level types (all TOML documents are tables at the top-level).

Generics can be used to derive ToTable for simple record types. Manually defined instances are available for the more complex cases.

instance ToValue Fruits   where toValue = defaultTableToValue
instance ToValue Fruit    where toValue = defaultTableToValue
instance ToValue Physical where toValue = defaultTableToValue
instance ToValue Variety  where toValue = defaultTableToValue

instance ToTable Fruits   where toTable = genericToTable
instance ToTable Fruit    where toTable = genericToTable
instance ToTable Physical where toTable x = table ["color" .= color x, "shape" .= shape x]
instance ToTable Variety  where toTable (Variety x) = table ["name" .= x]

encodes :: Spec
encodes = it "encodes" $
    show (encode (Fruits [Fruit
            "apple"
            (Just (Physical "red" "round"))
            [Variety "red delicious", Variety "granny smith"]]))
    `shouldBe` [quoteStr|
        [[fruits]]
        name = "apple"

        [fruits.physical]
        color = "red"
        shape = "round"

        [[fruits.varieties]]
        name = "red delicious"

        [[fruits.varieties]]
        name = "granny smith"|]

More Examples

A demonstration of using this package at a more realistic scale can be found in HieDemoSpec. The various unit test files demonstrate what you can do with this library and what outputs you can expect.

See the low-level operations used to build a TOML syntax highlighter in TomlHighlighter.