/src/Data/Morpheus/Server/Deriving/Schema/Internal.hs

https://github.com/morpheusgraphql/morpheus-graphql · Haskell · 373 lines · 302 code · 43 blank · 28 comment · 3 complexity · c782e2dc4ee0232f8d20bef7e35873f3 MD5 · raw file

  1. {-# LANGUAGE ConstraintKinds #-}
  2. {-# LANGUAGE DataKinds #-}
  3. {-# LANGUAGE DefaultSignatures #-}
  4. {-# LANGUAGE FlexibleContexts #-}
  5. {-# LANGUAGE FlexibleInstances #-}
  6. {-# LANGUAGE GADTs #-}
  7. {-# LANGUAGE MultiParamTypeClasses #-}
  8. {-# LANGUAGE NamedFieldPuns #-}
  9. {-# LANGUAGE OverloadedStrings #-}
  10. {-# LANGUAGE PolyKinds #-}
  11. {-# LANGUAGE RankNTypes #-}
  12. {-# LANGUAGE RecordWildCards #-}
  13. {-# LANGUAGE StandaloneDeriving #-}
  14. {-# LANGUAGE TemplateHaskell #-}
  15. {-# LANGUAGE TypeApplications #-}
  16. {-# LANGUAGE TypeFamilies #-}
  17. {-# LANGUAGE TypeOperators #-}
  18. {-# LANGUAGE UndecidableInstances #-}
  19. {-# LANGUAGE NoImplicitPrelude #-}
  20. module Data.Morpheus.Server.Deriving.Schema.Internal
  21. ( KindedProxy (..),
  22. KindedType (..),
  23. builder,
  24. inputType,
  25. outputType,
  26. setProxyType,
  27. unpackMs,
  28. UpdateDef (..),
  29. withObject,
  30. TyContentM,
  31. asObjectType,
  32. fromSchema,
  33. updateByContent,
  34. )
  35. where
  36. -- MORPHEUS
  37. import Control.Applicative (Applicative (..))
  38. import Control.Monad.Fail (fail)
  39. import Data.Foldable (concatMap, traverse_)
  40. import Data.Functor (($>), (<$>), Functor (..))
  41. import Data.List (partition)
  42. import qualified Data.Map as M
  43. import Data.Maybe (Maybe (..), fromMaybe)
  44. import Data.Morpheus.Error (globalErrorMessage)
  45. import Data.Morpheus.Internal.Utils
  46. ( Failure (..),
  47. singleton,
  48. )
  49. import Data.Morpheus.Server.Deriving.Utils
  50. ( ConsRep (..),
  51. FieldRep (..),
  52. ResRep (..),
  53. fieldTypeName,
  54. isEmptyConstraint,
  55. isUnionRef,
  56. )
  57. import Data.Morpheus.Server.Types.GQLType
  58. ( GQLType (..),
  59. TypeData (..),
  60. )
  61. import Data.Morpheus.Server.Types.SchemaT
  62. ( SchemaT,
  63. insertType,
  64. updateSchema,
  65. )
  66. import Data.Morpheus.Types.Internal.AST
  67. ( CONST,
  68. DataEnumValue (..),
  69. Description,
  70. Directives,
  71. FieldContent (..),
  72. FieldDefinition (..),
  73. FieldName,
  74. FieldName (..),
  75. FieldsDefinition,
  76. IN,
  77. LEAF,
  78. OBJECT,
  79. OUT,
  80. Schema (..),
  81. TRUE,
  82. Token,
  83. TypeCategory,
  84. TypeContent (..),
  85. TypeDefinition (..),
  86. TypeName (..),
  87. UnionMember (..),
  88. VALID,
  89. mkEnumContent,
  90. mkField,
  91. mkInputValue,
  92. mkType,
  93. mkUnionMember,
  94. msg,
  95. unsafeFromFields,
  96. )
  97. import Data.Morpheus.Types.Internal.Resolving
  98. ( Eventless,
  99. Result (..),
  100. )
  101. import Data.Semigroup ((<>))
  102. import Data.Traversable (traverse)
  103. import Language.Haskell.TH (Exp, Q)
  104. import Prelude
  105. ( ($),
  106. (.),
  107. Bool (..),
  108. Show (..),
  109. map,
  110. null,
  111. otherwise,
  112. sequence,
  113. )
  114. -- | context , like Proxy with multiple parameters
  115. -- * 'kind': object, scalar, enum ...
  116. -- * 'a': actual gql type
  117. data KindedProxy k a
  118. = KindedProxy
  119. data KindedType (cat :: TypeCategory) a where
  120. InputType :: KindedType IN a
  121. OutputType :: KindedType OUT a
  122. -- converts:
  123. -- f a -> KindedType IN a
  124. -- or
  125. -- f k a -> KindedType IN a
  126. inputType :: f a -> KindedType IN a
  127. inputType _ = InputType
  128. outputType :: f a -> KindedType OUT a
  129. outputType _ = OutputType
  130. deriving instance Show (KindedType cat a)
  131. setProxyType :: f b -> kinded k a -> KindedProxy k b
  132. setProxyType _ _ = KindedProxy
  133. fromSchema :: Eventless (Schema VALID) -> Q Exp
  134. fromSchema Success {} = [|()|]
  135. fromSchema Failure {errors} = fail (show errors)
  136. withObject :: (GQLType a) => KindedType c a -> TypeContent TRUE any s -> SchemaT (FieldsDefinition c s)
  137. withObject InputType DataInputObject {inputObjectFields} = pure inputObjectFields
  138. withObject OutputType DataObject {objectFields} = pure objectFields
  139. withObject x _ = failureOnlyObject x
  140. asObjectType ::
  141. GQLType a =>
  142. (f2 a -> SchemaT (FieldsDefinition OUT CONST)) ->
  143. f2 a ->
  144. SchemaT (TypeDefinition OBJECT CONST)
  145. asObjectType f proxy = (`mkObjectType` gqlTypeName (__type proxy)) <$> f proxy
  146. mkObjectType :: FieldsDefinition OUT CONST -> TypeName -> TypeDefinition OBJECT CONST
  147. mkObjectType fields typeName = mkType typeName (DataObject [] fields)
  148. failureOnlyObject :: forall c a b. (GQLType a) => KindedType c a -> SchemaT b
  149. failureOnlyObject proxy =
  150. failure
  151. $ globalErrorMessage
  152. $ msg (gqlTypeName $ __type proxy) <> " should have only one nonempty constructor"
  153. type TyContentM kind = (SchemaT (Maybe (FieldContent TRUE kind CONST)))
  154. type TyContent kind = Maybe (FieldContent TRUE kind CONST)
  155. unpackM :: FieldRep (TyContentM k) -> SchemaT (FieldRep (TyContent k))
  156. unpackM FieldRep {..} =
  157. FieldRep fieldSelector fieldTypeRef fieldIsObject
  158. <$> fieldValue
  159. unpackCons :: ConsRep (TyContentM k) -> SchemaT (ConsRep (TyContent k))
  160. unpackCons ConsRep {..} = ConsRep consName <$> traverse unpackM consFields
  161. unpackMs :: [ConsRep (TyContentM k)] -> SchemaT [ConsRep (TyContent k)]
  162. unpackMs = traverse unpackCons
  163. builder ::
  164. GQLType a =>
  165. KindedType kind a ->
  166. [ConsRep (TyContent kind)] ->
  167. SchemaT (TypeContent TRUE kind CONST)
  168. builder scope [ConsRep {consFields}] = buildObj <$> sequence (implements scope)
  169. where
  170. buildObj interfaces = wrapFields interfaces scope (mkFieldsDefinition consFields)
  171. builder scope cons = genericUnion cons
  172. where
  173. typeData = __type scope
  174. genericUnion =
  175. mkUnionType scope typeData
  176. . analyseRep (gqlTypeName typeData)
  177. class UpdateDef value where
  178. updateDef :: GQLType a => f a -> value -> value
  179. instance UpdateDef (TypeContent TRUE c CONST) where
  180. updateDef proxy DataObject {objectFields = fields, ..} =
  181. DataObject {objectFields = fmap (updateDef proxy) fields, ..}
  182. updateDef proxy DataInputObject {inputObjectFields = fields} =
  183. DataInputObject {inputObjectFields = fmap (updateDef proxy) fields, ..}
  184. updateDef proxy DataInterface {interfaceFields = fields} =
  185. DataInterface {interfaceFields = fmap (updateDef proxy) fields, ..}
  186. updateDef proxy (DataEnum enums) = DataEnum $ fmap (updateDef proxy) enums
  187. updateDef _ x = x
  188. instance GetFieldContent cat => UpdateDef (FieldDefinition cat CONST) where
  189. updateDef proxy FieldDefinition {fieldName, fieldType, fieldContent} =
  190. FieldDefinition
  191. { fieldName,
  192. fieldDescription = lookupDescription (readName fieldName) proxy,
  193. fieldDirectives = lookupDirectives (readName fieldName) proxy,
  194. fieldContent = getFieldContent fieldName fieldContent proxy,
  195. ..
  196. }
  197. instance UpdateDef (DataEnumValue CONST) where
  198. updateDef proxy DataEnumValue {enumName} =
  199. DataEnumValue
  200. { enumName,
  201. enumDescription = lookupDescription (readTypeName enumName) proxy,
  202. enumDirectives = lookupDirectives (readTypeName enumName) proxy
  203. }
  204. lookupDescription :: GQLType a => Token -> f a -> Maybe Description
  205. lookupDescription name = (name `M.lookup`) . getDescriptions
  206. lookupDirectives :: GQLType a => Token -> f a -> Directives CONST
  207. lookupDirectives name = fromMaybe [] . (name `M.lookup`) . getDirectives
  208. class GetFieldContent c where
  209. getFieldContent :: GQLType a => FieldName -> Maybe (FieldContent TRUE c CONST) -> f a -> Maybe (FieldContent TRUE c CONST)
  210. instance GetFieldContent IN where
  211. getFieldContent name val proxy =
  212. case name `M.lookup` getFieldContents proxy of
  213. Just (Just x, _) -> Just (DefaultInputValue x)
  214. _ -> val
  215. instance GetFieldContent OUT where
  216. getFieldContent name args proxy =
  217. case name `M.lookup` getFieldContents proxy of
  218. Just (_, Just x) -> Just (FieldArgs x)
  219. _ -> args
  220. updateByContent ::
  221. GQLType a =>
  222. (f kind a -> SchemaT (TypeContent TRUE cat CONST)) ->
  223. f kind a ->
  224. SchemaT ()
  225. updateByContent f proxy =
  226. updateSchema
  227. (gqlFingerprint $ __type proxy)
  228. deriveD
  229. proxy
  230. where
  231. deriveD =
  232. fmap
  233. ( TypeDefinition
  234. (description proxy)
  235. (gqlTypeName (__type proxy))
  236. []
  237. )
  238. . f
  239. analyseRep :: TypeName -> [ConsRep (Maybe (FieldContent TRUE kind CONST))] -> ResRep (Maybe (FieldContent TRUE kind CONST))
  240. analyseRep baseName cons =
  241. ResRep
  242. { enumCons = fmap consName enumRep,
  243. unionRef = fieldTypeName <$> concatMap consFields unionRefRep,
  244. unionRecordRep
  245. }
  246. where
  247. (enumRep, left1) = partition isEmptyConstraint cons
  248. (unionRefRep, unionRecordRep) = partition (isUnionRef baseName) left1
  249. mkUnionType ::
  250. KindedType kind a ->
  251. TypeData ->
  252. ResRep (Maybe (FieldContent TRUE kind CONST)) ->
  253. SchemaT (TypeContent TRUE kind CONST)
  254. mkUnionType InputType _ ResRep {unionRef = [], unionRecordRep = [], enumCons} = pure $ mkEnumContent enumCons
  255. mkUnionType OutputType _ ResRep {unionRef = [], unionRecordRep = [], enumCons} = pure $ mkEnumContent enumCons
  256. mkUnionType InputType _ ResRep {unionRef, unionRecordRep, enumCons} = DataInputUnion <$> typeMembers
  257. where
  258. typeMembers :: SchemaT [UnionMember IN CONST]
  259. typeMembers = withMembers <$> buildUnions unionRecordRep
  260. where
  261. withMembers unionMembers = fmap mkUnionMember (unionRef <> unionMembers) <> fmap (`UnionMember` False) enumCons
  262. mkUnionType OutputType typeData ResRep {unionRef, unionRecordRep, enumCons} = DataUnion . map mkUnionMember <$> typeMembers
  263. where
  264. typeMembers = do
  265. enums <- buildUnionEnum typeData enumCons
  266. unions <- buildUnions unionRecordRep
  267. pure (unionRef <> enums <> unions)
  268. wrapFields :: [TypeName] -> KindedType kind a -> FieldsDefinition kind CONST -> TypeContent TRUE kind CONST
  269. wrapFields _ InputType = DataInputObject
  270. wrapFields interfaces OutputType = DataObject interfaces
  271. mkFieldsDefinition :: [FieldRep (Maybe (FieldContent TRUE kind CONST))] -> FieldsDefinition kind CONST
  272. mkFieldsDefinition = unsafeFromFields . fmap fieldByRep
  273. fieldByRep :: FieldRep (Maybe (FieldContent TRUE kind CONST)) -> FieldDefinition kind CONST
  274. fieldByRep FieldRep {fieldSelector, fieldTypeRef, fieldValue} =
  275. mkField fieldValue fieldSelector fieldTypeRef
  276. buildUnions ::
  277. PackObject kind =>
  278. [ConsRep (Maybe (FieldContent TRUE kind CONST))] ->
  279. SchemaT [TypeName]
  280. buildUnions cons =
  281. traverse_ buildURecType cons $> fmap consName cons
  282. where
  283. buildURecType = insertType . buildUnionRecord
  284. buildUnionRecord ::
  285. PackObject kind =>
  286. ConsRep (Maybe (FieldContent TRUE kind CONST)) ->
  287. TypeDefinition kind CONST
  288. buildUnionRecord ConsRep {consName, consFields} =
  289. mkType consName (packObject $ mkFieldsDefinition consFields)
  290. class PackObject kind where
  291. packObject :: FieldsDefinition kind CONST -> TypeContent TRUE kind CONST
  292. instance PackObject OUT where
  293. packObject = DataObject []
  294. instance PackObject IN where
  295. packObject = DataInputObject
  296. buildUnionEnum ::
  297. TypeData ->
  298. [TypeName] ->
  299. SchemaT [TypeName]
  300. buildUnionEnum TypeData {gqlTypeName} enums = updates $> members
  301. where
  302. members
  303. | null enums = []
  304. | otherwise = [enumTypeWrapperName]
  305. enumTypeName = gqlTypeName <> "Enum"
  306. enumTypeWrapperName = enumTypeName <> "Object"
  307. -------------------------
  308. updates :: SchemaT ()
  309. updates
  310. | null enums = pure ()
  311. | otherwise =
  312. buildEnumObject enumTypeWrapperName enumTypeName
  313. *> buildEnum enumTypeName enums
  314. buildEnum :: TypeName -> [TypeName] -> SchemaT ()
  315. buildEnum typeName tags =
  316. insertType
  317. ( mkType typeName (mkEnumContent tags) ::
  318. TypeDefinition LEAF CONST
  319. )
  320. buildEnumObject :: TypeName -> TypeName -> SchemaT ()
  321. buildEnumObject typeName enumTypeName =
  322. insertType
  323. ( mkType
  324. typeName
  325. ( DataObject []
  326. $ singleton
  327. $ mkInputValue "enum" [] enumTypeName
  328. ) ::
  329. TypeDefinition OBJECT CONST
  330. )