sexp-grammar-1.1.1: Invertible parsers for S-expressions

Safe HaskellNone
LanguageHaskell2010

Language.SexpGrammar

Contents

Description

Write your grammar once and get both parser and pretty-printer, for free.

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.

(person "John Doe" :address "42 Whatever str." :age 25)

will parse into:

Person {pName = "John Doe", pAddress = "42 Whatever str.", pAge = Just 25}

and the record will pretty-print back into:

(person
 "John Doe"
 :address
 "42 Whatever str."
 :age
 25)

Grammar types diagram:

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

Synopsis

Documentation

data Grammar g t t' Source

Instances

type SexpG a = forall t. Grammar SexpGrammar (Sexp :- t) (a :- t) Source

Grammar which matches Sexp to a value of type a and vice versa.

type SexpG_ = forall t. Grammar SexpGrammar (Sexp :- t) t Source

Grammar which pattern matches Sexp and produces nothing, or consumes nothing but generates some Sexp.

Combinators

Primitive grammars

iso :: (a -> b) -> (b -> a) -> Grammar g (a :- t) (b :- t) Source

Make a grammar from a total isomorphism on top element of stack

embedPrism :: StackPrism a b -> Grammar g (a :- t) (b :- t) Source

Make a grammar from a prism which can fail during generation

embedParsePrism :: String -> StackPrism b a -> Grammar g (a :- t) (b :- t) Source

Make a grammar from a prism which can fail during parsing

push :: Eq a => a -> Grammar g t (a :- t) Source

Unconditionally push given value on stack, i.e. it does not consume anything on parsing. However such grammar expects the same value as given one on stack during generation.

pushForget :: a -> Grammar g t (a :- t) Source

Same as push except it does not check the value on stack during generation. Potentially unsafe as it "forgets" some data.

Atom grammars

bool :: SexpG Bool Source

Define an atomic Bool grammar

integer :: SexpG Integer Source

Define an atomic Integer grammar

int :: SexpG Int Source

Define an atomic Int grammar

real :: SexpG Scientific Source

Define an atomic real number (Scientific) grammar

double :: SexpG Double Source

Define an atomic double precision floating point number (Double) grammar

string :: SexpG Text Source

Define an atomic string (Text) grammar

symbol :: SexpG Text Source

Define a grammar for a symbol (Text)

keyword :: SexpG Kw Source

Define a grammar for a keyword

string' :: SexpG String Source

Define an atomic string ([Char]) grammar

symbol' :: SexpG String Source

Define a grammar for a symbol ([Char])

enum :: (Enum a, Bounded a, Eq a, Data a) => SexpG a Source

Define a grammar for an enumeration type. Automatically derives all symbol names from data constructor names and "lispifies" them.

sym :: Text -> SexpG_ Source

Define a grammar for a constant symbol

kw :: Kw -> SexpG_ Source

Define a grammar for a constant keyword

Complex grammars

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

Define a sequence grammar inside a list

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

Define a sequence grammar inside a vector

Sequence grammars

el :: Grammar SexpGrammar (Sexp :- a) b -> Grammar SeqGrammar a b Source

Define a sequence element grammar

rest :: Grammar SexpGrammar (Sexp :- a) (b :- a) -> Grammar SeqGrammar a ([b] :- a) Source

Define a grammar for rest of the sequence

props :: Grammar PropGrammar a b -> Grammar SeqGrammar a b Source

Define a property list grammar on the rest of the sequence. The remaining sequence must be empty or start with a keyword and its corresponding value and continue with the sequence built by the same rules.

E.g.

:kw1 <val1> :kw2 <val2> ... :kwN <valN>

Property grammars

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

Define property pair grammar

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

Define optional property pair grammar

Utility grammars

pair :: Grammar g (b :- (a :- t)) ((a, b) :- t) Source

Construct pair from two top elements of stack

unpair :: Grammar g ((a, b) :- t) (b :- (a :- t)) Source

Deconstruct pair into two top elements of stack

swap :: Grammar g (b :- (a :- t)) (a :- (b :- t)) Source

Swap two top elements of stack. Useful for defining grammars for data constructors with inconvenient field order.

E.g. consider a data type, which has field order different from what would like to display to user:

data Command = Command { args :: [String], executable :: FilePath }

In S-expression executable should go first:

commandGrammar =
  $(grammarFor 'Command) .
    list ( el (sym "call") >>>  -- symbol "call"
           el string'      >>>  -- executable name
           rest string'    >>>  -- arguments
           swap )

coproduct :: [Grammar g a b] -> Grammar g a b Source

Combine several alternative grammars into one grammar. Useful for defining grammars for sum types.

E.g. consider a data type:

data Maybe a = Nothing | Just a

A total grammar which would handle both cases should be constructed with coproduct combinator or with Semigroup's instance.

maybeGrammar :: SexpG a -> SexpG (Maybe a)
maybeGrammar g =
  coproduct
    [ $(grammarFor 'Nothing) . kw (Kw "nil")
    , $(grammarFor 'Just)    . g
    ]

TemplateHaskell helpers

grammarFor :: Name -> ExpQ Source

Build a prism and the corresponding grammar that will match on the given constructor and convert it to reverse sequence of :- stacks.

E.g. consider a data type:

data FooBar a b c = Foo a b c | Bar

For constructor Foo

fooGrammar = $(grammarFor 'Foo)

will expand into

fooGrammar = GenPrism "Foo" $
 stackPrism
  (\(c :- b :- a :- t) -> Foo a b c :- t)
  (\case { Foo a b c :- t -> Just $ c :- b :- a :- t; _ -> Nothing })

Note the order of elements on the stack:

ghci> :t fooGrammar
fooGrammar :: Grammar g (c :- (b :- (a :- t))) (FooBar a b c :- t)

Grammar types

Parsing and printing

Low-level printing and parsing

parse :: (Functor m, MonadPlus m, MonadError String m, InvertibleGrammar m g) => Grammar g (Sexp :- ()) (a :- ()) -> Sexp -> m a Source

gen :: (Functor m, MonadPlus m, MonadError String m, InvertibleGrammar m g) => Grammar g (Sexp :- ()) (a :- ()) -> a -> m Sexp Source

Typeclass for Sexp grammars

class SexpIso a where Source

Minimal complete definition

Nothing

Methods

sexpIso :: SexpG a Source

Re-exported from stack-prism

type StackPrism a b = forall p f. (Choice p, Applicative f) => p a (f a) -> p b (f b)

data h :- t :: * -> * -> *

Constructors

h :- t 

Instances

Functor ((:-) h) 
(Eq h, Eq t) => Eq ((:-) h t) 
(Show h, Show t) => Show ((:-) h t)