{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGuaGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGuaGE DeriveGeneric #-}
{-# LANGuaGE FlexibleContexts #-}
module Data.Aeson.AutoType.CodeGen.ElmFormat(
displaySplitTypes,
normalizeTypeName) where
import Control.Arrow ((&&&))
import Control.Applicative ((<$>), (<*>))
import Control.Lens.TH
import Control.Lens
import Control.Monad (forM)
import Control.Exception(assert)
import qualified Data.HashMap.Strict as Map
import Data.Monoid
import qualified Data.Set as Set
import qualified Data.Text as Text
import Data.Text (Text)
import Data.Set (Set, toList)
import Data.List (foldl1')
import Data.Char (isAlpha, isDigit)
import Control.Monad.State.Class
import Control.Monad.State.Strict(State, runState)
import GHC.Generics (Generic)
import Data.Aeson.AutoType.Type
import Data.Aeson.AutoType.Extract
import Data.Aeson.AutoType.Split
import Data.Aeson.AutoType.Format
import Data.Aeson.AutoType.Util ()
trace _ x = x
fst3 :: (t, t1, t2) -> t
fst3 (a, _b, _c) = a
data DeclState = DeclState { _decls :: [Text]
, _counter :: Int
}
deriving (Eq, Show, Ord, Generic)
makeLenses ''DeclState
type DeclM = State DeclState
type Map k v = Map.HashMap k v
stepM :: DeclM Int
stepM = counter %%= (\i -> (i, i+1))
tShow :: (Show a) => a -> Text
tShow = Text.pack . show
wrapAlias :: Text -> Text -> Text
wrapAlias identifier contents = Text.unwords ["type alias ", identifier, "=", contents]
wrapDecl :: Text -> Text -> Text
wrapDecl identifier contents = Text.unlines [header, contents, " }"]
where
header = Text.concat ["type alias ", identifier, " = ", " { "]
type MappedKey = (Text, Text, Text, Type, Bool)
makeDecoder :: Text -> [MappedKey] -> Text
makeDecoder identifier contents =
Text.unlines [
Text.concat [decodeIdentifier, " : Json.Decode.Decoder ", identifier]
, Text.concat [decodeIdentifier, " ="]
, Text.unwords [" Json.Decode.Pipeline.decode", identifier]
, Text.unlines (makeParser identifier <$> contents) ]
where
decodeIdentifier = decoderIdent identifier
makeParser identifier (jsonId, _, _, ty, isOptional) = Text.unwords [
" |>"
, if isOptional
then "Json.Decode.Pipeline.optional"
else "Json.Decode.Pipeline.required"
, Text.concat ["\"", jsonId, "\""]
, "(" <> getDecoder ty <> ")"]
getDecoder TString = "Json.Decode.string"
getDecoder TNum = "Json.Decode.float"
getDecoder TBool = "Json.Decode.bool"
getDecoder (TArray t) = "Json.Decode.list (" <> getDecoder t <> ")"
getDecoder (TLabel l) = decoderIdent l
getDecoder (TObj o) = error "getDecoder cannot handle complex object types!"
getDecoder (TUnion u) = case nonNull of
[] -> "Json.Decode.value"
[x] -> getDecoder x
_ -> foldl1' altDecoder $ map getDecoder nonNull
where
nonNull = nonNullComponents u
altDecoder a b = "(Json.Decode.oneOf [Json.Decode.map Either.Left ("
<> a <> "), Json.Decode.map Either.Right ("
<> b <> ")])"
decoderIdent ident = "decode" <> capitalize (normalizeTypeName ident)
encoderIdent ident = "encode" <> capitalize (normalizeTypeName ident)
makeEncoder :: Text -> [MappedKey] -> Text
makeEncoder identifier contents =
Text.unlines [
Text.unwords [encoderIdent identifier, ":", identifier, "->", "Json.Encode.Value"]
, encoderIdent identifier <> " record ="
, " Json.Encode.object ["
, " " <> (joinWith "\n , " (makeEncoder <$> contents))
, " ]"
]
where
makeEncoder (jsonId, haskellId, _typeText, ty, _nullable) = Text.concat [
"(", tShow jsonId, ", (", getEncoder ty, ") record.", normalizeFieldName identifier jsonId, ")"
]
escapeText = Text.pack . show . Text.unpack
getEncoder :: Type -> Text
getEncoder TString = "Json.Encode.string"
getEncoder TNum = "Json.Encode.float"
getEncoder TBool = "Json.Encode.bool"
getEncoder TNull = "identity"
getEncoder (TLabel l) = encoderIdent l
getEncoder (TArray e) = "Json.Encode.list << List.map (" <> getEncoder e <> ")"
getEncoder (TObj o) = error $ "Seeing direct object encoder: " <> show o
getEncoder (TUnion u) = case nonNull of
[] -> "identity"
[x] -> getDecoder x
_ -> foldl1' altEncoder $ map getEncoder nonNull
where
nonNull = nonNullComponents u
altEncoder a b = "Either.unpack (" <> a <> ") (" <> b <> ")"
joinWith :: Text -> [Text] -> Text
joinWith _ [] = ""
joinWith joiner (aFirst:rest) = aFirst <> Text.concat (map (joiner <>) rest)
genericIdentifier :: DeclM Text
genericIdentifier = do
i <- stepM
return $! "Obj" `Text.append` tShow i
newDecl :: Text -> [(Text, Type)] -> DeclM Text
newDecl identifier kvs = do attrs <- forM kvs $ \(k, v) -> do
formatted <- formatType v
return (k, normalizeFieldName identifier k, formatted, v, isNullable v)
let decl = Text.unlines [wrapDecl identifier $ fieldDecls attrs
,""
,makeDecoder identifier attrs
,""
,makeEncoder identifier attrs]
addDecl decl
return identifier
where
fieldDecls attrList = Text.intercalate ",\n" $ map fieldDecl attrList
fieldDecl :: (Text, Text, Text, Type, Bool) -> Text
fieldDecl (_jsonName, haskellName, fType, _type, _nullable) = Text.concat [
" ", haskellName, " : ", fType]
addDecl decl = decls %%= (\ds -> ((), decl:ds))
newAlias :: Text -> Type -> DeclM Text
newAlias identifier content = do formatted <- formatType content
addDecl $ Text.unlines [wrapAlias identifier formatted]
return identifier
normalizeFieldName :: Text -> Text -> Text
normalizeFieldName identifier = escapeKeywords .
uncapitalize .
(normalizeTypeName identifier `Text.append`) .
normalizeTypeName
keywords :: Set Text
keywords = Set.fromList ["type", "alias", "exposing", "module", "class",
"where", "let", "do"]
escapeKeywords :: Text -> Text
escapeKeywords k | k `Set.member` keywords = k `Text.append` "_"
escapeKeywords k = k
nonNullComponents = Set.toList . Set.filter (TNull /=)
formatType :: Type -> DeclM Text
formatType TString = return "String"
formatType TNum = return "Float"
formatType TBool = return "Bool"
formatType (TLabel l) = return $ normalizeTypeName l
formatType (TUnion u) = wrap <$> case length nonNull of
0 -> return emptyTypeRepr
1 -> formatType $ head nonNull
_ -> foldl1' join <$> mapM formatType nonNull
where
nonNull = nonNullComponents u
wrap :: Text -> Text
wrap inner | TNull `Set.member` u = Text.concat ["(Maybe (", inner, "))"]
| otherwise = inner
join fAlt fOthers = Text.concat ["Either (", fAlt, ") (", fOthers, ")"]
formatType (TArray a) = do inner <- formatType a
return $ Text.concat ["List (", inner, ")"]
formatType (TObj o) = do ident <- genericIdentifier
newDecl ident d
where
d = Map.toList $ unDict o
formatType e | e `Set.member` emptySetLikes = return emptyTypeRepr
formatType t = return $ "ERROR: Don't know how to handle: " `Text.append` tShow t
emptyTypeRepr :: Text
emptyTypeRepr = "Json.Decode.Value"
runDecl :: DeclM a -> Text
runDecl decl = Text.unlines $ finalState ^. decls
where
initialState = DeclState [] 1
(_, finalState) = runState decl initialState
type TypeTree = Map Text [Type]
type TypeTreeM a = State TypeTree a
addType :: Text -> Type -> TypeTreeM ()
addType label typ = modify $ Map.insertWith (++) label [typ]
formatObjectType :: Text -> Type -> DeclM Text
formatObjectType identifier (TObj o) = newDecl identifier d
where
d = Map.toList $ unDict o
formatObjectType identifier other = newAlias identifier other
displaySplitTypes :: Map Text Type -> Text
displaySplitTypes dict = trace ("displaySplitTypes: " ++ show (toposort dict)) $ runDecl declarations
where
declarations =
forM (toposort dict) $ \(name, typ) ->
formatObjectType (normalizeTypeName name) typ
normalizeTypeName :: Text -> Text
normalizeTypeName s = ifEmpty "JsonEmptyKey" .
escapeKeywords .
escapeFirstNonAlpha .
Text.concat .
map capitalize .
filter (not . Text.null) .
Text.split (not . acceptableInVariable) $ s
where
ifEmpty x "" = x
ifEmpty _ nonEmpty = nonEmpty
acceptableInVariable c = isAlpha c || isDigit c
escapeFirstNonAlpha cs | Text.null cs = cs
escapeFirstNonAlpha cs@(Text.head -> c) | isAlpha c = cs
escapeFirstNonAlpha cs = "_" `Text.append` cs
allLabels :: Type -> [Text]
allLabels = flip go []
where
go (TLabel l) ls = l:ls
go (TArray t) ls = go t ls
go (TUnion u) ls = Set.foldr go ls u
go (TObj o) ls = Map.foldr go ls $ unDict o
go _other ls = ls
remapLabels :: Map Text Text -> Type -> Type
remapLabels ls (TObj o) = TObj $ Dict $ Map.map (remapLabels ls) $ unDict o
remapLabels ls (TArray t) = TArray $ remapLabels ls t
remapLabels ls (TUnion u) = TUnion $ Set.map (remapLabels ls) u
remapLabels ls (TLabel l) = TLabel $ Map.lookupDefault l l ls
remapLabels _ other = other