sexp-grammar: Invertible parsers for S-expressions

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Invertible grammar combinators for serializing and deserializing from S-expessions


[Skip to Readme]

Properties

Versions 1.0.0, 1.1.0, 1.1.1, 1.1.1, 1.2.0, 1.2.0.1, 1.2.1, 1.2.2, 1.2.3, 1.2.4, 1.3.0, 2.0.0, 2.0.1, 2.0.2, 2.1.0, 2.2.0, 2.2.1, 2.3.0, 2.3.1, 2.3.2, 2.3.3, 2.3.3.1, 2.3.4.0, 2.3.4.1, 2.3.4.2
Change log None available
Dependencies array, base (>=4.7 && <5), containers, mtl (>=2.1), scientific, semigroups, split, stack-prism, template-haskell, text, wl-pprint-text [details]
License BSD-3-Clause
Author Eugene Smolanka, Sergey Vinokurov
Maintainer Eugene Smolanka <esmolanka@gmail.com>, Sergey Vinokurov <serg.foo@gmail.com>
Category Language
Home page https://github.com/esmolanka/sexp-grammar
Source repo head: git clone https://github.com/esmolanka/sexp-grammar
Uploaded by SergeyVinokurov at 2016-02-04T11:47:35Z

Modules

[Index]

Flags

Manual Flags

NameDescriptionDefault
dev

whether to build library in development mode with strict checks

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for sexp-grammar-1.1.1

[back to package description]

sexp-grammar

Invertible syntax library for serializing and deserializing Haskell structures into S-expressions. Just write a grammar once and get both parser and pretty-printer, for free.

The package is heavily inspired by the paper [Invertible syntax descriptions: Unifying parsing and pretty printing] (http://www.informatik.uni-marburg.de/~rendel/unparse/) and a similar implementation of invertible grammar approach for JSON, library by Martijn van Steenbergen called JsonGrammar2.

Let's take a look at example:

data Person = Person
  { pName    :: String
  , pAddress :: String
  , pAge     :: Maybe Int
  } deriving (Show)

personGrammar :: SexpG Person
personGrammar =
  $(grammarFor 'Person) .               -- construct Person from
    list (                              -- a list with
      el (sym "person") >>>             -- symbol "person",
      el string'        >>>             -- some string,
      props (                           -- and properties
        Kw "address" .: string' >>>     -- :address with string value,
        Kw "age" .:? int))              -- and optional :age int proprety

So now we can use personGrammar to parse S-expessions to Person record and pretty-print any Person back to S-expression:

ghci> :m Control.Category Language.SexpGrammar
ghci> parseFromString personGrammar <$> getLine
(person "John Doe" :address "42 Whatever str." :age 25)
Right (Person {pName = "John Doe", pAddress = "42 Whatever str.", pAge = Just 25})
ghci> let (Right person) = it
ghci> prettyToText personGrammar person
(person
 "John Doe"
 :address
 "42 Whatever str."
 :age
 25)

The grammars are described in terms of isomorphisms and stack manipulations.

The simplest primitive grammars are atom grammars, which match Sexp atoms with Haskell counterparts:

                             --               grammar type   | consumes     | produces
                             --    --------------------------+--------------+-------------------
bool    :: SexpG Bool        -- or Grammar    SexpGrammar      (Sexp :- t)    (Bool       :- t)
integer :: SexpG Integer     -- or Grammar    SexpGrammar      (Sexp :- t)    (Integer    :- t)
int     :: SexpG Int         -- or Grammar    SexpGrammar      (Sexp :- t)    (Int        :- t)
real    :: SexpG Scientific  -- or Grammar    SexpGrammar      (Sexp :- t)    (Scientific :- t)
double  :: SexpG Double      -- or Grammar    SexpGrammar      (Sexp :- t)    (Double     :- t)
string  :: SexpG Text        -- or Grammar    SexpGrammar      (Sexp :- t)    (Text       :- t)
string' :: SexpG String      -- or Grammar    SexpGrammar      (Sexp :- t)    (String     :- t)
symbol  :: SexpG Text        -- or Grammar    SexpGrammar      (Sexp :- t)    (Text       :- t)
symbol' :: SexpG String      -- or Grammar    SexpGrammar      (Sexp :- t)    (String     :- t)
keyword :: SexpG Kw          -- or Grammar    SexpGrammar      (Sexp :- t)    (Kw         :- t)
sym     :: Text -> SexpG_    -- or Grammar    SexpGrammar      (Sexp :- t)    t
kw      :: Kw   -> SexpG_    -- or Grammar    SexpGrammar      (Sexp :- t)    t

Grammars matching lists and vectors can be defined using an auxiliary grammar type SeqGrammar. The following primitives embed SeqGrammars into main SexpGrammar context:

list  :: Grammar SeqGrammar t t' -> Grammar SexpGrammar (Sexp :- t) t'
vect  :: Grammar SeqGrammar t t' -> Grammar SexpGrammar (Sexp :- t) t'

Grammar type SeqGrammar basically describes the sequence of elements in a Sexp list (or vector). Single element grammar is defined with el, "match rest of the sequence as list" grammar could be defined with rest combinator. If the rest of the sequence is a property list, props combinator should be used.

el    :: Grammar SexpGrammar (Sexp :- a)  b       -> Grammar SeqGrammar a b
rest  :: Grammar SexpGrammar (Sexp :- a) (b :- a) -> Grammar SeqGrammar a ([b] :- a)
props :: Grammar PropGrammar a b                  -> Grammar SeqGrammar a b

props combinator embeds properties grammar PropGrammar into a SeqGrammar context. PropGrammar describes what keys and values to match.

(.:)  :: Kw
      -> Grammar SexpGrammar (Sexp :- t) (a :- t)
      -> Grammar PropGrammar t (a :- t)

(.:?) :: Kw
      -> Grammar SexpGrammar (Sexp :- t) (a :- t)
      -> Grammar PropGrammar t (Maybe a :- t)

Please refer to Haddock on Hackage for API documentation.

Diagram of grammar contexts:


     --------------------------------------
     |              AtomGrammar           |
     --------------------------------------
         ^
         |  atomic grammar combinators
         v
 ------------------------------------------------------
 |                      SexpGrammar                   |
 ------------------------------------------------------
         | list, vect     ^              ^
         v                | el, rest     |
     ----------------------------------  |
     |           SeqGrammar           |  |
     ----------------------------------  | (.:)
              | props                    | (.:?)
              v                          |
          -------------------------------------
          |             PropGrammar           |
          -------------------------------------