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

Portabilityportable
Stabilitydevelopment
Maintainerandrzej@scrive.com
Safe HaskellNone

Text.JSON.Gen

Contents

Description

Abusing monadic 'do' notation library for generating JSON object. Hard-binded to 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
  • 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 IdentitySource

Basic types

data JSONGenT m a Source

Instances

MonadTrans JSONGenT 
Monad m => Monad (JSONGenT m) 
Functor m => Functor (JSONGenT m) 
(Functor (JSONGenT m), Monad m, Functor m) => Applicative (JSONGenT m) 
(Monad (JSONGenT m), MonadIO m) => MonadIO (JSONGenT m) 
(Monad (JSONGenT m), Monad m) => MonadReader (Seq (String, JSValue)) (JSONGenT m)

This instance gives us the ability to use FromJSValue function while generating.

Runners

runJSONGen :: JSONGen () -> JSValueSource

Simple runner

Creating JSON's

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

Set pure value under given name in final JSON object

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

Monadic verion of value

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

Embed other JSON object as field in resulting JSON object.

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

Version for lists of objects.