Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 | -------------------------------------
- data Sexp
- data Atom
- newtype Kw = Kw {}
- data Grammar g t t'
- type SexpG a = forall t. Grammar SexpGrammar (Sexp :- t) (a :- t)
- type SexpG_ = forall t. Grammar SexpGrammar (Sexp :- t) t
- data h :- t = h :- t
- iso :: (a -> b) -> (b -> a) -> Grammar g (a :- t) (b :- t)
- osi :: (b -> a) -> (a -> b) -> Grammar g (a :- t) (b :- t)
- partialIso :: String -> (a -> b) -> (b -> Either Mismatch a) -> Grammar g (a :- t) (b :- t)
- partialOsi :: String -> (b -> a) -> (a -> Either Mismatch b) -> Grammar g (a :- t) (b :- t)
- push :: Eq a => a -> Grammar g t (a :- t)
- pushForget :: a -> Grammar g t (a :- t)
- bool :: SexpG Bool
- integer :: SexpG Integer
- int :: SexpG Int
- real :: SexpG Scientific
- double :: SexpG Double
- string :: SexpG Text
- symbol :: SexpG Text
- keyword :: SexpG Kw
- string' :: SexpG String
- symbol' :: SexpG String
- enum :: (Enum a, Bounded a, Eq a, Data a) => SexpG a
- sym :: Text -> SexpG_
- kw :: Kw -> SexpG_
- list :: Grammar SeqGrammar t t' -> Grammar SexpGrammar (Sexp :- t) t'
- vect :: Grammar SeqGrammar t t' -> Grammar SexpGrammar (Sexp :- t) t'
- 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
- (.:) :: 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)
- position :: Grammar SexpGrammar (Sexp :- t) (Position :- (Sexp :- t))
- pair :: Grammar g (b :- (a :- t)) ((a, b) :- t)
- unpair :: Grammar g ((a, b) :- t) (b :- (a :- t))
- swap :: Grammar g (b :- (a :- t)) (a :- (b :- t))
- coproduct :: [Grammar g a b] -> Grammar g a b
- data SexpGrammar a b
- data AtomGrammar a b
- data SeqGrammar a b
- data PropGrammar a b
- decode :: SexpIso a => Text -> Either String a
- decodeWith :: SexpG a -> Text -> Either String a
- encode :: SexpIso a => a -> Either String ByteString
- encodeWith :: SexpG a -> a -> Either String ByteString
- decodeNamed :: SexpIso a => FilePath -> Text -> Either String a
- decodeNamedWith :: SexpG a -> FilePath -> Text -> Either String a
- encodePretty :: SexpIso a => a -> Either String Text
- encodePrettyWith :: SexpG a -> a -> Either String Text
- parseSexp :: SexpG a -> Sexp -> Either String a
- genSexp :: SexpG a -> a -> Either String Sexp
- data Mismatch
- expected :: Text -> Mismatch
- unexpected :: Text -> Mismatch
- class SexpIso a where
Documentation
Sexp ADT
Sexp atom types
Keyword newtype wrapper to distinguish keywords from symbols
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.
h :- t infixr 5 |
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
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
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.
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
data SexpGrammar a b Source #
data AtomGrammar a b Source #
data SeqGrammar a b Source #
data PropGrammar a b Source #
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.
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
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
class SexpIso a where Source #
SexpIso Bool Source # | |
SexpIso Double Source # | |
SexpIso Int Source # | |
SexpIso Integer Source # | |
SexpIso Text Source # | |
SexpIso Scientific Source # | |
SexpIso a => SexpIso [a] Source # | |
SexpIso a => SexpIso (Maybe a) Source # | |
SexpIso a => SexpIso (NonEmpty a) Source # | |
(Ord a, SexpIso a) => SexpIso (Set a) Source # | |
(SexpIso a, SexpIso b) => SexpIso (a, b) Source # | |
(Ord k, SexpIso k, SexpIso v) => SexpIso (Map k v) Source # | |