2 Module : Gargantext.API
3 Description : Server API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Main REST API of Gargantext (both Server and Client sides)
12 TODO App type, the main monad in which the bot code is written with.
13 Provide config, state, logs and IO
14 type App m a = ( MonadState AppState m
16 , MonadLog (WithSeverity Doc) m
18 Thanks @yannEsposito for this.
21 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
23 {-# LANGUAGE DataKinds #-}
24 {-# LANGUAGE DeriveGeneric #-}
25 {-# LANGUAGE FlexibleInstances #-}
26 {-# LANGUAGE OverloadedStrings #-}
27 {-# LANGUAGE TemplateHaskell #-}
28 {-# LANGUAGE TypeOperators #-}
29 {-# LANGUAGE KindSignatures #-}
30 {-# LANGUAGE TypeFamilies #-}
31 {-# LANGUAGE UndecidableInstances #-}
33 ---------------------------------------------------------------------
36 ---------------------------------------------------------------------
37 import Gargantext.Prelude
39 import System.IO (FilePath, print)
41 import GHC.Generics (D1, Meta (..), Rep)
42 import GHC.TypeLits (AppendSymbol, Symbol)
45 import Data.Aeson.Encode.Pretty (encodePretty)
46 import qualified Data.ByteString.Lazy.Char8 as BL8
48 import Data.Text (Text, pack)
49 --import qualified Data.Set as Set
51 import Database.PostgreSQL.Simple (Connection, connect)
54 import Network.Wai.Handler.Warp
57 import Servant.Mock (mock)
58 import Servant.Swagger
59 import Servant.Swagger.UI
60 -- import Servant.API.Stream
62 --import Gargantext.API.Swagger
63 import Gargantext.API.FrontEnd (FrontEndAPI, frontEndServer)
65 import Gargantext.API.Node ( Roots , roots
69 import Gargantext.API.Count ( CountAPI, count, Query)
70 import Gargantext.Database.Utils (databaseParameters)
72 ---------------------------------------------------------------------
73 ---------------------------------------------------------------------
75 ---------------------------------------------------------------------
78 -- | API for serving @swagger.json@
79 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
81 -- | API for serving main operational routes of @gargantext.org@
82 type GargAPI = "user" :> Summary "First user endpoint"
85 :<|> "node" :> Summary "Node endpoint"
86 :> Capture "id" Int :> NodeAPI
88 :<|> "corpus":> Summary "Corpus endpoint"
89 :> Capture "id" Int :> NodeAPI
91 :<|> "nodes" :> Summary "Nodes endpoint"
92 :> ReqBody '[JSON] [Int] :> NodesAPI
94 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
95 :<|> "count" :> Summary "Count endpoint"
96 :> ReqBody '[JSON] Query :> CountAPI
102 -- :<|> "list" :> Capture "id" Int :> NodeAPI
103 -- :<|> "ngrams" :> Capture "id" Int :> NodeAPI
104 -- :<|> "auth" :> Capture "id" Int :> NodeAPI
105 ---------------------------------------------------------------------
106 type SwaggerFrontAPI = SwaggerAPI :<|> FrontEndAPI
108 type API = SwaggerFrontAPI :<|> GargAPI
110 ---------------------------------------------------------------------
111 -- | Server declaration
112 server :: Connection -> Server API
113 server conn = swaggerFront
120 ---------------------------------------------------------------------
121 swaggerFront :: Server SwaggerFrontAPI
122 swaggerFront = schemaUiServer swaggerDoc
125 gargMock :: Server GargAPI
126 gargMock = mock apiGarg Proxy
128 ---------------------------------------------------------------------
129 app :: Connection -> Application
130 app = serve api . server
132 appMock :: Application
133 appMock = serve api (swaggerFront :<|> gargMock)
135 ---------------------------------------------------------------------
139 apiGarg :: Proxy GargAPI
141 ---------------------------------------------------------------------
143 schemaUiServer :: (Server api ~ Handler Swagger)
144 => Swagger -> Server (SwaggerSchemaUI' dir api)
145 schemaUiServer = swaggerSchemaUIServer
148 -- Type Familiy for the Documentation
149 type family TypeName (x :: *) :: Symbol where
151 TypeName Text = "Text"
152 TypeName x = GenericTypeName x (Rep x ())
154 type family GenericTypeName t (r :: *) :: Symbol where
155 GenericTypeName t (D1 ('MetaData name mod pkg nt) f x) = name
157 type Desc t n = Description (AppendSymbol (TypeName t) (AppendSymbol " | " n))
160 -- | Swagger Specifications
161 swaggerDoc :: Swagger
162 swaggerDoc = toSwagger (Proxy :: Proxy GargAPI)
163 & info.title .~ "Gargantext"
164 & info.version .~ "0.1.0"
165 -- & info.base_url ?~ (URL "http://gargantext.org/")
166 & info.description ?~ "REST API specifications"
167 -- & tags .~ Set.fromList [Tag "Garg" (Just "Main perations") Nothing]
168 & applyTagsFor (subOperations (Proxy :: Proxy GargAPI)(Proxy :: Proxy GargAPI))
169 ["Garg" & description ?~ "Main operations"]
170 & info.license ?~ ("AGPLV3 (English) and CECILL (French)" & url ?~ URL urlLicence )
172 urlLicence = "https://gitlab.iscpif.fr/gargantext/haskell-gargantext/blob/master/LICENSE"
174 -- | Output generated @swagger.json@ file for the @'TodoAPI'@.
175 swaggerWriteJSON :: IO ()
176 swaggerWriteJSON = BL8.writeFile "swagger.json" (encodePretty swaggerDoc)
179 -- | startGargantext takes as parameters port number and Ini file.
180 startGargantext :: PortNumber -> FilePath -> IO ()
181 startGargantext port file = do
182 print ("Starting Gargantext server" <> show port)
183 print ("http://localhost:" <> show port)
184 param <- databaseParameters file
185 conn <- connect param
188 startGargantextMock :: PortNumber -> IO ()
189 startGargantextMock port = do
190 print (pack "Starting Mock server")
191 print (pack $ "curl "
192 <> "-H \"content-type: application/json"
193 <> "-d \'{\"query_query\":\"query\"}\' "
194 <> "-v http://localhost:"