{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
module Crypto.JOSE.TH
  (
    deriveJOSEType
  ) where
import Data.Aeson
import Data.Char
import Language.Haskell.TH.Lib
import Language.Haskell.TH.Syntax
capitalize :: String -> String
capitalize (x:xs) = toUpper x:xs
capitalize s = s
sanitize :: String -> String
sanitize = map (\c -> if isAlphaNum c then c else '_')
conize :: String -> Name
conize = mkName . capitalize . sanitize
guardPred :: String -> ExpQ
guardPred s = [e| $(varE $ mkName "s") == s |]
guardExp :: String -> ExpQ
guardExp s = [e| pure $(conE $ conize s) |]
guard :: String -> Q (Guard, Exp)
guard s = normalGE (guardPred s) (guardExp s)
endGuardPred :: ExpQ
endGuardPred = [e| otherwise |]
endGuardExp :: String -> ExpQ
endGuardExp s = [e| fail ("unrecognised value; expected: " ++ s) |]
endGuard :: String -> Q (Guard, Exp)
endGuard s = normalGE endGuardPred (endGuardExp s)
guardedBody :: [String] -> BodyQ
guardedBody vs = guardedB (map guard vs ++ [endGuard (show vs)])
parseJSONClauseQ :: [String] -> ClauseQ
parseJSONClauseQ vs = clause [varP $ mkName "s"] (guardedBody vs) []
parseJSONFun :: [String] -> DecQ
parseJSONFun vs = funD 'parseJSON [parseJSONClauseQ vs]
toJSONClause :: String -> ClauseQ
toJSONClause s = clause [conP (conize s) []] (normalB [| s |]) []
toJSONFun :: [String] -> DecQ
toJSONFun vs = funD 'toJSON (map toJSONClause vs)
aesonInstance :: String -> Name -> TypeQ
aesonInstance s n = appT (conT n) (conT $ mkName s)
deriveJOSEType
  :: String
  
  -> [String]
  
  
  
  -> Q [Dec]
deriveJOSEType s vs = sequenceQ [
  let
    derive = map mkName ["Eq", "Ord", "Show"]
  in
#if ! MIN_VERSION_template_haskell(2,11,0)
    dataD (cxt []) (mkName s) [] (map conQ vs) derive
#elif ! MIN_VERSION_template_haskell(2,12,0)
    dataD (cxt []) (mkName s) [] Nothing (map conQ vs) (mapM conT derive)
#else
    dataD (cxt []) (mkName s) [] Nothing (map conQ vs) [return (DerivClause Nothing (map ConT derive))]
#endif
  , instanceD (cxt []) (aesonInstance s ''FromJSON) [parseJSONFun vs]
  , instanceD (cxt []) (aesonInstance s ''ToJSON) [toJSONFun vs]
  ]
  where
    conQ v = normalC (conize v) []