{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module Snap.Extras.JSON
(
getBoundedJSON
, getJSON
, reqBoundedJSON
, reqJSON
, getJSONField
, reqJSONField
, writeJSON
) where
import Data.Aeson as A
import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy.Char8 as LB
import Data.Int
import Snap.Core
import Snap.Extras.CoreUtils
reqJSON :: (MonadSnap m, A.FromJSON b) => m b
reqJSON = reqBoundedJSON 50000
reqBoundedJSON
:: (MonadSnap m, FromJSON a)
=> Int64
-> m a
reqBoundedJSON n = do
res <- getBoundedJSON n
case res of
Left e -> badReq $ B.pack e
Right a -> return a
getJSON :: (MonadSnap m, A.FromJSON a) => m (Either String a)
getJSON = getBoundedJSON 50000
getBoundedJSON
:: (MonadSnap m, FromJSON a)
=> Int64
-> m (Either String a)
getBoundedJSON n = do
bodyVal <- A.decode `fmap` readRequestBody (fromIntegral n)
return $ case bodyVal of
Nothing -> Left "Can't find JSON data in POST body"
Just v -> case A.fromJSON v of
A.Error e -> Left e
A.Success a -> Right a
getJSONField
:: (MonadSnap m, FromJSON a)
=> B.ByteString
-> m (Either String a)
getJSONField fld = do
val <- getParam fld
return $ case val of
Nothing -> Left $ "Cant find field " ++ B.unpack fld
Just val' ->
case A.decode (LB.fromChunks . return $ val') of
Nothing -> Left $ "Can't decode JSON data in field " ++ B.unpack fld
Just v ->
case A.fromJSON v of
A.Error e -> Left e
A.Success a -> Right a
reqJSONField
:: (MonadSnap m, FromJSON a)
=> B.ByteString
-> m a
reqJSONField fld = do
res <- getJSONField fld
case res of
Left e -> badReq $ B.pack e
Right a -> return a
writeJSON :: (MonadSnap m, ToJSON a) => a -> m ()
writeJSON a = do
jsonResponse
writeLBS . encode $ a