JsonGrammar-1.0.1: Combinators for bidirectional JSON parsing

Safe HaskellNone
LanguageHaskell98

Language.JsonGrammar

Contents

Description

JsonGrammar allows you to express a bidirectional mapping between Haskell datatypes and JSON ASTs in one go.

Synopsis

The Aeson example

Aeson provides this example datatype:

data Person = Person
    { name :: Text
    , age  :: Int
    } deriving Show

With these conversion functions:

{-# LANGUAGE OverloadedStrings #-}

instance FromJSON Person where
    parseJSON (Object v) = Person <$>
                           v .: "name" <*>
                           v .: "age"
    -- A non-Object value is of the wrong type, so fail.
    parseJSON _          = mzero

instance ToJSON Person where
    toJSON (Person name age) = object ["name" .= name, "age" .= age]

From JsonGrammar's point of view, the problem with writing the conversions this way is that the same thing is written down twice: from one conversion, one can figure out what the conversion in the opposite direction should look like.

In JsonGrammar, the conversion looks like this:

{-# LANGUAGE TemplateHaskell #-}

deriveStackPrismsFor ["person"] ''Person

instance Json Person where
  grammar = fromPrism person . object (prop "name" . prop "age")

This expresses the conversion in both directions in one go. The resulting parser and serializer are each other's inverse by construction.

As a bonus, if you name your grammar, JsonGrammar will generate a TypeScript definition for you:

instance Json Person where
  grammar = label "Person" $
    fromPrism person . object (prop "name" . prop "age")

This results in this TypeScript definition:

interface Person {age : number ;name : string ;}

Types

data Grammar c t1 t2 Source

A Grammar provides a bidirectional mapping between a Haskell datatype and its JSON encoding. Its first type argument specifies its context: either it's defining properties (context Obj), array elements (context Arr) or values (context Val).

Instances

Category * (Grammar c)

The . operator is the main way to compose two grammars.

IsString (Grammar Val ((:-) Value t) t)

String literals convert to grammars that expect or produce a specific JSON string literal value.

Monoid (Grammar c t1 t2)

The Monoid instance allows you to denote choice: if the left grammar doesn't succeed, the right grammar is tried.

data Context Source

The context of a grammar. Most combinators ask for a grammar in a specific context as input, and produce a grammar in another context.

Constructors

Val

Value context

Obj

Object context, for defining object members

Arr

Array context, for defining array elements

data h :- t :: * -> * -> * infixr 5

Heterogenous stack with a head and a tail. Or: an infix way to write (,).

Constructors

h :- t infixr 5 

Instances

Functor ((:-) h) 
(Eq h, Eq t) => Eq ((:-) h t) 
(Show h, Show t) => Show ((:-) h t) 
IsString (Grammar Val ((:-) Value t) t)

String literals convert to grammars that expect or produce a specific JSON string literal value.

Elemental building blocks

pure :: (t1 -> Parser t2) -> (t2 -> Maybe t1) -> Grammar c t1 t2 Source

Creates a pure grammar that doesn't specify any JSON format but just operates on the Haskell level. Pure grammars can be used in any context.

many :: Grammar c t t -> Grammar c t t Source

Try to apply a grammar as many times as possible. The argument grammar's output is fed to itself as input until doing so again would fail. This allows you to express repetitive constructions such as array elements. many can be used in any context.

literal :: Value -> Grammar Val (Value :- t) t Source

Expect or produce a literal JSON Value. You can only use this constructor in the value context Val.

label :: Text -> Grammar Val t1 t2 -> Grammar Val t1 t2 Source

Label a value grammar with a name. This doesn't affect the JSON conversion itself, but it generates an interface definition when converting to TypeScript interfaces.

object :: Grammar Obj t1 t2 -> Grammar Val (Value :- t1) t2 Source

Expect or produce a JSON object whose properties match the specified Obj grammar. You can create Obj grammars using property. Alternatively, if you want to match an empty object, use object id.

property :: Text -> Grammar Val (Value :- t1) t2 -> Grammar Obj t1 t2 Source

Expect or produce an object property with the specified name, and a value that can be parsed/produced by the specified grammar. This function creates a grammar in the Obj context. You can combine multiple property grammars using the . operator from Category.

Use <> to denote choice. For example, if you are creating an object with a property called "type", whose value determines what other properties your object has, you can write it like this:

grammar = object (propertiesA <> propertiesB)
  where
    propertiesA = property "type" "A" . fromPrism constructorA . prop "foo"
    propertiesB = property "type" "B" . fromPrism constructorB . prop "bar" . prop "baz"

array :: Grammar Arr t1 t2 -> Grammar Val (Value :- t1) t2 Source

Expect or produce a JSON array value whose contents match the specified Arr grammar. You can create Arr grammars using element. Alternatively, if you want to match an empty array, use array id.

element :: Grammar Val (Value :- t1) t2 -> Grammar Arr t1 t2 Source

Expect or produce a JSON array element whose value matches the specified Val grammar.

coerce :: Type -> Grammar Val t1 t2 -> Grammar Val t1 t2 Source

Mark a grammar to be of a specific TypeScript type. This doesn't affect the JSON conversion, but when generating TypeScript interfaces a coercion causes the interface generator to stop looking at the underlying grammar and just use the specified TypeScript Type as inferred type instead.

This is useful if you write a grammar that, for example, wraps a primitive type like string (in which case you would specify Predefined StringType as type). Another use is when you find the generated interface can't be described by a Grammar, for example because it uses a generic type parameter.

Constructing grammars

fromPrism :: StackPrism a b -> Grammar c a b Source

Create a pure grammar from a StackPrism.

defaultValue :: Eq a => a -> Grammar c t (a :- t) Source

Create a pure grammar that expects or produces a specific Haskell value.

Wrapping constructors

nil :: Grammar c t ([a] :- t) Source

A pure grammar that expects or produces the empty list [].

cons :: Grammar c (a :- ([a] :- t)) ([a] :- t) Source

A pure grammar that expects or produces a cons :.

tup2 :: Grammar c (a :- (b :- t)) ((a, b) :- t) Source

A pure grammar that wraps or unwraps a tuple.

Type-directed grammars

class Json a where Source

A type class for types that can be converted from and to JSON using a Grammar. The grammar is expected to be in the value context Val and consumes (or produces) a JSON Value.

Methods

grammar :: Grammar Val (Value :- t) (a :- t) Source

Instances

Json Float 
Json Int 
Json Text 
Json a => Json [a] 
(Json a, Json b) => Json (a, b) 

el :: Json a => Grammar Arr t (a :- t) Source

Expect or produce an array element whose value grammar is specified by grammar.

prop :: Json a => Text -> Grammar Obj t (a :- t) Source

Expect or produce an object property whose value grammar is specified by grammar.

Using grammars

parse :: Grammar Val (a :- ()) (b :- ()) -> a -> Parser b Source

Parse a JSON value according to the specified grammar.

serialize :: Grammar Val (a :- ()) (b :- ()) -> b -> Maybe a Source

Serialize a Haskell value to a JSON value according to the specified grammar.

interfaces :: [SomeGrammar Val] -> [DeclarationElement] Source

Generate a list of TypeScript interface declarations from the specified grammars.

data SomeGrammar c where Source

Wrap a Grammar, discarding the input/output type arguments.

Constructors

SomeGrammar :: Grammar c t1 t2 -> SomeGrammar c