Commit bb2ad37b authored by Mael NICOLAS's avatar Mael NICOLAS

Merge branch 'master' into fromRFC3339

parents a5f2a719 f3ef6505
...@@ -2,7 +2,7 @@ ...@@ -2,7 +2,7 @@
-- --
-- see: https://github.com/sol/hpack -- see: https://github.com/sol/hpack
-- --
-- hash: 4e7c51f92304a8a22c00c60b641f336bcfa0c3994bd4beac6f2e9eafa90c408a -- hash: d4561cbff71c5a3432f81acb07d955452c13d94813fdc788977e81067144e27b
name: gargantext name: gargantext
version: 0.1.0.0 version: 0.1.0.0
...@@ -57,8 +57,8 @@ library ...@@ -57,8 +57,8 @@ library
Gargantext.Utils.Prefix Gargantext.Utils.Prefix
other-modules: other-modules:
Gargantext.API.Count Gargantext.API.Count
Gargantext.API.FrontEnd
Gargantext.API.Node Gargantext.API.Node
Gargantext.API.Swagger
Gargantext.Database.Queries Gargantext.Database.Queries
Gargantext.Utils Gargantext.Utils
Paths_gargantext Paths_gargantext
......
...@@ -57,9 +57,11 @@ import Servant ...@@ -57,9 +57,11 @@ import Servant
import Servant.Mock (mock) import Servant.Mock (mock)
import Servant.Swagger import Servant.Swagger
import Servant.Swagger.UI import Servant.Swagger.UI
import Servant.Static.TH (createApiAndServerDecs)
-- import Servant.API.Stream -- import Servant.API.Stream
--import Gargantext.API.Swagger
import Gargantext.API.FrontEnd (FrontEndAPI, frontEndServer)
import Gargantext.API.Node ( Roots , roots import Gargantext.API.Node ( Roots , roots
, NodeAPI , nodeAPI , NodeAPI , nodeAPI
, NodesAPI , nodesAPI , NodesAPI , nodesAPI
...@@ -73,14 +75,9 @@ type PortNumber = Int ...@@ -73,14 +75,9 @@ type PortNumber = Int
--------------------------------------------------------------------- ---------------------------------------------------------------------
-- | API Global -- | API Global
-- | API for serving @swagger.json@ -- | API for serving @swagger.json@
-- TODO Do we need to add this in the API ?
-- type SwaggerAPI = "swagger.json" :> Get '[JSON] Swagger
type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json" type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
-- | API for serving main operational routes of @gargantext.org@ -- | API for serving main operational routes of @gargantext.org@
type GargAPI = "user" :> Summary "First user endpoint" type GargAPI = "user" :> Summary "First user endpoint"
:> Roots :> Roots
...@@ -106,9 +103,6 @@ type GargAPI = "user" :> Summary "First user endpoint" ...@@ -106,9 +103,6 @@ type GargAPI = "user" :> Summary "First user endpoint"
-- :<|> "ngrams" :> Capture "id" Int :> NodeAPI -- :<|> "ngrams" :> Capture "id" Int :> NodeAPI
-- :<|> "auth" :> Capture "id" Int :> NodeAPI -- :<|> "auth" :> Capture "id" Int :> NodeAPI
--------------------------------------------------------------------- ---------------------------------------------------------------------
-- | Serve front end files
$(createApiAndServerDecs "FrontEndAPI" "frontEndServer" "frontEnd")
type SwaggerFrontAPI = SwaggerAPI :<|> FrontEndAPI type SwaggerFrontAPI = SwaggerAPI :<|> FrontEndAPI
type API = SwaggerFrontAPI :<|> GargAPI type API = SwaggerFrontAPI :<|> GargAPI
......
{-|
Module : Gargantext.API.FrontEnd
Description : Server FrontEnd API
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TemplateHaskell #-}
---------------------------------------------------------------------
module Gargantext.API.FrontEnd
where
import Servant.Static.TH (createApiAndServerDecs)
---------------------------------------------------------------------
$(createApiAndServerDecs "FrontEndAPI" "frontEndServer" "frontEnd")
---------------------------------------------------------------------
{-|
Module : Gargantext.API.Swagger
Description : Swagger Documentation API
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
---------------------------------------------------------------------
module Gargantext.API.Swagger
where
---------------------------------------------------------------------
import Gargantext.Prelude
import System.IO (FilePath, print)
import GHC.Generics (D1, Meta (..), Rep)
import GHC.TypeLits (AppendSymbol, Symbol)
import Control.Lens
import Data.Aeson.Encode.Pretty (encodePretty)
import qualified Data.ByteString.Lazy.Char8 as BL8
import Data.Swagger
import Data.Text (Text, pack)
--import qualified Data.Set as Set
import Database.PostgreSQL.Simple (Connection, connect)
import Network.Wai
import Network.Wai.Handler.Warp
import Servant
import Servant.Mock (mock)
import Servant.Swagger
import Servant.Swagger.UI
import Servant.Static.TH (createApiAndServerDecs)
-- import Servant.API.Stream
import Gargantext.API.Node ( Roots , roots
, NodeAPI , nodeAPI
, NodesAPI , nodesAPI
)
import Gargantext.API.Count ( CountAPI, count, Query)
import Gargantext.Database.Utils (databaseParameters)
---------------------------------------------------------------------
---------------------------------------------------------------------
type PortNumber = Int
---------------------------------------------------------------------
-- | API Global
-- | API for serving @swagger.json@
-- TODO Do we need to add this in the API ?
-- type SwaggerAPI = "swagger.json" :> Get '[JSON] Swagger
type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
-- | Serve front end files
$(createApiAndServerDecs "FrontEndAPI" "frontEndServer" "frontEnd")
type SwaggerFrontAPI = SwaggerAPI :<|> FrontEndAPI
type API = SwaggerFrontAPI :<|> GargAPI
---------------------------------------------------------------------
-- | Server declaration
server :: Connection -> Server API
server conn = swaggerFront
:<|> roots conn
:<|> nodeAPI conn
:<|> nodeAPI conn
:<|> nodesAPI conn
:<|> count
---------------------------------------------------------------------
swaggerFront :: Server SwaggerFrontAPI
swaggerFront = schemaUiServer swaggerDoc
:<|> frontEndServer
gargMock :: Server GargAPI
gargMock = mock apiGarg Proxy
---------------------------------------------------------------------
app :: Connection -> Application
app = serve api . server
appMock :: Application
appMock = serve api (swaggerFront :<|> gargMock)
---------------------------------------------------------------------
api :: Proxy API
api = Proxy
apiGarg :: Proxy GargAPI
apiGarg = Proxy
---------------------------------------------------------------------
schemaUiServer :: (Server api ~ Handler Swagger)
=> Swagger -> Server (SwaggerSchemaUI' dir api)
schemaUiServer = swaggerSchemaUIServer
-- Type Familiy for the Documentation
type family TypeName (x :: *) :: Symbol where
TypeName Int = "Int"
TypeName Text = "Text"
TypeName x = GenericTypeName x (Rep x ())
type family GenericTypeName t (r :: *) :: Symbol where
GenericTypeName t (D1 ('MetaData name mod pkg nt) f x) = name
type Desc t n = Description (AppendSymbol (TypeName t) (AppendSymbol " | " n))
-- | Swagger Specifications
swaggerDoc :: Swagger
swaggerDoc = toSwagger (Proxy :: Proxy GargAPI)
& info.title .~ "Gargantext"
& info.version .~ "0.1.0"
-- & info.base_url ?~ (URL "http://gargantext.org/")
& info.description ?~ "REST API specifications"
-- & tags .~ Set.fromList [Tag "Garg" (Just "Main perations") Nothing]
& applyTagsFor (subOperations (Proxy :: Proxy GargAPI)(Proxy :: Proxy GargAPI))
["Garg" & description ?~ "Main operations"]
& info.license ?~ ("AGPLV3 (English) and CECILL (French)" & url ?~ URL urlLicence )
where
urlLicence = "https://gitlab.iscpif.fr/gargantext/haskell-gargantext/blob/master/LICENSE"
-- | Output generated @swagger.json@ file for the @'TodoAPI'@.
swaggerWriteJSON :: IO ()
swaggerWriteJSON = BL8.writeFile "swagger.json" (encodePretty swaggerDoc)
-- | startGargantext takes as parameters port number and Ini file.
startGargantext :: PortNumber -> FilePath -> IO ()
startGargantext port file = do
print ("Starting Gargantext server" <> show port)
print ("http://localhost:" <> show port)
param <- databaseParameters file
conn <- connect param
run port (app conn)
startGargantextMock :: PortNumber -> IO ()
startGargantextMock port = do
print (pack "Starting Mock server")
print (pack $ "curl "
<> "-H \"content-type: application/json"
<> "-d \'{\"query_query\":\"query\"}\' "
<> "-v http://localhost:"
<> show port
<>"/count"
)
run port appMock
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