{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Yesod.Json
    ( -- * Convert from a JSON value
      defaultLayoutJson
    , jsonToRepJson
      -- * Compatibility wrapper for old API
    , Json
    , jsonScalar
    , jsonList
    , jsonMap
    ) where

import Yesod.Handler (GHandler)
import Yesod.Content
    ( ToContent (toContent), RepHtmlJson (RepHtmlJson), RepHtml (RepHtml)
    , RepJson (RepJson), Content (ContentBuilder)
    )
import Yesod.Core (defaultLayout, Yesod)
import Yesod.Widget (GWidget)
import qualified Data.Aeson as J
import qualified Data.Aeson.Encode as JE
import Data.Aeson.Encode (fromValue)
import Data.Text (pack)
import Control.Arrow (first)
#if MIN_VERSION_aeson(0, 4, 0)
import Data.HashMap.Strict (fromList)
#else
import Data.Map (fromList)
#endif
import qualified Data.Vector as V
import Text.Julius (ToJavascript (..))
import Data.Text.Lazy.Builder (fromLazyText)
import Data.Text.Lazy.Encoding (decodeUtf8)
#if MIN_VERSION_aeson(0, 5, 0)
import Data.Text.Lazy.Builder (toLazyText)
import qualified Blaze.ByteString.Builder.Char.Utf8 as Blaze
#endif

instance ToContent J.Value where
#if MIN_VERSION_aeson(0, 5, 0)
    toContent = flip ContentBuilder Nothing
              . Blaze.fromLazyText
              . toLazyText
              . fromValue
#else
    toContent = flip ContentBuilder Nothing . fromValue
#endif

-- | Provide both an HTML and JSON representation for a piece of data, using
-- the default layout for the HTML output ('defaultLayout').
defaultLayoutJson :: Yesod master
                  => GWidget sub master ()
                  -> J.Value
                  -> GHandler sub master RepHtmlJson
defaultLayoutJson w json = do
    RepHtml html' <- defaultLayout w
    return $ RepHtmlJson html' $ toContent json

-- | Wraps the 'Content' generated by 'jsonToContent' in a 'RepJson'.
jsonToRepJson :: J.Value -> GHandler sub master RepJson
jsonToRepJson = return . RepJson . toContent

type Json = J.Value

jsonScalar :: String -> Json
jsonScalar = J.String . pack

jsonList :: [Json] -> Json
jsonList = J.Array . V.fromList

jsonMap :: [(String, Json)] -> Json
jsonMap = J.Object . fromList . map (first pack)

instance ToJavascript J.Value where
    toJavascript = fromLazyText . decodeUtf8 . JE.encode