{-# language DeriveGeneric #-}
{-# language OverloadedStrings #-}
module Data.Aeson.AutoType.Nested(
defaultImportedModules
, generateModuleImports
, inferType
, CodeFragment
, TypeName
, DeclaredType(..)
) where
import Data.Aeson
import Data.Aeson.AutoType.CodeGen.Haskell(generateModuleImports, requiredPackages, importedModules)
import Data.Aeson.AutoType.CodeGen.HaskellFormat(displaySplitTypes)
import Data.Aeson.AutoType.Extract(extractType, unifyTypes)
import Data.Aeson.AutoType.Split(splitTypeByLabel)
import Data.Default
import Data.Typeable
import Data.Text(Text)
import GHC.Generics
type CodeFragment = Text
type TypeName = Text
type ImportedModule = Text
type PackageName = Text
data DeclaredType = DeclaredType
{
DeclaredType -> CodeFragment
typeCodeFragment :: CodeFragment
, DeclaredType -> CodeFragment
typeName :: TypeName
, DeclaredType -> [CodeFragment]
typeImportedModules :: [ImportedModule]
, DeclaredType -> [CodeFragment]
typePackages :: [PackageName]
}
deriving
( DeclaredType -> DeclaredType -> Bool
(DeclaredType -> DeclaredType -> Bool)
-> (DeclaredType -> DeclaredType -> Bool) -> Eq DeclaredType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeclaredType -> DeclaredType -> Bool
$c/= :: DeclaredType -> DeclaredType -> Bool
== :: DeclaredType -> DeclaredType -> Bool
$c== :: DeclaredType -> DeclaredType -> Bool
Eq
, Int -> DeclaredType -> ShowS
[DeclaredType] -> ShowS
DeclaredType -> String
(Int -> DeclaredType -> ShowS)
-> (DeclaredType -> String)
-> ([DeclaredType] -> ShowS)
-> Show DeclaredType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeclaredType] -> ShowS
$cshowList :: [DeclaredType] -> ShowS
show :: DeclaredType -> String
$cshow :: DeclaredType -> String
showsPrec :: Int -> DeclaredType -> ShowS
$cshowsPrec :: Int -> DeclaredType -> ShowS
Show
, (forall x. DeclaredType -> Rep DeclaredType x)
-> (forall x. Rep DeclaredType x -> DeclaredType)
-> Generic DeclaredType
forall x. Rep DeclaredType x -> DeclaredType
forall x. DeclaredType -> Rep DeclaredType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeclaredType x -> DeclaredType
$cfrom :: forall x. DeclaredType -> Rep DeclaredType x
Generic
, Typeable
)
instance Default DeclaredType where
def :: DeclaredType
def = DeclaredType :: CodeFragment
-> CodeFragment -> [CodeFragment] -> [CodeFragment] -> DeclaredType
DeclaredType {
typeCodeFragment :: CodeFragment
typeCodeFragment = ""
, typeName :: CodeFragment
typeName = "Data.Aeson.Value"
, typeImportedModules :: [CodeFragment]
typeImportedModules = ["qualified Data.Aeson"]
, typePackages :: [CodeFragment]
typePackages = ["aeson"]
}
defaultImportedModules :: [CodeFragment]
defaultImportedModules = [CodeFragment]
importedModules
inferType :: Text -> [Value] -> DeclaredType
inferType :: CodeFragment -> [Value] -> DeclaredType
inferType typeName :: CodeFragment
typeName [] = DeclaredType
forall a. Default a => a
def
inferType typeName :: CodeFragment
typeName jsonValues :: [Value]
jsonValues =
DeclaredType :: CodeFragment
-> CodeFragment -> [CodeFragment] -> [CodeFragment] -> DeclaredType
DeclaredType {
typeImportedModules :: [CodeFragment]
typeImportedModules = [CodeFragment]
defaultImportedModules
, typeCodeFragment :: CodeFragment
typeCodeFragment = Map CodeFragment Type -> CodeFragment
displaySplitTypes Map CodeFragment Type
splitTypeDescriptors
, typeName :: CodeFragment
typeName = CodeFragment
typeName
, typePackages :: [CodeFragment]
typePackages = [CodeFragment]
requiredPackages
}
where
valueTypes :: [Type]
valueTypes = (Value -> Type) -> [Value] -> [Type]
forall a b. (a -> b) -> [a] -> [b]
map Value -> Type
extractType [Value]
jsonValues
unifiedType :: Type
unifiedType = (Type -> Type -> Type) -> [Type] -> Type
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 Type -> Type -> Type
unifyTypes [Type]
valueTypes
splitTypeDescriptors :: Map CodeFragment Type
splitTypeDescriptors = CodeFragment -> Type -> Map CodeFragment Type
splitTypeByLabel CodeFragment
typeName Type
unifiedType