module Data.Aeson.Codec
( JSONCodec(..)
, defJSON
, ObjectParser, ObjectBuilder, ObjectCodec
, field, field'
, asObject
, ArrayParser, ArrayBuilder, ArrayCodec
, element, element'
, asArray
, arrayOf, arrayOf'
) where
import Control.Monad.Codec
import Data.Aeson
import Data.Aeson.Encoding
import qualified Data.Aeson.Encoding.Internal as AEI
import Data.Aeson.Types (Parser, Pair)
import Control.Monad.Reader
import Control.Monad.State
import Control.Monad.Writer.Strict
import qualified Data.Text as T
import qualified Data.Vector as V
data JSONCodec a = JSONCodec
{ parseJSONCodec :: Value -> Parser a
, toJSONCodec :: a -> Value
, toEncodingCodec :: a -> Encoding
}
defJSON :: (FromJSON a, ToJSON a) => JSONCodec a
defJSON = JSONCodec
{ parseJSONCodec = parseJSON
, toJSONCodec = toJSON
, toEncodingCodec = toEncoding
}
type ObjectParser = ReaderT Object Parser
type ObjectBuilder = Writer ( Series, Endo [ Pair ] )
type ObjectCodec a = Codec ObjectParser ObjectBuilder a
field' :: T.Text -> JSONCodec a -> ObjectCodec a
field' key valCodec = Codec
{ codecIn = ReaderT $ \obj -> (obj .: key) >>= parseJSONCodec valCodec
, codecOut = \val ->
writer
( val
, ( pair key (toEncodingCodec valCodec val)
, Endo ((key .= toJSONCodec valCodec val) :)
)
)
}
field :: (FromJSON a, ToJSON a) => T.Text -> ObjectCodec a
field key = field' key defJSON
asObject :: String -> ObjectCodec a -> JSONCodec a
asObject err objCodec = JSONCodec
{ parseJSONCodec = withObject err (runReaderT (codecIn objCodec))
, toJSONCodec = object . (`appEndo` []) . snd . execOut
, toEncodingCodec = pairs . fst . execOut
} where execOut = execWriter . codecOut objCodec
type ArrayParser = StateT [ Value ] Parser
type ArrayBuilder = Writer ( Series, [ Value ] )
type ArrayCodec a = Codec ArrayParser ArrayBuilder a
element' :: JSONCodec a -> ArrayCodec a
element' valCodec = Codec
{ codecIn = StateT $ \case
[] -> fail "Expected an element, got an empty list."
x : xs -> do
val <- parseJSONCodec valCodec x
return ( val, xs )
, codecOut = \val -> writer ( val, ( AEI.Value $ AEI.retagEncoding $ toEncodingCodec valCodec val, [ toJSONCodec valCodec val ] ) )
}
element :: (FromJSON a, ToJSON a) => ArrayCodec a
element = element' defJSON
asArray :: String -> ArrayCodec a -> JSONCodec a
asArray err arrCodec = JSONCodec
{ parseJSONCodec = withArray err $ \arr -> do
( val, leftover ) <- runStateT (codecIn arrCodec) (V.toList arr)
unless (null leftover) $ fail "Elements left over in parsed array."
return val
, toJSONCodec = Array . V.fromList . snd . execOut
, toEncodingCodec = \val -> case fst (execOut val) of
AEI.Empty -> emptyArray_
AEI.Value enc -> AEI.wrapArray enc
} where execOut = execWriter . codecOut arrCodec
arrayOf' :: (a -> [ b ]) -> ([ b ] -> a) -> JSONCodec b -> JSONCodec a
arrayOf' aToList listToA elemCodec = JSONCodec
{ parseJSONCodec = \arr -> do
vals <- parseJSON arr
parsedVals <- traverse (parseJSONCodec elemCodec) (vals :: [ Value ])
return (listToA parsedVals)
, toJSONCodec = Array . V.fromList . map (toJSONCodec elemCodec) . aToList
, toEncodingCodec = AEI.list (toEncodingCodec elemCodec) . aToList
}
arrayOf :: (FromJSON b, ToJSON b) => (a -> [ b ]) -> ([ b ] -> a) -> JSONCodec a
arrayOf aToList listToA = arrayOf' aToList listToA defJSON