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

Convert GraphQL API to Named routes

parent 319a5c26
Pipeline #6194 passed with stages
in 242 minutes and 48 seconds
......@@ -15,6 +15,8 @@ Portability : POSIX
{-# LANGUAGE KindSignatures #-} -- for use of Endpoint (name :: Symbol)
{-# LANGUAGE PartialTypeSignatures #-} -- to automatically use suggested type hole signatures during compilation
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-}
module Gargantext.API.GraphQL where
......@@ -46,16 +48,9 @@ import Gargantext.Core.NLP (HasNLPServer)
import Gargantext.Database.Prelude (CmdCommon)
import Gargantext.Prelude hiding (ByteString)
import Servant
( (:<|>) (..)
, (:>)
, Get
, JSON
, Post
, ReqBody
, ServerT
)
import Servant.Auth qualified as SA
import Servant.Auth.Server qualified as SAS
import Servant.Server.Generic
-- | Represents possible GraphQL queries.
......@@ -127,7 +122,7 @@ rootResolver authenticatedUser policyManager =
, user_infos = GQLUserInfo.resolveUserInfos authenticatedUser policyManager
, users = GQLUser.resolveUsers authenticatedUser policyManager
, tree = GQLTree.resolveTree authenticatedUser policyManager
, team = GQLTeam.resolveTeam
, team = GQLTeam.resolveTeam
, tree_branch = GQLTree.resolveBreadcrumb }
, mutationResolver = Mutation { update_user_info = GQLUserInfo.updateUserInfo
, update_user_pubmed_api_key = GQLUser.updateUserPubmedAPIKey
......@@ -151,34 +146,37 @@ app authenticatedUser policyManager = deriveApp (rootResolver authenticatedUser
-- servant.
-- | Servant route for the app we defined above.
type GQAPI = ReqBody '[JSON] GQLRequest :> Post '[JSON] GQLResponse
-- type Schema = "schema" :> Get '[PlainText] Text
-- | Servant route for the playground.
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)
newtype GQAPI mode = GQAPI
{ gqApi :: mode :- ReqBody '[JSON] GQLRequest :> Post '[JSON] GQLResponse
} deriving Generic
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
-- 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.
--api :: Server API
api
:: (Typeable env, CmdCommon env, HasJobEnv' env, HasSettings env)
=> ServerT API (GargM env BackendInternalError)
api (SAS.Authenticated auser) = (httpPubApp [] . app auser) :<|> pure httpPlayground
api _ = panicTrace "401 in graphql" -- SAS.throwAll (_ServerError # err401)
=> GraphQLAPI (AsServerT (GargM env BackendInternalError))
api = GraphQLAPI $ \case
(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
import Gargantext.API.Admin.Auth.Types
import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
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.Public
import Gargantext.API.Routes.Types
......@@ -42,7 +42,7 @@ newtype API mode = API
data NamedAPI mode = NamedAPI
{ swaggerAPI :: mode :- SwaggerSchemaUI "swagger-ui" "swagger.json"
, 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
} deriving Generic
......
......@@ -16,7 +16,7 @@ import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Admin.FrontEnd (frontEndServer)
import Gargantext.API.Auth.PolicyCheck ()
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.Server.Named.Public (serverPublicGargAPI)
import Gargantext.API.Routes.Named
......@@ -56,7 +56,7 @@ server env =
(transformJSON errScheme)
(serverGargAPI (env ^. hasConfig . gc_url_backend_api))
, graphqlAPI = hoistServerWithContext
(Proxy :: Proxy GraphQL.API)
(Proxy :: Proxy (NamedRoutes GraphQLAPI))
(Proxy :: Proxy AuthContext)
(transformJSONGQL errScheme)
GraphQL.api
......
......@@ -29,7 +29,7 @@ module Gargantext.Database.Query.Table.Node.Error (
import Control.Lens (Prism', (#), (^?))
import Data.Aeson (object)
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.Prelude hiding (sum, head)
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