module Generics.Generic.Aeson
( gtoJson
, gparseJson
, GtoJson (..)
, GfromJson (..)
, formatLabel
, Settings (..)
, defaultSettings
, gtoJsonWithSettings
, gparseJsonWithSettings
) where
import Control.Applicative
import Control.Monad.State
import Data.Aeson
import Data.Aeson.Types hiding (GFromJSON, GToJSON)
import Data.Proxy
import Data.Text (Text)
import GHC.Generics
import Generics.Deriving.ConNames
import qualified Data.HashMap.Strict as H
import qualified Data.Text as T
import qualified Data.Vector as V
import Generics.Generic.Aeson.Util
class GtoJson f where
gtoJSONf :: Settings -> Bool -> Bool -> f a -> Either [Value] [(Text, Value)]
class GfromJson f where
gparseJSONf :: Settings -> Bool -> Bool -> Bool -> StateT [Value] Parser (f a)
instance GtoJson U1 where
gtoJSONf _ _ _ U1 = Right []
instance GfromJson U1 where
gparseJSONf _ _ _ _ = return U1
gtoJson
:: forall a. (Generic a, GtoJson (Rep a), ConNames (Rep a), GIsEnum (Rep a))
=> a -> Value
gtoJson = gtoJsonWithSettings defaultSettings
gtoJsonWithSettings
:: forall a. (Generic a, GtoJson (Rep a), ConNames (Rep a), GIsEnum (Rep a))
=> Settings -> a -> Value
gtoJsonWithSettings settings x =
case gtoJSONf settings (multipleConstructors $ conNames x) (isEnum (Proxy :: Proxy a)) (from x) of
Left [v] -> v
Left _ -> error "The impossible happened: multiple returned values in gtoJSON."
Right _ -> error "The impossible happened: labeled values returned in gtoJSON."
gparseJson
:: forall a. (Generic a, GfromJson (Rep a), ConNames (Rep a), GIsEnum (Rep a))
=> Value -> Parser a
gparseJson = gparseJsonWithSettings defaultSettings
gparseJsonWithSettings
:: forall a. (Generic a, GfromJson (Rep a), ConNames (Rep a), GIsEnum (Rep a))
=> Settings -> Value -> Parser a
gparseJsonWithSettings set
= fmap to
. evalStateT (gparseJSONf set (multipleConstructors $ conNames (undefined :: a)) False (isEnum (Proxy :: Proxy a)))
. return
instance ToJSON c => GtoJson (K1 a c) where
gtoJSONf _ _ _ (K1 a) = Left [toJSON a]
instance FromJSON c => GfromJson (K1 a c) where
gparseJSONf _ _ _ _ = lift . fmap K1 . parseJSON =<< pop
instance (GtoJson f, GtoJson g) => GtoJson (f :+: g) where
gtoJSONf set mc enm (L1 x) = gtoJSONf set mc enm x
gtoJSONf set mc enm (R1 x) = gtoJSONf set mc enm x
instance (GfromJson f, GfromJson g) => GfromJson (f :+: g) where
gparseJSONf set mc smf enm
= L1 <$> gparseJSONf set mc smf enm
<|> R1 <$> gparseJSONf set mc smf enm
instance (GtoJson f, GtoJson g) => GtoJson (f :*: g) where
gtoJSONf set mc enm (x :*: y) =
case (gtoJSONf set mc enm x, gtoJSONf set mc enm y) of
(Left xvs, Left yvs) -> Left (xvs ++ yvs)
(Right xvs, Right yvs) -> Right (xvs ++ yvs)
_ -> error "The impossible happened: product of mixed label and non-label fields in GJSON instance for (:*:)."
instance (GfromJson f, GfromJson g) => GfromJson (f :*: g) where
gparseJSONf set mc smf enm =
do unless smf selFields
(:*:) <$> gparseJSONf set mc True enm <*> gparseJSONf set mc True enm
where
selFields =
do v <- pop
case v of
o@Object{} -> put (repeat o)
Array vs -> put (V.toList vs)
_ -> fail "Expected object or array in gparseJSONf for (:*:)."
instance GtoJson f => GtoJson (M1 D c f) where
gtoJSONf set a b (M1 x) = gtoJSONf set a b x
instance GfromJson f => GfromJson (M1 D c f) where
gparseJSONf set a b x = M1 <$> gparseJSONf set a b x
instance (Constructor c, GtoJson f) => GtoJson (M1 C c f) where
gtoJSONf set _ True (M1 _) = Left [toJSON $ conNameT set (undefined :: M1 C c f p)]
gtoJSONf set mc False (M1 x) =
case gtoJSONf set mc False x of
Left [v] -> Left [wrap v]
Left vs -> Left [wrap . Array $ V.fromList vs]
Right vs -> Left [wrap $ toObject vs]
where
wrap = if mc
then toObject
. return
. (conNameT set (undefined :: M1 C c f p), )
else id
instance (Constructor c, GfromJson f) => GfromJson (M1 C c f) where
gparseJSONf set mc smf True =
do str <- pop
conStr <- lift (parseJSON str)
let expectedConStr = conNameT set (undefined :: M1 C c f p)
unless (conStr == expectedConStr) $
fail $ "Error parsing enumeration: expected " ++ T.unpack expectedConStr ++ ", found " ++ T.unpack conStr ++ "."
M1 <$> gparseJSONf set mc smf True
gparseJSONf set mc smf False =
do
when mc (selProp "C" propName)
M1 <$> gparseJSONf set mc smf False
where
propName = case conNameT set (undefined :: M1 C c f p) of
"" -> Nothing
n -> Just n
instance (Selector c, GtoJson f) => GtoJson (M1 S c f) where
gtoJSONf set mc enm (M1 x) =
case gtoJSONf set mc enm x of
Left [v] -> case selNameT set (undefined :: M1 S c f p) of
Nothing -> Left [v]
Just n -> Right [(n, v)]
Left _ -> error "The impossible happened: multiple returned values inside label in GJSON instance for S."
Right _ -> error "The impossible happened: label inside a label in GJSON instance for S."
instance (Selector c, GfromJson f) => GfromJson (M1 S c f) where
gparseJSONf set mc smf enm =
do selProp "S" propName
M1 <$> gparseJSONf set mc smf enm
where
propName = selNameT set (undefined :: M1 S c f p)
instance (Selector c, ToJSON a) => GtoJson (M1 S c (K1 i (Maybe a))) where
gtoJSONf set _ _ (M1 (K1 n@Nothing)) = case selNameT set (undefined :: M1 S c f p) of
Nothing -> Left [toJSON n]
Just _ -> Right []
gtoJSONf set mc enm (M1 (K1 (Just x))) = gtoJSONf set mc enm (M1 (K1 x) :: (M1 S c (K1 i a)) p)
instance (Selector c, FromJSON a) => GfromJson (M1 S c (K1 i (Maybe a))) where
gparseJSONf set mc smf enm =
do M1 (K1 x) <- parser
return (M1 (K1 (Just x)))
<|>
do case selNameT set (undefined :: M1 S c (K1 i a) p) of
Nothing ->
do o <- pop
M1 . K1 <$> lift (parseJSON o)
Just n ->
do o <- pop
case o of
Object h | H.member n h -> error impossible <$> parser
| otherwise -> return $ M1 (K1 Nothing)
_ -> lift $ typeMismatch "Object" (Array V.empty)
where
parser = gparseJSONf set mc smf enm :: StateT [Value] Parser (M1 S c (K1 i a) p)
impossible = "The impossible happened: parser succeeded after failing in GfromJson S Maybe"
selProp :: Text -> Maybe Text -> StateT [Value] Parser ()
selProp cname propName =
case propName of
Nothing -> do o <- pop
modify (o:)
Just p -> do o <- pop
v <- lift (withObject ("Expected property " ++ show propName ++ " in object in gparseJSONf for " ++ show cname ++ ".")
(.: p) o)
modify (v:)
pop :: MonadState [Value] m => m Value
pop =
do (v:vs) <- get
put vs
return v
toObject :: ToJSON v => [(Text, v)] -> Value
toObject = object . map (uncurry (.=))