]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API.hs
[CLEAN] fix gitignore on cabal files in order to minimize merge/error risks.
[gargantext.git] / src / Gargantext / API.hs
1 {-|
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
8 Portability : POSIX
9
10 Main REST API of Gargantext (both Server and Client sides)
11
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
15 , MonadReader Conf m
16 , MonadLog (WithSeverity Doc) m
17 , MonadIO m) => m a
18 Thanks @yannEsposito for this.
19 -}
20
21 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
22
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 #-}
32
33 ---------------------------------------------------------------------
34 module Gargantext.API
35 where
36 ---------------------------------------------------------------------
37 import Gargantext.Prelude
38
39 import System.IO (FilePath, print)
40
41 import GHC.Generics (D1, Meta (..), Rep)
42 import GHC.TypeLits (AppendSymbol, Symbol)
43
44 import Control.Lens
45 import Data.Aeson.Encode.Pretty (encodePretty)
46 import qualified Data.ByteString.Lazy.Char8 as BL8
47 import Data.Swagger
48 import Data.Text (Text, pack)
49 --import qualified Data.Set as Set
50
51 import Database.PostgreSQL.Simple (Connection, connect)
52
53 import Network.Wai
54 import Network.Wai.Handler.Warp
55
56 import Servant
57 import Servant.Mock (mock)
58 import Servant.Swagger
59 import Servant.Swagger.UI
60 -- import Servant.API.Stream
61
62 --import Gargantext.API.Swagger
63 import Gargantext.API.FrontEnd (FrontEndAPI, frontEndServer)
64
65 import Gargantext.API.Node ( Roots , roots
66 , NodeAPI , nodeAPI
67 , NodesAPI , nodesAPI
68 )
69 import Gargantext.API.Count ( CountAPI, count, Query)
70 import Gargantext.Database.Utils (databaseParameters)
71
72 ---------------------------------------------------------------------
73 ---------------------------------------------------------------------
74 type PortNumber = Int
75 ---------------------------------------------------------------------
76 -- | API Global
77
78 -- | API for serving @swagger.json@
79 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
80
81 -- | API for serving main operational routes of @gargantext.org@
82 type GargAPI = "user" :> Summary "First user endpoint"
83 :> Roots
84
85 :<|> "node" :> Summary "Node endpoint"
86 :> Capture "id" Int :> NodeAPI
87
88 :<|> "corpus":> Summary "Corpus endpoint"
89 :> Capture "id" Int :> NodeAPI
90
91 :<|> "nodes" :> Summary "Nodes endpoint"
92 :> ReqBody '[JSON] [Int] :> NodesAPI
93
94 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
95 :<|> "count" :> Summary "Count endpoint"
96 :> ReqBody '[JSON] Query :> CountAPI
97
98 -- /mv/<id>/<id>
99 -- /merge/<id>/<id>
100 -- /rename/<id>
101 -- :<|> "static"
102 -- :<|> "list" :> Capture "id" Int :> NodeAPI
103 -- :<|> "ngrams" :> Capture "id" Int :> NodeAPI
104 -- :<|> "auth" :> Capture "id" Int :> NodeAPI
105 ---------------------------------------------------------------------
106 type SwaggerFrontAPI = SwaggerAPI :<|> FrontEndAPI
107
108 type API = SwaggerFrontAPI :<|> GargAPI
109
110 ---------------------------------------------------------------------
111 -- | Server declaration
112 server :: Connection -> Server API
113 server conn = swaggerFront
114 :<|> roots conn
115 :<|> nodeAPI conn
116 :<|> nodeAPI conn
117 :<|> nodesAPI conn
118 :<|> count
119
120 ---------------------------------------------------------------------
121 swaggerFront :: Server SwaggerFrontAPI
122 swaggerFront = schemaUiServer swaggerDoc
123 :<|> frontEndServer
124
125 gargMock :: Server GargAPI
126 gargMock = mock apiGarg Proxy
127
128 ---------------------------------------------------------------------
129 app :: Connection -> Application
130 app = serve api . server
131
132 appMock :: Application
133 appMock = serve api (swaggerFront :<|> gargMock)
134
135 ---------------------------------------------------------------------
136 api :: Proxy API
137 api = Proxy
138
139 apiGarg :: Proxy GargAPI
140 apiGarg = Proxy
141 ---------------------------------------------------------------------
142
143 schemaUiServer :: (Server api ~ Handler Swagger)
144 => Swagger -> Server (SwaggerSchemaUI' dir api)
145 schemaUiServer = swaggerSchemaUIServer
146
147
148 -- Type Familiy for the Documentation
149 type family TypeName (x :: *) :: Symbol where
150 TypeName Int = "Int"
151 TypeName Text = "Text"
152 TypeName x = GenericTypeName x (Rep x ())
153
154 type family GenericTypeName t (r :: *) :: Symbol where
155 GenericTypeName t (D1 ('MetaData name mod pkg nt) f x) = name
156
157 type Desc t n = Description (AppendSymbol (TypeName t) (AppendSymbol " | " n))
158
159
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 )
171 where
172 urlLicence = "https://gitlab.iscpif.fr/gargantext/haskell-gargantext/blob/master/LICENSE"
173
174 -- | Output generated @swagger.json@ file for the @'TodoAPI'@.
175 swaggerWriteJSON :: IO ()
176 swaggerWriteJSON = BL8.writeFile "swagger.json" (encodePretty swaggerDoc)
177
178
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
186 run port (app conn)
187
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:"
195 <> show port
196 <>"/count"
197 )
198 run port appMock
199