fields-json-0.3: Abusing monadic syntax JSON objects generation.

Copyright(c) Scrive 2011
LicenseBSD-style (see the LICENSE file in the distribution)
Maintainerandrzej@scrive.com
Stabilitydevelopment
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Text.JSON.Gen

Contents

Description

Abusing monadic 'do' notation library for generating JSON object. Hard-bound to JSValue from json package from hackage.

Main ideas

  • Overloaded function value to set values in underlying JSON - Bool, Int, String, lists, etc.
  • JSON generation may not be pure with valueM. You can perform some IO while generating JSON. This is usefull skip useless inner binding.
  • Compositionality - use object to easy create JSON objects. The objects function is there to support arrays of objects.
  • Monadic notation - it really looks nicer then composition with . or some magic combinator
runJSONGen $ do
    value "a" "a"
    value "b" [1,2,3]
    object "c" $ do
        value "x" True
        value "y" False

Will generate json object:

{a : "a", b: [1,2,3], c: {x: true, y : false}}

Synopsis

Documentation

Basic types

type JSONGen = JSONGenT Identity Source

Basic types

data JSONGenT m a Source

A monad that keeps currently constructed JSON.

Runners

runJSONGen :: JSONGen () -> JSValue Source

Runner. Example:

let js = runJSONGen $ do
           value "abc" "def"

runJSONGenT :: Monad m => JSONGenT m () -> m JSValue Source

Runner as monad transformer. Example:

js <- runJSONGenT $ do
           d <- lift $ getFromOuterMonad
           value "abc" d

Creating JSON's

value :: (Monad m, ToJSValue a) => String -> a -> JSONGenT m () Source

Set pure value under given name in final JSON object. Example:

value "key" "value"

valueM :: (Monad m, ToJSValue a) => String -> m a -> JSONGenT m () Source

Monadic verion of value using monad transformer. Example:

js <- runJSONGenT $ do
         valueM "abc" (getLine)

object :: Monad m => String -> JSONGenT m () -> JSONGenT m () Source

Embed other JSON object as field in a resulting JSON object. Example:

let js = runJSONGen $ do
           object "nested" $ do
               value "abc" "def"

objects :: Monad m => String -> [JSONGenT m ()] -> JSONGenT m () Source

Version for lists of objects. Example:

let js = runJSONGen $ do
           objects "nested" [ do
                                value "abc" "def"
                                value "x" "y",
                              do
                                value "qwe" "rty"
                            ]