Swagger.hs 2.28 KB
{-# OPTIONS_GHC -freduction-depth=400 #-}
{-# LANGUAGE TypeApplications         #-}
{-# LANGUAGE TypeOperators #-}

{-|
Module      : Gargantext.API.Swagger
Description : Swagger API generation
Copyright   : (c) CNRS, 2017-Present
License     : AGPL + CECILL v3
Maintainer  : team@gargantext.org
Stability   : experimental
Portability : POSIX

-}

---------------------------------------------------------------------
module Gargantext.API.Swagger (
    backendApiProxy
  , openApiDoc
  ) where

import Control.Lens ((?~))
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.OpenApi

backendApiProxy :: Proxy (NamedRoutes (Named.MkBackEndAPI (Named.GargAPIVersion Named.GargAPI')))
backendApiProxy = Proxy

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.description ?~ "REST API specifications"
  & applyTagsFor (subOperations backendApiProxy backendApiProxy)
                 ["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"