Commit e2a437a9 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Convert GraphQL API to Named routes

parent 319a5c26
...@@ -15,6 +15,8 @@ Portability : POSIX ...@@ -15,6 +15,8 @@ Portability : POSIX
{-# LANGUAGE KindSignatures #-} -- for use of Endpoint (name :: Symbol) {-# LANGUAGE KindSignatures #-} -- for use of Endpoint (name :: Symbol)
{-# LANGUAGE PartialTypeSignatures #-} -- to automatically use suggested type hole signatures during compilation {-# LANGUAGE PartialTypeSignatures #-} -- to automatically use suggested type hole signatures during compilation
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-}
module Gargantext.API.GraphQL where module Gargantext.API.GraphQL where
...@@ -46,16 +48,9 @@ import Gargantext.Core.NLP (HasNLPServer) ...@@ -46,16 +48,9 @@ import Gargantext.Core.NLP (HasNLPServer)
import Gargantext.Database.Prelude (CmdCommon) import Gargantext.Database.Prelude (CmdCommon)
import Gargantext.Prelude hiding (ByteString) import Gargantext.Prelude hiding (ByteString)
import Servant import Servant
( (:<|>) (..)
, (:>)
, Get
, JSON
, Post
, ReqBody
, ServerT
)
import Servant.Auth qualified as SA import Servant.Auth qualified as SA
import Servant.Auth.Server qualified as SAS import Servant.Auth.Server qualified as SAS
import Servant.Server.Generic
-- | Represents possible GraphQL queries. -- | Represents possible GraphQL queries.
...@@ -127,7 +122,7 @@ rootResolver authenticatedUser policyManager = ...@@ -127,7 +122,7 @@ rootResolver authenticatedUser policyManager =
, user_infos = GQLUserInfo.resolveUserInfos authenticatedUser policyManager , user_infos = GQLUserInfo.resolveUserInfos authenticatedUser policyManager
, users = GQLUser.resolveUsers authenticatedUser policyManager , users = GQLUser.resolveUsers authenticatedUser policyManager
, tree = GQLTree.resolveTree authenticatedUser policyManager , tree = GQLTree.resolveTree authenticatedUser policyManager
, team = GQLTeam.resolveTeam , team = GQLTeam.resolveTeam
, tree_branch = GQLTree.resolveBreadcrumb } , tree_branch = GQLTree.resolveBreadcrumb }
, mutationResolver = Mutation { update_user_info = GQLUserInfo.updateUserInfo , mutationResolver = Mutation { update_user_info = GQLUserInfo.updateUserInfo
, update_user_pubmed_api_key = GQLUser.updateUserPubmedAPIKey , update_user_pubmed_api_key = GQLUser.updateUserPubmedAPIKey
...@@ -151,34 +146,37 @@ app authenticatedUser policyManager = deriveApp (rootResolver authenticatedUser ...@@ -151,34 +146,37 @@ app authenticatedUser policyManager = deriveApp (rootResolver authenticatedUser
-- servant. -- servant.
-- | Servant route for the app we defined above. -- | Servant route for the app we defined above.
type GQAPI = ReqBody '[JSON] GQLRequest :> Post '[JSON] GQLResponse newtype GQAPI mode = GQAPI
-- type Schema = "schema" :> Get '[PlainText] Text { gqApi :: mode :- ReqBody '[JSON] GQLRequest :> Post '[JSON] GQLResponse
-- | Servant route for the playground. } deriving Generic
type Playground = Get '[HTML] ByteString
-- type API' (name :: Symbol) = name :> (GQAPI :<|> Schema :<|> Playground)
-- | Our API consists of `GQAPI` and `Playground`.
type API = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
:> "gql" :> (PolicyChecked GQAPI :<|> Playground)
gqapi :: Proxy API -- | Servant route for the playground.
newtype Playground mode = Playground
{ playground :: mode :- Get '[HTML] ByteString
} deriving Generic
newtype GraphQLAPI mode = GraphQLAPI
{ graphQLAPI :: mode :- SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser
:> "gql"
:> NamedRoutes GraphQLAPIEndpoints
} deriving Generic
data GraphQLAPIEndpoints mode = GraphQLAPIEndpoints
{ gqApiEp :: mode :- PolicyChecked (NamedRoutes GQAPI)
, playgroundEp :: mode :- NamedRoutes Playground
}
deriving Generic
gqapi :: Proxy (ToServantApi GraphQLAPI)
gqapi = Proxy gqapi = Proxy
-- serveEndpoint ::
-- ( SubApp ServerApp e
-- , PubApp e
-- ) =>
-- [e -> IO ()] ->
-- App e IO ->
-- Server (API name)
-- serveEndpoint publish app' = (liftIO . httpPubApp publish app') :<|> withSchema app' :<|> pure httpPlayground
--
-- withSchema :: (Applicative f) => App e m -> f Text
-- withSchema = pure . LT.toStrict . decodeUtf8 . render
-- | Implementation of our API. -- | Implementation of our API.
--api :: Server API
api api
:: (Typeable env, CmdCommon env, HasJobEnv' env, HasSettings env) :: (Typeable env, CmdCommon env, HasJobEnv' env, HasSettings env)
=> ServerT API (GargM env BackendInternalError) => GraphQLAPI (AsServerT (GargM env BackendInternalError))
api (SAS.Authenticated auser) = (httpPubApp [] . app auser) :<|> pure httpPlayground api = GraphQLAPI $ \case
api _ = panicTrace "401 in graphql" -- SAS.throwAll (_ServerError # err401) (SAS.Authenticated auser)
-> GraphQLAPIEndpoints { gqApiEp = GQAPI . httpPubApp [] . app auser
, playgroundEp = Playground $ pure httpPlayground
}
_ -> panicTrace "401 in graphql" -- SAS.throwAll (_ServerError # err401)
...@@ -24,7 +24,7 @@ import GHC.Generics ...@@ -24,7 +24,7 @@ import GHC.Generics
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types
import Gargantext.API.Admin.FrontEnd (FrontEndAPI) import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.GraphQL qualified as GraphQL import Gargantext.API.GraphQL
import Gargantext.API.Routes.Named.Private import Gargantext.API.Routes.Named.Private
import Gargantext.API.Routes.Named.Public import Gargantext.API.Routes.Named.Public
import Gargantext.API.Routes.Types import Gargantext.API.Routes.Types
...@@ -42,7 +42,7 @@ newtype API mode = API ...@@ -42,7 +42,7 @@ newtype API mode = API
data NamedAPI mode = NamedAPI data NamedAPI mode = NamedAPI
{ swaggerAPI :: mode :- SwaggerSchemaUI "swagger-ui" "swagger.json" { swaggerAPI :: mode :- SwaggerSchemaUI "swagger-ui" "swagger.json"
, backendAPI :: mode :- NamedRoutes BackEndAPI , backendAPI :: mode :- NamedRoutes BackEndAPI
, graphqlAPI :: mode :- GraphQL.API -- FIXME(adn) convert to named! , graphqlAPI :: mode :- NamedRoutes GraphQLAPI -- FIXME(adn) convert to named!
, frontendAPI :: mode :- FrontEndAPI , frontendAPI :: mode :- FrontEndAPI
} deriving Generic } deriving Generic
......
...@@ -16,7 +16,7 @@ import Gargantext.API.Admin.EnvTypes (Env) ...@@ -16,7 +16,7 @@ import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Admin.FrontEnd (frontEndServer) import Gargantext.API.Admin.FrontEnd (frontEndServer)
import Gargantext.API.Auth.PolicyCheck () import Gargantext.API.Auth.PolicyCheck ()
import Gargantext.API.Errors import Gargantext.API.Errors
import Gargantext.API.GraphQL qualified as GraphQL import Gargantext.API.GraphQL as GraphQL
import Gargantext.API.Prelude (GargM) import Gargantext.API.Prelude (GargM)
import Gargantext.API.Server.Named.Public (serverPublicGargAPI) import Gargantext.API.Server.Named.Public (serverPublicGargAPI)
import Gargantext.API.Routes.Named import Gargantext.API.Routes.Named
...@@ -56,7 +56,7 @@ server env = ...@@ -56,7 +56,7 @@ server env =
(transformJSON errScheme) (transformJSON errScheme)
(serverGargAPI (env ^. hasConfig . gc_url_backend_api)) (serverGargAPI (env ^. hasConfig . gc_url_backend_api))
, graphqlAPI = hoistServerWithContext , graphqlAPI = hoistServerWithContext
(Proxy :: Proxy GraphQL.API) (Proxy :: Proxy (NamedRoutes GraphQLAPI))
(Proxy :: Proxy AuthContext) (Proxy :: Proxy AuthContext)
(transformJSONGQL errScheme) (transformJSONGQL errScheme)
GraphQL.api GraphQL.api
......
...@@ -29,7 +29,7 @@ module Gargantext.Database.Query.Table.Node.Error ( ...@@ -29,7 +29,7 @@ module Gargantext.Database.Query.Table.Node.Error (
import Control.Lens (Prism', (#), (^?)) import Control.Lens (Prism', (#), (^?))
import Data.Aeson (object) import Data.Aeson (object)
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.Core.Types.Individu ( renderUser, User, Username ) import Gargantext.Core.Types.Individu ( Username )
import Gargantext.Database.Admin.Types.Node (ListId, NodeId(..), ContextId, UserId, ParentId) import Gargantext.Database.Admin.Types.Node (ListId, NodeId(..), ContextId, UserId, ParentId)
import Gargantext.Prelude hiding (sum, head) import Gargantext.Prelude hiding (sum, head)
import Prelude hiding (null, id, map, sum, show) import Prelude hiding (null, id, map, sum, show)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment