module Data.API.Tools.CBOR
( cborTool
) where
import Data.API.TH
import Data.API.Tools.Combinators
import Data.API.Tools.Datatypes
import Data.API.Tools.Enum
import Data.API.Types
import Control.Applicative
import Codec.Serialise.Class
import Codec.Serialise.Decoding
import Codec.Serialise.Encoding
import Data.Binary.Serialise.CBOR.Extra
import Data.List (foldl', sortBy)
import qualified Data.Map as Map
import Data.Monoid
import Data.Ord (comparing)
import qualified Data.Text as T
import Language.Haskell.TH
import Prelude
cborTool :: APITool
cborTool = apiNodeTool $
apiSpecTool gen_sn_to gen_sr_to gen_su_to gen_se_to mempty
<> gen_pr
gen_sn_to :: Tool (APINode, SpecNewtype)
gen_sn_to = mkTool $ \ ts (an, sn) -> optionalInstanceD ts ''Serialise [nodeRepT an]
[ simpleD 'encode (bdy_in an sn)
, simpleD 'decode (bdy_out ts an sn)]
where
bdy_in an sn = [e| $(ine sn) . $(newtypeProjectionE an) |]
bdy_out ts an sn = [e| $(nodeNewtypeConE ts an sn) <$> $(oute sn) |]
ine sn = case snType sn of
BTstring -> [e| encodeString |]
BTbinary -> [e| encode |]
BTbool -> [e| encodeBool |]
BTint -> [e| encodeInt |]
BTutc -> [e| encode |]
oute sn =
case snType sn of
BTstring -> [e| decodeString |]
BTbinary -> [e| decode |]
BTbool -> [e| decodeBool |]
BTint -> [e| decodeInt |]
BTutc -> [e| decode |]
gen_sr_to :: Tool (APINode, SpecRecord)
gen_sr_to = mkTool $ \ ts (an, sr) -> do
x <- newName "x"
optionalInstanceD ts ''Serialise [nodeRepT an] [ simpleD 'encode (bdy_in an sr x)
, simpleD 'decode (cl an sr)
]
where
bdy_in an sr x =
let fields = sortFields sr
len = fromIntegral (length fields)
lenE = varE 'fromIntegral
`appE` (sigE (litE (integerL len))
(conT ''Integer))
writeRecordHeader = varE 'encodeMapLen `appE` lenE
encFields =
varE 'encodeRecordFields `appE`
listE [ [e| encodeString $(fieldNameE fn)
<> encode ($(nodeFieldE an fn) $(varE x)) |]
| (fn, _fty) <- fields ]
in lamE [varP x] $
varE '(<>)
`appE` writeRecordHeader
`appE` encFields
cl an sr = varE '(>>)
`appE` (varE 'decodeMapLen)
`appE` bdy
where
sorted_fields = map fst $ sortFields sr
original_fields = map fst $ srFields sr
bdy = applicativeE dataCon $ map project sorted_fields
project _fn = [e| decodeString >> decode |]
dataCon | sorted_fields == original_fields = nodeConE an
| otherwise = lamE (map (nodeFieldP an) sorted_fields)
(foldl' appE (nodeConE an) (map (nodeFieldE an) original_fields))
sortFields sr = sortBy (comparing fst) $ srFields sr
gen_su_to :: Tool (APINode, SpecUnion)
gen_su_to = mkTool $ \ ts (an, su) -> optionalInstanceD ts ''Serialise [nodeRepT an]
[ funD 'encode (cls an su)
, simpleD 'decode (bdy_out an su)
]
where
cls an su = map (cl an) (suFields su)
cl an (fn, (_ty, _)) = do
x <- newName "x"
clause [nodeAltConP an fn [varP x]] (bdy fn x) []
bdy fn x = normalB [e| encodeUnion $(fieldNameE fn) (encode $(varE x)) |]
bdy_out an su = varE 'decodeUnion `appE` listE (map (alt an) (suFields su))
alt an (fn, _) = [e| ( $(fieldNameE fn) , fmap $(nodeAltConE an fn) decode ) |]
gen_se_to :: Tool (APINode, SpecEnum)
gen_se_to = mkTool $ \ ts (an, _se) -> optionalInstanceD ts ''Serialise [nodeRepT an]
[ simpleD 'encode (bdy_in an)
, simpleD 'decode (bdy_out an)
]
where
bdy_in an = [e| encodeString . $(varE (text_enum_nm an)) |]
bdy_out an = [e| decodeString >>= cborStrMap_p $(varE (map_enum_nm an)) |]
cborStrMap_p :: (Monad m, Ord a) => Map.Map T.Text a -> T.Text -> m a
cborStrMap_p mp t = case Map.lookup t mp of
Nothing -> fail "Unexpected enumeration key in CBOR"
Just r -> return r
gen_pr :: Tool APINode
gen_pr = mkTool $ \ ts an -> case anConvert an of
Nothing -> return []
Just (inj_fn, prj_fn) -> optionalInstanceD ts ''Serialise [nodeT an] [ simpleD 'encode bdy_in
, simpleD 'decode bdy_out
]
where
bdy_in = [e| encode . $(fieldNameVarE prj_fn) |]
bdy_out = [e| decode >>= $(fieldNameVarE inj_fn) |]