Portability | portable |
---|---|
Stability | development |
Maintainer | andrzej@scrive.com |
Safe Haskell | None |
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}}
- module Text.JSON.ToJSValue
- type JSONGen = JSONGenT Identity
- data JSONGenT m a
- runJSONGen :: JSONGen () -> JSValue
- runJSONGenT :: Monad m => JSONGenT m () -> m JSValue
- value :: (Monad m, ToJSValue a) => String -> a -> JSONGenT m ()
- valueM :: (Monad m, ToJSValue a) => String -> m a -> JSONGenT m ()
- object :: Monad m => String -> JSONGenT m () -> JSONGenT m ()
- objects :: Monad m => String -> [JSONGenT m ()] -> JSONGenT m ()
Documentation
module Text.JSON.ToJSValue
Basic types
MonadTrans JSONGenT | |
Monad m => Monad (JSONGenT m) | |
Functor m => Functor (JSONGenT m) | |
(Monad m, Functor m) => Applicative (JSONGenT m) | |
MonadIO m => MonadIO (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
runJSONGenT :: Monad m => JSONGenT m () -> m JSValueSource
Creating JSON's
value :: (Monad m, ToJSValue a) => String -> a -> JSONGenT m ()Source
Set pure value under given name in final JSON object