1 {-# LANGUAGE DeriveAnyClass #-}
2 {-# LANGUAGE DuplicateRecordFields #-} -- permit duplications for field names in multiple constructors
3 {-# LANGUAGE KindSignatures #-} -- for use of Endpoint (name :: Symbol)
4 {-# LANGUAGE PartialTypeSignatures #-} -- to automatically use suggested type hole signatures during compilation
5 {-# LANGUAGE TypeOperators #-}
7 module Gargantext.API.GraphQL where
9 import Data.ByteString.Lazy.Char8
12 import Data.List.NonEmpty (NonEmpty ((:|)))
17 import Data.Morpheus.Server
20 import Data.Morpheus.Subscriptions
25 import Data.Morpheus.Types
33 import Gargantext.API.Admin.Auth.Types (AuthenticatedUser)
34 import Gargantext.API.Admin.Orchestrator.Types (JobLog)
35 import Gargantext.API.Prelude (HasJobEnv')
36 import qualified Gargantext.API.GraphQL.AsyncTask as GQLAT
37 import qualified Gargantext.API.GraphQL.IMT as GQLIMT
38 import qualified Gargantext.API.GraphQL.Node as GQLNode
39 import qualified Gargantext.API.GraphQL.User as GQLUser
40 import qualified Gargantext.API.GraphQL.UserInfo as GQLUserInfo
41 import qualified Gargantext.API.GraphQL.TreeFirstLevel as GQLTree
42 import Gargantext.API.Prelude (GargM, GargError)
43 import Gargantext.Core.Mail.Types (HasMail)
44 import Gargantext.Database.Prelude (HasConnectionPool, HasConfig)
45 import Gargantext.Prelude
46 import GHC.Generics (Generic)
47 import Network.HTTP.Media ((//), (/:))
48 import qualified Prelude
60 import qualified Servant.Auth as SA
61 import qualified Servant.Auth.Server as SAS
62 import Gargantext.API.Admin.Types (HasSettings)
64 -- | Represents possible GraphQL queries.
67 { imt_schools :: GQLIMT.SchoolsArgs -> m [GQLIMT.School]
68 , job_logs :: GQLAT.JobLogArgs -> m (Map Int JobLog)
69 , nodes :: GQLNode.NodeArgs -> m [GQLNode.Node]
70 , node_parent :: GQLNode.NodeParentArgs -> m [GQLNode.Node]
71 , user_infos :: GQLUserInfo.UserInfoArgs -> m [GQLUserInfo.UserInfo]
72 , users :: GQLUser.UserArgs -> m [GQLUser.User m]
73 , tree :: GQLTree.TreeArgs -> m (GQLTree.TreeFirstLevel m)
74 } deriving (Generic, GQLType)
78 { update_user_info :: GQLUserInfo.UserInfoMArgs -> m Int }
79 deriving (Generic, GQLType)
81 -- | Possible GraphQL Events, i.e. here we describe how we will
82 -- manipulate the data.
83 type EVENT m = Event Channel (Contet m)
85 -- | Channels are possible actions to call when manipulating the data.
89 deriving (Eq, Show, Generic, Hashable)
91 -- | This type describes what data we will operate on.
93 = UserContet [GQLUser.User m]
94 | UserInfoContet [GQLUserInfo.UserInfo]
96 -- | The main GraphQL resolver: how queries, mutations and
97 -- subscriptions are handled.
99 :: (HasConnectionPool env, HasConfig env, HasMail env, HasJobEnv' env, HasSettings env)
100 => RootResolver (GargM env GargError) e Query Mutation Undefined
103 { queryResolver = Query { imt_schools = GQLIMT.resolveSchools
104 , job_logs = GQLAT.resolveJobLogs
105 , nodes = GQLNode.resolveNodes
106 , node_parent = GQLNode.resolveNodeParent
107 , user_infos = GQLUserInfo.resolveUserInfos
108 , users = GQLUser.resolveUsers
109 , tree = GQLTree.resolveTree }
110 , mutationResolver = Mutation { update_user_info = GQLUserInfo.updateUserInfo }
111 , subscriptionResolver = Undefined }
113 -- | Main GraphQL "app".
115 :: (Typeable env, HasConnectionPool env, HasConfig env, HasMail env, HasJobEnv' env, HasSettings env)
116 => App (EVENT (GargM env GargError)) (GargM env GargError)
117 app = deriveApp rootResolver
119 ----------------------------------------------
121 -- Now for some boilerplate to integrate the above GraphQL app with
124 -- | HTML type is needed for the GraphQL Playground.
125 data HTML deriving (Typeable)
126 instance Accept HTML where
127 contentTypes _ = "text" // "html" /: ("charset", "utf-8") :| ["text" // "html"]
128 instance MimeRender HTML ByteString where
129 mimeRender _ = Prelude.id
131 -- | Servant route for the app we defined above.
132 type GQAPI = ReqBody '[JSON] GQLRequest :> Post '[JSON] GQLResponse
133 -- type Schema = "schema" :> Get '[PlainText] Text
134 -- | Servant route for the playground.
135 type Playground = Get '[HTML] ByteString
136 -- type API' (name :: Symbol) = name :> (GQAPI :<|> Schema :<|> Playground)
137 -- | Our API consists of `GQAPI` and `Playground`.
138 type API = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
139 :> "gql" :> (GQAPI :<|> Playground)
145 -- ( SubApp ServerApp e
151 -- serveEndpoint publish app' = (liftIO . httpPubApp publish app') :<|> withSchema app' :<|> pure httpPlayground
153 -- withSchema :: (Applicative f) => App e m -> f Text
154 -- withSchema = pure . LT.toStrict . decodeUtf8 . render
156 -- | Implementation of our API.
159 :: (Typeable env, HasConnectionPool env, HasConfig env, HasMail env, HasJobEnv' env, HasSettings env)
160 => ServerT API (GargM env GargError)
161 api (SAS.Authenticated _auser) = httpPubApp [] app :<|> pure httpPlayground
162 api _ = panic "401 in graphql" -- SAS.throwAll (_ServerError # err401)