{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE NoImplicitPrelude #-} module Data.Morpheus.Client.CodeGen.Interpreting.Global ( toGlobalDefinitions, ) where import Data.Morpheus.Client.CodeGen.AST ( ClientDeclaration, ClientTypeDefinition (..), ) import Data.Morpheus.Client.CodeGen.Interpreting.Core (toClientDeclarations, toCodeGenField) import Data.Morpheus.Client.CodeGen.Interpreting.PreDeclarations ( mapPreDeclarations, ) import Data.Morpheus.CodeGen.Internal.AST ( CodeGenConstructor (..), CodeGenTypeName (..), fromTypeName, ) import Data.Morpheus.Internal.Ext (GQLResult) import Data.Morpheus.Types.Internal.AST ( ANY, DataEnumValue (DataEnumValue, enumName), Schema (Schema, types), TRUE, TypeContent (..), TypeDefinition (..), TypeKind (..), TypeName, VALID, isNotSystemTypeName, isResolverType, ) import Relude hiding (empty) toGlobalDefinitions :: (TypeName -> Bool) -> Schema VALID -> GQLResult [ClientDeclaration] toGlobalDefinitions :: (TypeName -> Bool) -> Schema VALID -> GQLResult [ClientDeclaration] toGlobalDefinitions TypeName -> Bool f Schema {TypeDefinitions VALID types :: TypeDefinitions VALID types :: forall (s :: Stage). Schema s -> TypeDefinitions s types} = forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) traverse forall (m :: * -> *). MonadFail m => ClientPreDeclaration -> m ClientDeclaration mapPreDeclarations forall a b. (a -> b) -> a -> b $ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap ClientTypeDefinition -> [ClientPreDeclaration] toClientDeclarations forall a b. (a -> b) -> a -> b $ forall a b. (a -> Maybe b) -> [a] -> [b] mapMaybe TypeDefinition ANY VALID -> Maybe ClientTypeDefinition generateGlobalType forall a b. (a -> b) -> a -> b $ forall a. (a -> Bool) -> [a] -> [a] filter TypeDefinition ANY VALID -> Bool shouldInclude (forall b a. Ord b => (a -> b) -> [a] -> [a] sortWith forall (a :: TypeCategory) (s :: Stage). TypeDefinition a s -> TypeName typeName forall a b. (a -> b) -> a -> b $ forall (t :: * -> *) a. Foldable t => t a -> [a] toList TypeDefinitions VALID types) where shouldInclude :: TypeDefinition ANY VALID -> Bool shouldInclude TypeDefinition ANY VALID t = Bool -> Bool not (forall t. Strictness t => t -> Bool isResolverType TypeDefinition ANY VALID t) Bool -> Bool -> Bool && TypeName -> Bool isNotSystemTypeName (forall (a :: TypeCategory) (s :: Stage). TypeDefinition a s -> TypeName typeName TypeDefinition ANY VALID t) Bool -> Bool -> Bool && TypeName -> Bool f (forall (a :: TypeCategory) (s :: Stage). TypeDefinition a s -> TypeName typeName TypeDefinition ANY VALID t) generateGlobalType :: TypeDefinition ANY VALID -> Maybe ClientTypeDefinition generateGlobalType :: TypeDefinition ANY VALID -> Maybe ClientTypeDefinition generateGlobalType TypeDefinition {TypeName typeName :: TypeName typeName :: forall (a :: TypeCategory) (s :: Stage). TypeDefinition a s -> TypeName typeName, TypeContent TRUE ANY VALID typeContent :: forall (a :: TypeCategory) (s :: Stage). TypeDefinition a s -> TypeContent TRUE a s typeContent :: TypeContent TRUE ANY VALID typeContent} = do (TypeKind clientKind, [CodeGenConstructor] clientCons) <- TypeContent TRUE ANY VALID -> Maybe (TypeKind, [CodeGenConstructor]) genContent TypeContent TRUE ANY VALID typeContent forall (f :: * -> *) a. Applicative f => a -> f a pure ClientTypeDefinition { clientTypeName :: CodeGenTypeName clientTypeName = TypeName -> CodeGenTypeName fromTypeName TypeName typeName, TypeKind clientKind :: TypeKind clientKind :: TypeKind clientKind, [CodeGenConstructor] clientCons :: [CodeGenConstructor] clientCons :: [CodeGenConstructor] clientCons } where genContent :: TypeContent TRUE ANY VALID -> Maybe (TypeKind, [CodeGenConstructor]) genContent :: TypeContent TRUE ANY VALID -> Maybe (TypeKind, [CodeGenConstructor]) genContent (DataInputObject FieldsDefinition IN VALID inputFields) = forall (f :: * -> *) a. Applicative f => a -> f a pure ( TypeKind KindInputObject, [ CodeGenConstructor { constructorName :: CodeGenTypeName constructorName = TypeName -> CodeGenTypeName fromTypeName TypeName typeName, constructorFields :: [CodeGenField] constructorFields = forall (a :: TypeCategory) (b :: Stage). FieldDefinition a b -> CodeGenField toCodeGenField forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall (t :: * -> *) a. Foldable t => t a -> [a] toList FieldsDefinition IN VALID inputFields } ] ) genContent (DataEnum DataEnum VALID enumTags) = forall (f :: * -> *) a. Applicative f => a -> f a pure (TypeKind KindEnum, forall (s :: Stage). TypeName -> DataEnumValue s -> CodeGenConstructor mkConsEnum TypeName typeName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> DataEnum VALID enumTags) genContent DataScalar {} = forall (f :: * -> *) a. Applicative f => a -> f a pure (TypeKind KindScalar, []) genContent TypeContent TRUE ANY VALID _ = forall a. Maybe a Nothing mkConsEnum :: TypeName -> DataEnumValue s -> CodeGenConstructor mkConsEnum :: forall (s :: Stage). TypeName -> DataEnumValue s -> CodeGenConstructor mkConsEnum TypeName typename DataEnumValue {TypeName enumName :: TypeName enumName :: forall (s :: Stage). DataEnumValue s -> TypeName enumName} = CodeGenTypeName -> [CodeGenField] -> CodeGenConstructor CodeGenConstructor ([FieldName] -> [Text] -> TypeName -> CodeGenTypeName CodeGenTypeName [coerce :: forall a b. Coercible a b => a -> b coerce TypeName typename] [] TypeName enumName) []