module Composite.Aeson.Formats.Generic
( abeJsonFormat, aesonJsonFormat, jsonArrayFormat, jsonObjectFormat
, SumStyle(..), jsonSumFormat
) where
import Composite.Aeson.Base (JsonFormat(JsonFormat), JsonProfunctor(JsonProfunctor), FromJson(FromJson))
import Control.Arrow (second)
import Control.Lens (_Wrapped, over, unsnoc)
import Control.Monad.Error.Class (throwError)
import Data.Aeson (FromJSON, ToJSON, (.=), toJSON)
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.BetterErrors as ABE
import qualified Data.HashMap.Strict as StrictHashMap
import Data.List.NonEmpty (NonEmpty((:|)))
import qualified Data.List.NonEmpty as NEL
import Data.Monoid ((<>))
import Data.Text (Text, intercalate, unpack)
import qualified Data.Vector as Vector
import Language.Haskell.TH.Syntax (Lift, lift, liftString)
abeJsonFormat :: ToJSON a => ABE.Parse e a -> JsonFormat e a
abeJsonFormat p = JsonFormat $ JsonProfunctor toJSON p
aesonJsonFormat :: (ToJSON a, FromJSON a) => JsonFormat e a
aesonJsonFormat = JsonFormat $ JsonProfunctor toJSON ABE.fromAesonParser
jsonArrayFormat :: (t -> [a]) -> ([a] -> ABE.Parse e t) -> JsonFormat e a -> JsonFormat e t
jsonArrayFormat oToList iFromList =
over _Wrapped $ \ (JsonProfunctor o i) ->
JsonProfunctor (Aeson.Array . Vector.fromList . map o . oToList)
(ABE.eachInArray i >>= iFromList)
jsonObjectFormat :: (t -> [(Text, a)]) -> ([(Text, a)] -> ABE.Parse e t) -> JsonFormat e a -> JsonFormat e t
jsonObjectFormat oToList iFromList =
over _Wrapped $ \ (JsonProfunctor o i) ->
JsonProfunctor (Aeson.Object . StrictHashMap.fromList . map (second o) . oToList)
(ABE.eachInObject i >>= iFromList)
data SumStyle
= SumStyleFieldName
| SumStyleTypeValue Text Text
| SumStyleMergeType Text
deriving (Eq, Show)
instance Lift SumStyle where
lift = \ case
SumStyleFieldName -> [| SumStyleFieldName |]
SumStyleTypeValue a b -> [| SumStyleTypeValue $(liftString $ unpack a) $(liftString $ unpack b) |]
SumStyleMergeType a -> [| SumStyleMergeType $(liftString $ unpack a) |]
expectedFieldsForInputs :: NonEmpty (Text, x) -> String
expectedFieldsForInputs ((f, _) :| rest) =
case unsnoc rest of
Just (prefix, (fLast, _)) -> unpack $ f <> ", " <> intercalate ", " (map fst prefix) <> ", or " <> fLast
Nothing -> unpack f
jsonSumFormat :: SumStyle -> (a -> (Text, Aeson.Value)) -> NonEmpty (Text, FromJson e a) -> JsonFormat e a
jsonSumFormat = \ case
SumStyleFieldName -> jsonFieldNameSumFormat
SumStyleTypeValue t v -> jsonTypeValueSumFormat t v
SumStyleMergeType t -> jsonMergeTypeSumFormat t
jsonFieldNameSumFormat :: (a -> (Text, Aeson.Value)) -> NonEmpty (Text, FromJson e a) -> JsonFormat e a
jsonFieldNameSumFormat oA iAs =
JsonFormat (JsonProfunctor o i)
where
expected = expectedFieldsForInputs iAs
o a = let (t, v) = oA a in Aeson.object [t .= v]
i = do
fields <- ABE.withObject $ pure . StrictHashMap.keys
case fields of
[f] ->
case lookup f (NEL.toList iAs) of
Just (FromJson iA) -> ABE.key f iA
Nothing -> fail $ "unknown field " <> unpack f <> ", expected one of " <> expected
[] ->
fail $ "expected an object with one field (" <> expected <> ") not an empty object"
_ ->
fail $ "expected an object with one field (" <> expected <> ") not many fields"
jsonTypeValueSumFormat :: Text -> Text -> (a -> (Text, Aeson.Value)) -> NonEmpty (Text, FromJson e a) -> JsonFormat e a
jsonTypeValueSumFormat typeField valueField oA iAs =
JsonFormat (JsonProfunctor o i)
where
expected = expectedFieldsForInputs iAs
o a = let (t, v) = oA a in Aeson.object [typeField .= t, valueField .= v]
i = do
t <- ABE.key typeField ABE.asText
case lookup t (NEL.toList iAs) of
Just (FromJson iA) -> ABE.key valueField iA
Nothing -> toss $ "expected " <> unpack typeField <> " to be one of " <> expected
toss = throwError . ABE.BadSchema [] . ABE.FromAeson
jsonMergeTypeSumFormat :: Text -> (a -> (Text, Aeson.Value)) -> NonEmpty (Text, FromJson e a) -> JsonFormat e a
jsonMergeTypeSumFormat typeField oA iAs =
JsonFormat (JsonProfunctor o i)
where
expected = expectedFieldsForInputs iAs
o a = case oA a of
(t, Aeson.Object fields) | StrictHashMap.member typeField fields ->
error $ "PRECONDITION VIOLATED: encoding a value with merge type sum style yielded "
<> "(" <> unpack t <> ", " <> show (Aeson.Object fields) <> ") which already contains the field " <> unpack typeField
(t, Aeson.Object fields) ->
Aeson.Object (StrictHashMap.insert typeField (Aeson.String t) fields)
(t, other) ->
error $ "PRECONDITION VIOLATED: encoding a value with merge type sum style yielded "
<> "(" <> unpack t <> ", " <> show other <> ") which isn't an object"
i = do
t <- ABE.key typeField ABE.asText
case lookup t (NEL.toList iAs) of
Just (FromJson iA) -> iA
Nothing -> toss $ "expected " <> unpack typeField <> " to be one of " <> expected
toss = throwError . ABE.BadSchema [] . ABE.FromAeson