1 {-# OPTIONS_GHC -fprint-potential-instances #-}
3 {-# LANGUAGE DeriveAnyClass #-}
4 {-# LANGUAGE DuplicateRecordFields #-} -- permit duplications for field names in multiple constructors
5 {-# LANGUAGE KindSignatures #-} -- for use of Endpoint (name :: Symbol)
6 {-# LANGUAGE PartialTypeSignatures #-} -- to automatically use suggested type hole signatures during compilation
7 {-# LANGUAGE TypeOperators #-}
9 module Gargantext.API.GraphQL where
11 import Data.ByteString.Lazy.Char8
18 import Data.Morpheus.Server
21 import Data.Morpheus.Subscriptions
26 import Data.Morpheus.Types
34 import Gargantext.API.Admin.Auth.Types (AuthenticatedUser)
35 import Gargantext.API.Admin.Orchestrator.Types (JobLog)
36 import Gargantext.API.Prelude (HasJobEnv')
37 import qualified Gargantext.API.GraphQL.Annuaire as GQLA
38 import qualified Gargantext.API.GraphQL.AsyncTask as GQLAT
39 import qualified Gargantext.API.GraphQL.Context as GQLCTX
40 import qualified Gargantext.API.GraphQL.IMT as GQLIMT
41 import qualified Gargantext.API.GraphQL.Node as GQLNode
42 import qualified Gargantext.API.GraphQL.User as GQLUser
43 import qualified Gargantext.API.GraphQL.UserInfo as GQLUserInfo
44 import qualified Gargantext.API.GraphQL.TreeFirstLevel as GQLTree
45 import qualified Gargantext.API.GraphQL.Team as GQLTeam
46 import Gargantext.API.Prelude (GargM, GargError)
47 import Gargantext.API.Types
48 import Gargantext.Core.Mail.Types (HasMail)
49 import Gargantext.Database.Prelude (HasConnectionPool, HasConfig)
50 import Gargantext.Prelude
51 import GHC.Generics (Generic)
61 import qualified Servant.Auth as SA
62 import qualified Servant.Auth.Server as SAS
63 import Gargantext.API.Admin.Types (HasSettings)
66 -- | Represents possible GraphQL queries.
69 { annuaire_contacts :: GQLA.AnnuaireContactArgs -> m [GQLA.AnnuaireContact]
70 , contexts :: GQLCTX.NodeContextArgs -> m [GQLCTX.NodeContextGQL]
71 , imt_schools :: GQLIMT.SchoolsArgs -> m [GQLIMT.School]
72 , job_logs :: GQLAT.JobLogArgs -> m (Map Int JobLog)
73 , nodes :: GQLNode.NodeArgs -> m [GQLNode.Node]
74 , node_parent :: GQLNode.NodeParentArgs -> m [GQLNode.Node]
75 , user_infos :: GQLUserInfo.UserInfoArgs -> m [GQLUserInfo.UserInfo]
76 , users :: GQLUser.UserArgs -> m [GQLUser.User m]
77 , tree :: GQLTree.TreeArgs -> m (GQLTree.TreeFirstLevel m)
78 , team :: GQLTeam.TeamArgs -> m GQLTeam.Team
79 } deriving (Generic, GQLType)
83 { update_user_info :: GQLUserInfo.UserInfoMArgs -> m Int
84 , delete_team_membership :: GQLTeam.TeamDeleteMArgs -> m [Int]
85 , update_node_context_category :: GQLCTX.NodeContextCategoryMArgs -> m [Int]
86 } deriving (Generic, GQLType)
88 -- | Possible GraphQL Events, i.e. here we describe how we will
89 -- manipulate the data.
90 type EVENT m = Event Channel (Contet m)
92 -- | Channels are possible actions to call when manipulating the data.
96 deriving (Eq, Show, Generic, Hashable)
98 -- | This type describes what data we will operate on.
100 = UserContet [GQLUser.User m]
101 | UserInfoContet [GQLUserInfo.UserInfo]
103 -- | The main GraphQL resolver: how queries, mutations and
104 -- subscriptions are handled.
106 :: (HasConnectionPool env, HasConfig env, HasMail env, HasJobEnv' env, HasSettings env)
107 => RootResolver (GargM env GargError) e Query Mutation Undefined
110 { queryResolver = Query { annuaire_contacts = GQLA.resolveAnnuaireContacts
111 , contexts = GQLCTX.resolveNodeContext
112 , imt_schools = GQLIMT.resolveSchools
113 , job_logs = GQLAT.resolveJobLogs
114 , nodes = GQLNode.resolveNodes
115 , node_parent = GQLNode.resolveNodeParent
116 , user_infos = GQLUserInfo.resolveUserInfos
117 , users = GQLUser.resolveUsers
118 , tree = GQLTree.resolveTree
119 , team = GQLTeam.resolveTeam }
120 , mutationResolver = Mutation { update_user_info = GQLUserInfo.updateUserInfo
121 , delete_team_membership = GQLTeam.deleteTeamMembership
122 , update_node_context_category = GQLCTX.updateNodeContextCategory }
123 , subscriptionResolver = Undefined }
125 -- | Main GraphQL "app".
127 :: (Typeable env, HasConnectionPool env, HasConfig env, HasMail env, HasJobEnv' env, HasSettings env)
128 => App (EVENT (GargM env GargError)) (GargM env GargError)
129 app = deriveApp rootResolver
131 ----------------------------------------------
133 -- Now for some boilerplate to integrate the above GraphQL app with
136 -- | Servant route for the app we defined above.
137 type GQAPI = ReqBody '[JSON] GQLRequest :> Post '[JSON] GQLResponse
138 -- type Schema = "schema" :> Get '[PlainText] Text
139 -- | Servant route for the playground.
140 type Playground = Get '[HTML] ByteString
141 -- type API' (name :: Symbol) = name :> (GQAPI :<|> Schema :<|> Playground)
142 -- | Our API consists of `GQAPI` and `Playground`.
143 type API = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
144 :> "gql" :> (GQAPI :<|> Playground)
150 -- ( SubApp ServerApp e
156 -- serveEndpoint publish app' = (liftIO . httpPubApp publish app') :<|> withSchema app' :<|> pure httpPlayground
158 -- withSchema :: (Applicative f) => App e m -> f Text
159 -- withSchema = pure . LT.toStrict . decodeUtf8 . render
161 -- | Implementation of our API.
164 :: (Typeable env, HasConnectionPool env, HasConfig env, HasMail env, HasJobEnv' env, HasSettings env)
165 => ServerT API (GargM env GargError)
166 api (SAS.Authenticated _auser) = httpPubApp [] app :<|> pure httpPlayground
167 api _ = panic "401 in graphql" -- SAS.throwAll (_ServerError # err401)