{-# language DeriveGeneric #-}
{-# language OverloadedStrings #-}
{-# language TypeSynonymInstances #-}
{-# language FlexibleInstances #-}
module Data.Aeson.AutoType.Nested(
defaultImportedModules
, generateModuleImports
, inferType
, CodeFrag(..)
, TypeName
, TypeFrag
, ModuleImport
, PackageName
) where
import Data.Aeson
import Data.Aeson.AutoType.CodeGen.Haskell(generateModuleImports, requiredPackages, importedModules, ModuleImport)
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 Code = Text
type TypeName = Text
type PackageName = Text
data CodeFrag a = CodeFrag
{
CodeFrag a -> Code
codeFragCode :: Code
, CodeFrag a -> a
codeFragName :: a
, CodeFrag a -> [Code]
codeFragImports :: [ModuleImport]
, CodeFrag a -> [Code]
codeFragPackages :: [PackageName]
} deriving
( CodeFrag a -> CodeFrag a -> Bool
(CodeFrag a -> CodeFrag a -> Bool)
-> (CodeFrag a -> CodeFrag a -> Bool) -> Eq (CodeFrag a)
forall a. Eq a => CodeFrag a -> CodeFrag a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CodeFrag a -> CodeFrag a -> Bool
$c/= :: forall a. Eq a => CodeFrag a -> CodeFrag a -> Bool
== :: CodeFrag a -> CodeFrag a -> Bool
$c== :: forall a. Eq a => CodeFrag a -> CodeFrag a -> Bool
Eq
, Int -> CodeFrag a -> ShowS
[CodeFrag a] -> ShowS
CodeFrag a -> String
(Int -> CodeFrag a -> ShowS)
-> (CodeFrag a -> String)
-> ([CodeFrag a] -> ShowS)
-> Show (CodeFrag a)
forall a. Show a => Int -> CodeFrag a -> ShowS
forall a. Show a => [CodeFrag a] -> ShowS
forall a. Show a => CodeFrag a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CodeFrag a] -> ShowS
$cshowList :: forall a. Show a => [CodeFrag a] -> ShowS
show :: CodeFrag a -> String
$cshow :: forall a. Show a => CodeFrag a -> String
showsPrec :: Int -> CodeFrag a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CodeFrag a -> ShowS
Show
, (forall x. CodeFrag a -> Rep (CodeFrag a) x)
-> (forall x. Rep (CodeFrag a) x -> CodeFrag a)
-> Generic (CodeFrag a)
forall x. Rep (CodeFrag a) x -> CodeFrag a
forall x. CodeFrag a -> Rep (CodeFrag a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (CodeFrag a) x -> CodeFrag a
forall a x. CodeFrag a -> Rep (CodeFrag a) x
$cto :: forall a x. Rep (CodeFrag a) x -> CodeFrag a
$cfrom :: forall a x. CodeFrag a -> Rep (CodeFrag a) x
Generic
, Typeable
)
type TypeFrag = CodeFrag TypeName
instance Default TypeFrag where
def :: TypeFrag
def = CodeFrag :: forall a. Code -> a -> [Code] -> [Code] -> CodeFrag a
CodeFrag {
codeFragCode :: Code
codeFragCode = ""
, codeFragName :: Code
codeFragName = "Data.Aeson.Value"
, codeFragImports :: [Code]
codeFragImports = ["qualified Data.Aeson"]
, codeFragPackages :: [Code]
codeFragPackages = ["aeson"]
}
defaultImportedModules :: [Code]
defaultImportedModules = [Code]
importedModules
inferType :: Text -> [Value] -> TypeFrag
inferType :: Code -> [Value] -> TypeFrag
inferType typeName :: Code
typeName [] = TypeFrag
forall a. Default a => a
def
inferType typeName :: Code
typeName jsonValues :: [Value]
jsonValues =
CodeFrag :: forall a. Code -> a -> [Code] -> [Code] -> CodeFrag a
CodeFrag {
codeFragImports :: [Code]
codeFragImports = [Code]
defaultImportedModules
, codeFragCode :: Code
codeFragCode = Map Code Type -> Code
displaySplitTypes Map Code Type
splitTypeDescriptors
, codeFragName :: Code
codeFragName = Code
typeName
, codeFragPackages :: [Code]
codeFragPackages = [Code]
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 Code Type
splitTypeDescriptors = Code -> Type -> Map Code Type
splitTypeByLabel Code
typeName Type
unifiedType