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

Merge branch 'adinapoli/restore-swagger-auth' into 'dev'

Switch to OpenAPI3 from Swagger2, to use proper Bearer token

Closes #427

See merge request !369
parents a3879ca5 7decc3f4
Pipeline #7099 passed with stages
in 52 minutes and 4 seconds
......@@ -467,6 +467,8 @@ library
Gargantext.Database.Schema.NodeNode
Gargantext.Database.Schema.Prelude
Gargantext.Database.Types
Gargantext.Orphans
Gargantext.Orphans.OpenAPI
Gargantext.Utils.Aeson
Gargantext.Utils.Servant
Gargantext.Utils.UTCTime
......@@ -562,6 +564,7 @@ library
, opaleye ^>= 0.9.6.1
, opaleye-textsearch >= 0.2.0.0
, openalex
, openapi3 >= 3.2.3
, parallel ^>= 3.2.2.0
, parsec ^>= 3.1.16.1
, patches-class ^>= 0.1.0.1
......@@ -588,6 +591,7 @@ library
, servant-client-core >= 0.20 && < 0.21
, servant-ekg ^>= 0.3.1
, servant-routes < 0.2
, servant-openapi3 >= 2.0.1.6
, servant-server >= 0.18.3 && < 0.21
, servant-swagger ^>= 1.2
, servant-swagger-ui ^>= 0.3.5.3.5.0
......
......@@ -64,6 +64,7 @@ import Servant (HasServer(..), ServerT)
import Servant.Server.Internal.Delayed (addParameterCheck)
import Servant.Server.Internal.DelayedIO (DelayedIO(..))
import Servant.Swagger qualified as Swagger
import Servant.OpenApi qualified as OpenAPI
-------------------------------------------------------------------------------
-- Types
......@@ -299,6 +300,9 @@ instance AddSetCookies ('S n) old new => AddSetCookies ('S n) (AccessPolicyManag
instance Swagger.HasSwagger sub => Swagger.HasSwagger (PolicyChecked sub) where
toSwagger _ = Swagger.toSwagger (Proxy :: Proxy sub)
instance OpenAPI.HasOpenApi sub => OpenAPI.HasOpenApi (PolicyChecked sub) where
toOpenApi _ = OpenAPI.toOpenApi (Proxy :: Proxy sub)
instance HasEndpoint sub => HasEndpoint (PolicyChecked sub) where
getEndpoint _ = getEndpoint (Proxy :: Proxy sub)
enumerateEndpoints _ = enumerateEndpoints (Proxy :: Proxy sub)
......
......@@ -15,6 +15,7 @@ module Gargantext.API.Routes.Named (
, ForgotPasswordAPI(..)
, ForgotPasswordAsyncAPI(..)
, GargVersion(..)
, module Gargantext.API.Routes.Named.Private
) where
import Data.Text (Text)
......@@ -74,10 +75,9 @@ data GargAPI' mode = GargAPI'
, gargForgotPasswordAsyncAPI :: mode :- "async" :> "forgot-password" :> NamedRoutes ForgotPasswordAsyncAPI
, gargVersionAPI :: mode :- NamedRoutes GargVersion
, gargPrivateAPI :: mode :- NamedRoutes GargPrivateAPI
, gargPublicAPI :: mode :- "public" :> NamedRoutes GargPublicAPI
, gargPublicAPI :: mode :- NamedRoutes GargPublicAPI
} deriving Generic
newtype AuthAPI mode = AuthAPI
{ authEp :: mode :- "auth" :> Summary "AUTH API"
:> ReqBody '[JSON] AuthRequest
......
......@@ -2,7 +2,8 @@
module Gargantext.API.Routes.Named.Public (
-- * Routes types
GargPublicAPI(..)
GargPublicAPI'(..)
, GargPublicAPI(..)
, HomeAPI(..)
, NodeAPI(..)
) where
......@@ -13,8 +14,11 @@ import Gargantext.API.Routes.Named.File (FileAPI)
import Gargantext.Database.Admin.Types.Node ( NodeId )
import Servant.API
newtype GargPublicAPI mode = GargPublicAPI
{ gargAPIVersion :: mode :- "public" :> NamedRoutes GargPublicAPI'
} deriving Generic
data GargPublicAPI mode = GargPublicAPI
data GargPublicAPI' mode = GargPublicAPI'
{ publicHomeAPI :: mode :- NamedRoutes HomeAPI
, publicNodeAPI :: mode :- NamedRoutes NodeAPI
} deriving Generic
......
......@@ -29,7 +29,7 @@ import Servant
-- would fail because '#/share/NodeCorpus/16' by the RFC3968 spec is considered
-- an uriFragment, but BaseUrl cannot handle that.
newtype ShareLink = ShareLink { getShareLink :: URI }
deriving (Show, Eq, Ord)
deriving (Show, Eq, Ord, Generic)
renderShareLink :: ShareLink -> T.Text
renderShareLink = T.pack . show . getShareLink
......
......@@ -20,7 +20,7 @@ import Gargantext.API.GraphQL as GraphQL
import Gargantext.API.Prelude (GargM)
import Gargantext.API.Routes.Named
import Gargantext.API.Server.Named.Public (serverPublicGargAPI)
import Gargantext.API.Swagger (swaggerDoc)
import Gargantext.API.Swagger (openApiDoc)
import Gargantext.API.ThrowAll (serverPrivateGargAPI)
import Gargantext.Core.Notifications.Dispatcher.WebSocket qualified as Dispatcher
import Gargantext.Core.Config (gc_frontend_config, hasConfig)
......@@ -50,7 +50,7 @@ serverGargAPI env
server :: Env -> API AsServer
server env =
API $ \errScheme -> NamedAPI
{ swaggerAPI = swaggerSchemaUIServer swaggerDoc
{ swaggerAPI = swaggerSchemaUIServer openApiDoc
, backendAPI = hoistServerWithContext
(Proxy :: Proxy (NamedRoutes BackEndAPI))
(Proxy :: Proxy AuthContext)
......
......@@ -26,8 +26,8 @@ import Servant
import Servant.Server.Generic (AsServerT)
serverPublicGargAPI :: IsGargServer env err m => Text -> Named.GargPublicAPI (AsServerT m)
serverPublicGargAPI baseUrl =
Named.GargPublicAPI
serverPublicGargAPI baseUrl = Named.GargPublicAPI $
Named.GargPublicAPI'
{ publicHomeAPI = api_home baseUrl
, publicNodeAPI = Named.NodeAPI api_node
}
......
{-# OPTIONS_GHC -freduction-depth=400 #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-|
Module : Gargantext.API.Swagger
......@@ -12,30 +14,45 @@ Portability : POSIX
-}
---------------------------------------------------------------------
module Gargantext.API.Swagger where
---------------------------------------------------------------------
module Gargantext.API.Swagger (
backendApiProxy
, openApiDoc
) where
import Control.Lens ((?~))
import Data.Swagger
import Data.OpenApi
import Data.Version (showVersion)
import Gargantext.API.Routes.Named.Public qualified as Named
import Gargantext.API.Routes.Named qualified as Named
import Gargantext.Orphans () -- instance HasOpenApi
import Gargantext.Prelude
import Paths_gargantext qualified as PG -- cabal magic build module
import Servant
import Servant.Swagger (toSwagger, subOperations)
import Servant.OpenApi
backendApiProxy :: Proxy (ToServantApi Named.BackEndAPI)
backendApiProxy :: Proxy (NamedRoutes (Named.MkBackEndAPI (Named.GargAPIVersion Named.GargAPI')))
backendApiProxy = Proxy
-- | Swagger Specifications
swaggerDoc :: Swagger
swaggerDoc = toSwagger backendApiProxy
privateOps :: Proxy (NamedRoutes (Named.MkBackEndAPI (Named.GargAPIVersion Named.GargPrivateAPI)))
privateOps = Proxy
publicOps :: Proxy (NamedRoutes (Named.MkBackEndAPI (Named.GargAPIVersion Named.GargPublicAPI)))
publicOps = Proxy
-- | OpenAPI Specification. It supports programmatically adding the `Bearer` to the `Authorization`
-- header, which makes the Swagger UI actually useable, unlike the 'swaggerDoc' counterpart which
-- is stuck on version 2.x of the OpenAPI spec.
openApiDoc :: OpenApi
openApiDoc = toOpenApi backendApiProxy
& info.title .~ "GarganText"
& info.version .~ (cs $ showVersion PG.version)
-- & info.base_url ?~ (URL "http://gargantext.org/")
& info.description ?~ "REST API specifications"
-- & tags .~ Set.fromList [Tag "Garg" (Just "Main perations") Nothing]
& applyTagsFor (subOperations backendApiProxy backendApiProxy)
["Gargantext" & description ?~ "Main operations"]
["Gargantext" & description ?~ "All operations"]
& applyTagsFor (subOperations privateOps backendApiProxy)
["Private operations" & description ?~ "Operations requiring authentications"]
& applyTagsFor (subOperations publicOps backendApiProxy)
["Public operations" & description ?~ "Operations which don't require a valid authentication"]
& info.license ?~ ("AGPLV3 (English) and CECILL (French)" & url ?~ URL urlLicence )
where
urlLicence = "https://gitlab.iscpif.fr/gargantext/haskell-gargantext/blob/master/LICENSE"
module Gargantext.Orphans (
module Gargantext.Orphans.OpenAPI
) where
import Gargantext.Orphans.OpenAPI
This diff is collapsed.
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