{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE NoImplicitPrelude #-} module Data.Morpheus.Client.Transform.Global ( toArgumentsType, toGlobalDefinitions, ) where import Data.Morpheus.Client.Internal.Types ( ClientConstructorDefinition (..), ClientTypeDefinition (..), TypeNameTH (..), ) import Data.Morpheus.Internal.Utils ( empty, ) import Data.Morpheus.Types.Internal.AST ( ANY, DataEnumValue (DataEnumValue, enumName), FieldDefinition (..), RAW, Schema (Schema, types), TRUE, TypeContent (..), TypeDefinition (..), TypeKind (..), TypeName, VALID, Variable (..), VariableDefinitions, isNotSystemTypeName, isResolverType, toAny, ) import Relude hiding (empty) toArgumentsType :: TypeName -> VariableDefinitions RAW -> Maybe ClientTypeDefinition toArgumentsType :: TypeName -> VariableDefinitions RAW -> Maybe ClientTypeDefinition toArgumentsType TypeName cName VariableDefinitions RAW variables | forall (t :: * -> *) a. Foldable t => t a -> Bool null VariableDefinitions RAW variables = forall a. Maybe a Nothing | Bool otherwise = forall a. a -> Maybe a Just ClientTypeDefinition { clientTypeName :: TypeNameTH clientTypeName = [FieldName] -> TypeName -> TypeNameTH TypeNameTH [] TypeName cName, clientKind :: TypeKind clientKind = TypeKind KindInputObject, clientCons :: [ClientConstructorDefinition] clientCons = [ ClientConstructorDefinition { TypeName cName :: TypeName cName :: TypeName cName, cFields :: [FieldDefinition ANY VALID] cFields = Variable RAW -> FieldDefinition ANY VALID toFieldDefinition forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> forall (t :: * -> *) a. Foldable t => t a -> [a] toList VariableDefinitions RAW variables } ] } toFieldDefinition :: Variable RAW -> FieldDefinition ANY VALID toFieldDefinition :: Variable RAW -> FieldDefinition ANY VALID toFieldDefinition Variable {FieldName variableName :: forall (stage :: Stage). Variable stage -> FieldName variableName :: FieldName variableName, TypeRef variableType :: forall (stage :: Stage). Variable stage -> TypeRef variableType :: TypeRef variableType} = FieldDefinition { fieldName :: FieldName fieldName = FieldName variableName, fieldContent :: Maybe (FieldContent TRUE ANY VALID) fieldContent = forall a. Maybe a Nothing, fieldType :: TypeRef fieldType = TypeRef variableType, fieldDescription :: Maybe Description fieldDescription = forall a. Maybe a Nothing, fieldDirectives :: Directives VALID fieldDirectives = forall coll. Empty coll => coll empty } toGlobalDefinitions :: (TypeName -> Bool) -> Schema VALID -> [ClientTypeDefinition] toGlobalDefinitions :: (TypeName -> Bool) -> Schema VALID -> [ClientTypeDefinition] toGlobalDefinitions TypeName -> Bool f Schema {TypeDefinitions VALID types :: TypeDefinitions VALID types :: forall (s :: Stage). Schema s -> TypeDefinitions s types} = 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 (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, [ClientConstructorDefinition] clientCons) <- TypeContent TRUE ANY VALID -> Maybe (TypeKind, [ClientConstructorDefinition]) genContent TypeContent TRUE ANY VALID typeContent forall (f :: * -> *) a. Applicative f => a -> f a pure ClientTypeDefinition { clientTypeName :: TypeNameTH clientTypeName = [FieldName] -> TypeName -> TypeNameTH TypeNameTH [] TypeName typeName, TypeKind clientKind :: TypeKind clientKind :: TypeKind clientKind, [ClientConstructorDefinition] clientCons :: [ClientConstructorDefinition] clientCons :: [ClientConstructorDefinition] clientCons } where genContent :: TypeContent TRUE ANY VALID -> Maybe (TypeKind, [ClientConstructorDefinition]) genContent :: TypeContent TRUE ANY VALID -> Maybe (TypeKind, [ClientConstructorDefinition]) genContent (DataInputObject FieldsDefinition IN VALID inputFields) = do forall (f :: * -> *) a. Applicative f => a -> f a pure ( TypeKind KindInputObject, [ ClientConstructorDefinition { cName :: TypeName cName = TypeName typeName, cFields :: [FieldDefinition ANY VALID] cFields = forall (a :: TypeCategory -> Stage -> *) (k :: TypeCategory) (s :: Stage). ToCategory a k ANY => a k s -> a ANY s toAny 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). DataEnumValue s -> ClientConstructorDefinition mkConsEnum 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 :: DataEnumValue s -> ClientConstructorDefinition mkConsEnum :: forall (s :: Stage). DataEnumValue s -> ClientConstructorDefinition mkConsEnum DataEnumValue {TypeName enumName :: TypeName enumName :: forall (s :: Stage). DataEnumValue s -> TypeName enumName} = TypeName -> [FieldDefinition ANY VALID] -> ClientConstructorDefinition ClientConstructorDefinition TypeName enumName []