{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Rollbar.Item.Body
( Body(..)
, MessageBody(..)
) where
import Data.Aeson
( FromJSON
, KeyValue
, ToJSON
, Value(Object)
, object
, pairs
, parseJSON
, toEncoding
, toJSON
, (.:)
, (.=)
)
import Data.Aeson.Encoding (pair)
import Data.Aeson.Types (typeMismatch)
import Data.String (IsString)
import GHC.Generics (Generic)
import qualified Data.Text as T
data Body arbitrary
= Message
{ messageBody :: MessageBody
, messageData :: arbitrary
}
deriving (Eq, Generic, Show)
bodyKVs :: (KeyValue kv, ToJSON v) => Body v -> [kv]
bodyKVs Message{messageBody, messageData} =
[ "body" .= messageBody
, "data" .= messageData
]
instance FromJSON arbitrary => FromJSON (Body arbitrary) where
parseJSON (Object o') = do
o <- o' .: "message"
Message <$> o .: "body" <*> o .: "data"
parseJSON v = typeMismatch "Body arbitrary" v
instance ToJSON arbitrary => ToJSON (Body arbitrary) where
toJSON x = object ["message" .= object (bodyKVs x)]
toEncoding = pairs . pair "message" . pairs . mconcat . bodyKVs
newtype MessageBody
= MessageBody T.Text
deriving (Eq, FromJSON, IsString, Show, ToJSON)