]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/GraphQL.hs
[FIX] NodeWrites parsing first fix
[gargantext.git] / src / Gargantext / API / GraphQL.hs
1 {-# OPTIONS_GHC -fprint-potential-instances #-}
2
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 #-}
8
9 module Gargantext.API.GraphQL where
10
11 import Data.ByteString.Lazy.Char8
12 ( ByteString
13 )
14 import Data.Map (Map)
15 import Data.Morpheus
16 ( App
17 , deriveApp )
18 import Data.Morpheus.Server
19 ( httpPlayground
20 )
21 import Data.Morpheus.Subscriptions
22 ( Event (..)
23 , Hashable
24 , httpPubApp
25 )
26 import Data.Morpheus.Types
27 ( GQLRequest
28 , GQLResponse
29 , GQLType
30 , RootResolver(..)
31 , Undefined(..)
32 )
33 import Data.Proxy
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)
52 import Servant
53 ( (:<|>) (..)
54 , (:>)
55 , Get
56 , JSON
57 , Post
58 , ReqBody
59 , ServerT
60 )
61 import qualified Servant.Auth as SA
62 import qualified Servant.Auth.Server as SAS
63 import Gargantext.API.Admin.Types (HasSettings)
64
65
66 -- | Represents possible GraphQL queries.
67 data Query m
68 = Query
69 { annuaire_contacts :: GQLA.AnnuaireContactArgs -> m [GQLA.AnnuaireContact]
70 , contexts :: GQLCTX.NodeContextArgs -> m [GQLCTX.NodeContextGQL]
71 , contexts_for_ngrams :: GQLCTX.ContextsForNgramsArgs -> m [GQLCTX.ContextGQL]
72 , imt_schools :: GQLIMT.SchoolsArgs -> m [GQLIMT.School]
73 , job_logs :: GQLAT.JobLogArgs -> m (Map Int JobLog)
74 , nodes :: GQLNode.NodeArgs -> m [GQLNode.Node]
75 , node_parent :: GQLNode.NodeParentArgs -> m [GQLNode.Node]
76 , user_infos :: GQLUserInfo.UserInfoArgs -> m [GQLUserInfo.UserInfo]
77 , users :: GQLUser.UserArgs -> m [GQLUser.User m]
78 , tree :: GQLTree.TreeArgs -> m (GQLTree.TreeFirstLevel m)
79 , team :: GQLTeam.TeamArgs -> m GQLTeam.Team
80 } deriving (Generic, GQLType)
81
82 data Mutation m
83 = Mutation
84 { update_user_info :: GQLUserInfo.UserInfoMArgs -> m Int
85 , delete_team_membership :: GQLTeam.TeamDeleteMArgs -> m [Int]
86 , update_node_context_category :: GQLCTX.NodeContextCategoryMArgs -> m [Int]
87 } deriving (Generic, GQLType)
88
89 -- | Possible GraphQL Events, i.e. here we describe how we will
90 -- manipulate the data.
91 type EVENT m = Event Channel (Contet m)
92
93 -- | Channels are possible actions to call when manipulating the data.
94 data Channel
95 = Update
96 | New
97 deriving (Eq, Show, Generic, Hashable)
98
99 -- | This type describes what data we will operate on.
100 data Contet m
101 = UserContet [GQLUser.User m]
102 | UserInfoContet [GQLUserInfo.UserInfo]
103
104 -- | The main GraphQL resolver: how queries, mutations and
105 -- subscriptions are handled.
106 rootResolver
107 :: (HasConnectionPool env, HasConfig env, HasMail env, HasJobEnv' env, HasSettings env)
108 => RootResolver (GargM env GargError) e Query Mutation Undefined
109 rootResolver =
110 RootResolver
111 { queryResolver = Query { annuaire_contacts = GQLA.resolveAnnuaireContacts
112 , contexts = GQLCTX.resolveNodeContext
113 , contexts_for_ngrams = GQLCTX.resolveContextsForNgrams
114 , imt_schools = GQLIMT.resolveSchools
115 , job_logs = GQLAT.resolveJobLogs
116 , nodes = GQLNode.resolveNodes
117 , node_parent = GQLNode.resolveNodeParent
118 , user_infos = GQLUserInfo.resolveUserInfos
119 , users = GQLUser.resolveUsers
120 , tree = GQLTree.resolveTree
121 , team = GQLTeam.resolveTeam }
122 , mutationResolver = Mutation { update_user_info = GQLUserInfo.updateUserInfo
123 , delete_team_membership = GQLTeam.deleteTeamMembership
124 , update_node_context_category = GQLCTX.updateNodeContextCategory }
125 , subscriptionResolver = Undefined }
126
127 -- | Main GraphQL "app".
128 app
129 :: (Typeable env, HasConnectionPool env, HasConfig env, HasMail env, HasJobEnv' env, HasSettings env)
130 => App (EVENT (GargM env GargError)) (GargM env GargError)
131 app = deriveApp rootResolver
132
133 ----------------------------------------------
134
135 -- Now for some boilerplate to integrate the above GraphQL app with
136 -- servant.
137
138 -- | Servant route for the app we defined above.
139 type GQAPI = ReqBody '[JSON] GQLRequest :> Post '[JSON] GQLResponse
140 -- type Schema = "schema" :> Get '[PlainText] Text
141 -- | Servant route for the playground.
142 type Playground = Get '[HTML] ByteString
143 -- type API' (name :: Symbol) = name :> (GQAPI :<|> Schema :<|> Playground)
144 -- | Our API consists of `GQAPI` and `Playground`.
145 type API = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
146 :> "gql" :> (GQAPI :<|> Playground)
147
148 gqapi :: Proxy API
149 gqapi = Proxy
150
151 -- serveEndpoint ::
152 -- ( SubApp ServerApp e
153 -- , PubApp e
154 -- ) =>
155 -- [e -> IO ()] ->
156 -- App e IO ->
157 -- Server (API name)
158 -- serveEndpoint publish app' = (liftIO . httpPubApp publish app') :<|> withSchema app' :<|> pure httpPlayground
159 --
160 -- withSchema :: (Applicative f) => App e m -> f Text
161 -- withSchema = pure . LT.toStrict . decodeUtf8 . render
162
163 -- | Implementation of our API.
164 --api :: Server API
165 api
166 :: (Typeable env, HasConnectionPool env, HasConfig env, HasMail env, HasJobEnv' env, HasSettings env)
167 => ServerT API (GargM env GargError)
168 api (SAS.Authenticated _auser) = httpPubApp [] app :<|> pure httpPlayground
169 api _ = panic "401 in graphql" -- SAS.throwAll (_ServerError # err401)