herb: Accessible format for structured data serialization

[ bsd2, library, program, serialization, text ] [ Propose Tags ] [ Report a vulnerability ]

Serialization of data structures to a Prolog-like Herbrandt-universum-style universal format, useful for type-tagged things and various intermediate representations of program code. The text representation is very simple, allowing interoperability with various minimalistic programming systems.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0
Change log CHANGELOG.md
Dependencies attoparsec (>=0.14 && <0.15), base (>=4.17 && <4.22), herb, optparse-applicative (>=0.17 && <0.19), pretty (>=1.1 && <1.2), text (>=2 && <2.2) [details]
License BSD-2-Clause
Copyright (c) 2024-2025 Mirek Kratochvil
Author Mirek Kratochvil
Maintainer Mirek Kratochvil <exa.exa@gmail.com>
Category Text, Serialization
Home page https://gitlab.com/exaexa/herb
Bug tracker https://gitlab.com/exaexa/herb/-/issues
Source repo head: git clone https://gitlab.com/exaexa/herb.git
Uploaded by exaexa at 2025-01-16T11:17:49Z
Distributions
Executables herb-format
Downloads 0 total (0 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2025-01-16 [all 1 reports]

Readme for herb-0.1.0.0

[back to package description]

herb

Herbrandt-universum-style serialization of Haskell values.

  • Like Aeson, but all structures have heads!
  • Like Show, but no precedence issues or ties to Haskell syntax!
  • Like Prolog, but capital case doesn't mean variables!

The grammar is super-simple to allow easy interoperability between programs.

Example

Let's make a small language:

{-# LANGUAGE -XOverloadedStrings #-}
{-# LANGUAGE -XDeriveGeneric #-}
{-# LANGUAGE -XDeriveAnyClass #-}

import Data.Herb
import Data.Herb.Instances

data Expr
  = Number Int
  | Var Ident
  | Apply Expr Expr
  deriving (Show, Generic, FromHerb, ToHerb)

(Some more general typeclasses are provided too, mainly the deriving via wrapper for using Show, auto-deriving from Generic as used above, and HKD support with FromHerb1 and ToHerb1.)

We can convert the data to Herb representation and serialize them:

>>> encodeHerb $ Apply (Var "sqrt") (Number 5)
"Apply(Var(sqrt),Number(5))"

There's a prettyprinter for showing unwieldy values like this symbolic representation of foldr (+) 0 [1..5]:

>>> encodeHerb $ foldr (Apply . Apply (Var "add") . Number) (Number 0) [1..5]
"Apply(Apply(Var(add),Number(1)),Apply(Apply(Var(add),Number(2)),Apply(Apply(Var(add),Number(3)),Apply(Apply(Var(add),Number(4)),Apply(Apply(Var(add),Number(5)),Number(0))))))"

...piping the above through herb-format gives a relatively readable output:

Apply(Apply(Var(add), Number(1)),
      Apply(Apply(Var(add), Number(2)),
            Apply(Apply(Var(add), Number(3)),
                  Apply(Apply(Var(add), Number(4)),
                        Apply(Apply(Var(add), Number(5)), Number(0))))))

There's also an Attoparsec-based parser (the parsers and helper functions are in Data.Herb.Parser):

>>> import Data.Herb.Parser
>>> import Data.Attoparsec.Text
>>> parseOnly herbFile "stuff(this,that) \n stuff(others)"
Right [Struct "stuff" [Atom "this",Atom "that"],Struct "stuff" [Atom "others"]]

...together with a parsing shortcut:

>>> decodeHerb "Apply(Var(sqrt),Number(2))" :: Either String Expr
Right (Apply (Var "sqrt") (Number 2))

And that's it; this isn't supposed to be complex.