sexp-grammar-1.2.3: 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 property

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 Sexp Source #

Sexp ADT

Instances

Eq Sexp Source # 

Methods

(==) :: Sexp -> Sexp -> Bool #

(/=) :: Sexp -> Sexp -> Bool #

Ord Sexp Source # 

Methods

compare :: Sexp -> Sexp -> Ordering #

(<) :: Sexp -> Sexp -> Bool #

(<=) :: Sexp -> Sexp -> Bool #

(>) :: Sexp -> Sexp -> Bool #

(>=) :: Sexp -> Sexp -> Bool #

max :: Sexp -> Sexp -> Sexp #

min :: Sexp -> Sexp -> Sexp #

Show Sexp Source # 

Methods

showsPrec :: Int -> Sexp -> ShowS #

show :: Sexp -> String #

showList :: [Sexp] -> ShowS #

data Atom Source #

Sexp atom types

Instances

Eq Atom Source # 

Methods

(==) :: Atom -> Atom -> Bool #

(/=) :: Atom -> Atom -> Bool #

Ord Atom Source # 

Methods

compare :: Atom -> Atom -> Ordering #

(<) :: Atom -> Atom -> Bool #

(<=) :: Atom -> Atom -> Bool #

(>) :: Atom -> Atom -> Bool #

(>=) :: Atom -> Atom -> Bool #

max :: Atom -> Atom -> Atom #

min :: Atom -> Atom -> Atom #

Show Atom Source # 

Methods

showsPrec :: Int -> Atom -> ShowS #

show :: Atom -> String #

showList :: [Atom] -> ShowS #

newtype Kw Source #

Keyword newtype wrapper to distinguish keywords from symbols

Constructors

Kw 

Fields

Instances

Eq Kw Source # 

Methods

(==) :: Kw -> Kw -> Bool #

(/=) :: Kw -> Kw -> Bool #

Ord Kw Source # 

Methods

compare :: Kw -> Kw -> Ordering #

(<) :: Kw -> Kw -> Bool #

(<=) :: Kw -> Kw -> Bool #

(>) :: Kw -> Kw -> Bool #

(>=) :: Kw -> Kw -> Bool #

max :: Kw -> Kw -> Kw #

min :: Kw -> Kw -> Kw #

Show Kw Source # 

Methods

showsPrec :: Int -> Kw -> ShowS #

show :: Kw -> String #

showList :: [Kw] -> ShowS #

data Grammar g t t' Source #

Instances

Category * (Grammar c) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Semigroup (Grammar c t1 t2) Source # 

Methods

(<>) :: Grammar c t1 t2 -> Grammar c t1 t2 -> Grammar c t1 t2 #

sconcat :: NonEmpty (Grammar c t1 t2) -> Grammar c t1 t2 #

stimes :: Integral b => b -> Grammar c t1 t2 -> Grammar c t1 t2 #

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.

data h :- t infixr 5 Source #

Constructors

h :- t infixr 5 

Instances

Functor ((:-) h) Source # 

Methods

fmap :: (a -> b) -> (h :- a) -> h :- b #

(<$) :: a -> (h :- b) -> h :- a #

(Eq t, Eq h) => Eq ((:-) h t) Source # 

Methods

(==) :: (h :- t) -> (h :- t) -> Bool #

(/=) :: (h :- t) -> (h :- t) -> Bool #

(Show t, Show h) => Show ((:-) h t) Source # 

Methods

showsPrec :: Int -> (h :- t) -> ShowS #

show :: (h :- t) -> String #

showList :: [h :- t] -> ShowS #

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

osi :: (b -> a) -> (a -> b) -> Grammar g (a :- t) (b :- t) Source #

Make a grammar from a total isomorphism on top element of stack (flipped)

partialIso :: String -> (a -> b) -> (b -> Either Mismatch a) -> Grammar g (a :- t) (b :- t) Source #

Make a grammar from a partial isomorphism which can fail during backward run

partialOsi :: String -> (b -> a) -> (a -> Either Mismatch b) -> Grammar g (a :- t) (b :- t) Source #

Make a grammar from a partial isomorphism which can fail during forward run

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 the stack during backward run.

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

Same as push except it does not check the value on stack during backward run. 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

position :: Grammar SexpGrammar (Sexp :- t) (Position :- (Sexp :- t)) Source #

Get position of Sexp. Doesn't consume Sexp and doesn't have any effect on backward run.

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
    ]

Grammar types

Decoding and encoding (machine-oriented)

decode :: SexpIso a => Text -> Either String a Source #

Deserialize a value from a lazy ByteString. The input must contain exactly one S-expression. Comments are ignored.

decodeWith :: SexpG a -> Text -> Either String a Source #

Like decode but uses specified grammar.

encode :: SexpIso a => a -> Either String ByteString Source #

Serialize a value as a lazy ByteString with a non-formatted S-expression

encodeWith :: SexpG a -> a -> Either String ByteString Source #

Like encode but uses specified grammar.

Parsing and printing (human-oriented)

decodeNamed :: SexpIso a => FilePath -> Text -> Either String a Source #

Parse a value from ByteString. The input must contain exactly one S-expression. Unlike decode it takes an additional argument with a file name which is being parsed. It is used for error messages.

decodeNamedWith :: SexpG a -> FilePath -> Text -> Either String a Source #

Like decodeNamed but uses specified grammar.

encodePretty :: SexpIso a => a -> Either String Text Source #

Pretty-prints a value serialized to a lazy ByteString.

encodePrettyWith :: SexpG a -> a -> Either String Text Source #

Like encodePretty but uses specified grammar.

Parsing and encoding to Sexp

parseSexp :: SexpG a -> Sexp -> Either String a Source #

Run grammar in parsing direction

genSexp :: SexpG a -> a -> Either String Sexp Source #

Run grammar in generating direction

data Mismatch Source #

Data type to encode mismatches during parsing or generation, kept abstract. It is suggested to use expected and unexpected constructors to build a mismatch report.

expected :: Text -> Mismatch Source #

Construct a mismatch report with specified expectation. Can be appended to other expectations and unexpected reports to clarify a mismatch.

unexpected :: Text -> Mismatch Source #

Construct a mismatch report with information what has been occurred during processing but is not expected.

Typeclass for Sexp grammars