module Data.Binary.Serialise.CBOR.JSON (
cborToJson,
jsonToCbor,
encodeJSON,
decodeJSON,
) where
import qualified Data.Aeson as JSON
import qualified Data.Scientific as Scientific
import qualified Data.Vector as Vec
import qualified Data.HashMap.Strict as HashMap
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified Data.Text.Lazy as Text.Lazy
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as LBS
import qualified Data.ByteString.Base64 as Base64
import qualified Data.ByteString.Base16 as Base16
import Codec.Serialise.Decoding
import Codec.Serialise.Encoding
import Codec.CBOR.Term as CBOR
import Codec.Serialise
import Control.Applicative
import Prelude
instance Serialise JSON.Value where
encode = encodeJSON
decode = decodeJSON
encodeJSON :: JSON.Value -> Encoding
encodeJSON = encode . jsonToCbor
decodeJSON :: Decoder s JSON.Value
decodeJSON = cborToJson <$> decode
cborToJson :: CBOR.Term -> JSON.Value
cborToJson (CBOR.TInt n) = cborToJson (CBOR.TInteger (fromIntegral n))
cborToJson (CBOR.TBytes bs) = JSON.String (base64url bs)
cborToJson (CBOR.TBytesI bs) = JSON.String (base64url (LBS.toStrict bs))
cborToJson (CBOR.TString s) = JSON.String s
cborToJson (CBOR.TStringI s) = JSON.String (Text.Lazy.toStrict s)
cborToJson (TList vs) = JSON.Array (Vec.fromList (map cborToJson vs))
cborToJson (TMap kvs) = JSON.object [ (cborToJsonString k, cborToJson v)
| (k, v) <- kvs ]
cborToJson (TBool b) = JSON.Bool b
cborToJson TNull = JSON.Null
cborToJson (THalf f)
| isNaN f || isInfinite f = JSON.Null
| otherwise = JSON.Number (Scientific.fromFloatDigits f)
cborToJson (TFloat f)
| isNaN f || isInfinite f = JSON.Null
| otherwise = JSON.Number (Scientific.fromFloatDigits f)
cborToJson (TDouble f)
| isNaN f || isInfinite f = JSON.Null
| otherwise = JSON.Number (Scientific.fromFloatDigits f)
cborToJson (TSimple _) = JSON.Null
cborToJson (TInteger n) = JSON.Number (fromInteger n)
cborToJson (TTagged 21 (CBOR.TBytes bs)) = JSON.String (base64url bs)
cborToJson (TTagged 22 (CBOR.TBytes bs)) = JSON.String (base64 bs)
cborToJson (TTagged 23 (CBOR.TBytes bs)) = JSON.String (base16 bs)
cborToJson (TTagged _tag term) = cborToJson term
cborToJson (TListI kvs) = cborToJson (TList kvs)
cborToJson (TMapI kvs) = cborToJson (TMap kvs)
cborToJsonString :: CBOR.Term -> Text.Text
cborToJsonString (TInt n) = Text.pack (show n)
cborToJsonString (TInteger n) = Text.pack (show n)
cborToJsonString (TString s) = s
cborToJsonString (TStringI s) = Text.Lazy.toStrict s
cborToJsonString (TBytes bs) = base64url bs
cborToJsonString (TBytesI bs) = base64url (LBS.toStrict bs)
base64url :: ByteString -> Text
base64url = base64
base64 :: ByteString -> Text
base64 = Text.decodeLatin1 . Base64.encode
base16 :: ByteString -> Text
base16 = Text.decodeLatin1 . Base16.encode
jsonToCbor :: JSON.Value -> CBOR.Term
jsonToCbor (JSON.Object kvs) = CBOR.TMap [ (CBOR.TString k, jsonToCbor v)
| (k, v) <- HashMap.toList kvs ]
jsonToCbor (JSON.Array vs) = CBOR.TList [ jsonToCbor v | v <- Vec.toList vs ]
jsonToCbor (JSON.String str) = CBOR.TString str
jsonToCbor (JSON.Number n) = case Scientific.floatingOrInteger n of
Left d -> CBOR.TDouble d
Right i
| i >= fromIntegral (minBound :: Int) &&
i <= fromIntegral (maxBound :: Int)
-> CBOR.TInt (fromIntegral i)
| otherwise -> CBOR.TInteger i
jsonToCbor (JSON.Bool b) = CBOR.TBool b
jsonToCbor JSON.Null = CBOR.TNull